1

We know we can optimise our code from outside.
We know in fortran programming we define variables first in the program. Then we can take inputs from outside (via read statements) but can we make a small code that take kind of variable from outside.

I.e. if we put in the terminal 4 kind 4(i.e.real(kind =4) ) variable is introduced ie if we put 8 kind 8(i.e real(kind=8) variable is introduced . Is there any way.
I know we can do three separate if loops to define the variables (namely kind 4 , kind 8 ,kind 16 and repeat the program the program three times ).
The code i wrote was for findinding value of y using eulers method. I want to generalise to any kind and calculate the time taken. I hope this can be done in lesser cumbersome way.

The code I wrote:

       program euler
       implicit none
       real(kind=4)::t,h,y,s,e,r
       real(kind=8)::t8,h8,y8,s8,e8,r8
       real(kind=16)::t16,h16,y16,s16,e16,r16
       integer::k,i
       t=0
       t8=0
       t16=0
       y=10
       y8=10
       y16=10
       print *,"enter the kind you want to work with"
       read(*,*) k
       !so if user writes 4 kind 4 variables would do the work
       if(k==4) then
       print *,"enter the grid step"
       read(*,*) h
       r=10*exp(-5.0)
       call cpu_time(s)
       do i=1,999999999
       if(0.le.t.and.t.le.25) then
       y=y-h*y/5.0
       t=t+h
      end if
      end do
      call cpu_time(e)
      print *,"solution is",y 
      print *,"the error is",(r-y)/r
      print *,"time taken in seconds =",e-s
      else if(k==8) then
      print *,"enter the grid step"
      read(*,*) h8
     r8=10*exp(-5.0D0)
      call cpu_time(s8)
      do i=1,999999999
      if(0.le.t8.and.t8.le.25) then
      y8=y8-h8*y8/5.0
      t8=t8+h8
      end if
      end do
      call cpu_time(e8)
      print *,"solution is",y8
      print *,"the error is",(r8-y8)/r8
      print *,"time taken in seconds for kind 8 =",e8-s8
      else if(k==16) then
      print *,"enter the grid step"
      read(*,*) h16
      r16=10*exp(-5.0D0)
      call cpu_time(s16)
      do i=1,999999999
      if(0.le.t16.and.t16.le.25) then
      y16=y16-h16*y16/5.0
      t16=t16+h16
      end if
      end do
      call cpu_time(e16)
      print *,"solution is",y16
      print *,"the error is",(r16-y16)/r16
      print *,"time taken in seconds for kind 16 =",e16-s16
      end if
      end program euler
 

But im looking something more smart and less cumbersome.

user187604
  • 148
  • 8
  • 3
    This question needs a lot of clarifications/explanations. What does it mean "to optimize code from outside?" or "we can use sort of password using get command arguments?". What program are you referring to that needs three loops? Remember to get an effective answer you need to explain the problem with some minimal code to demonstrate what the expected out should be and where the problem is. – John Alexiou Oct 31 '21 at 04:04
  • parameterized derived types (PDT) could be one possible solution. – Scientist Oct 31 '21 at 04:36
  • 1
    The above won't compile - could you please repost without line numbers. Note also real*4 etc. is not part of Fortran and has never been part of Fortran, please learn about Fortran 90 kinds which is the standard conforming and so portable way to specify the precision and accuracy of your variables - https://stackoverflow.com/questions/838310/fortran-90-kind-parameter . `Implicit None` would be nice as well. – Ian Bush Oct 31 '21 at 08:43
  • Without recompilation I think I can see how to do this, but I can't see an easy way - it will be total overkill for what you want. If recompilation is allowed for each kind I can see how to do it with one line of pre-processing and a simple shell script. If the second is OK I'll post an answer (once you fix the code in the question) – Ian Bush Oct 31 '21 at 08:51
  • Oh, and somebody may well recommend special compiler flags. **Don't** do this. It will lead to a life of pain. – Ian Bush Oct 31 '21 at 08:54
  • @VladimirF - I think you have the wrong link in your comment – Ian Bush Oct 31 '21 at 09:03
  • I have edited the question now. @Ian Bush anymore suggestion are welcome. – user187604 Oct 31 '21 at 09:18
  • @IanBush, would your answer be more suitable for [this other question](https://stackoverflow.com/q/25534202/3157076)? – francescalus Oct 31 '21 at 09:30
  • @francescalus Looks like it yes - but do you mean the recompilation method or the OO overkill method? I am very, very much hoping it's the former! – Ian Bush Oct 31 '21 at 09:41
  • I can see how to use `class(*)` or even a smart pointer for a variable that can be anything. But for a whole code path it would be extremely cumbersome. – Vladimir F Героям слава Oct 31 '21 at 09:44
  • @IanBush, I meant the former: that other question wants "do for multiple kinds" and this one is "do once, but support multiple kinds" (as I read them). "Recompilation" would be the first; polymorphism/templates the second. (We can probably suggest similar questions for the second, also.) – francescalus Oct 31 '21 at 09:45
  • @francescalus - OK, will do, but later - a house to clean and then friends to see first – Ian Bush Oct 31 '21 at 09:47
  • I think the question can be boiled down to how to bypass the error `A kind type parameter must be a compile-time constant` when using the same routine for different data types. – John Alexiou Oct 31 '21 at 16:08
  • @JohnAlexiou I would not be so sure about that. If yes, we have plenty of duplicates. – Vladimir F Героям слава Oct 31 '21 at 18:08
  • If you are only changing the kind, and all the other code stays the same, you might consider to apply "templates". Just write `real(kind=my_kind)`, and let the preprocessor substitute it with 8 or 4. This way you will only need a compiler directive. – Jommy Nov 01 '21 at 12:57
  • jommy please elaborate – user187604 Nov 01 '21 at 13:00
  • See for example https://stackoverflow.com/a/66078604/3676517 – Jommy Nov 02 '21 at 14:35

1 Answers1

1

I don't think this is 100% what you want because there are still three separate subroutines each for a different kind, but they are called using the interface euler which determines which one to use based on the arguments

program SO_Euler
use iso_fortran_env, only : sp=>real32, dp=>real64, qp=>real128, i4=>int32, i8=>int64
implicit none

interface euler
    procedure euler_driver_sp, euler_driver_dp, euler_driver_qp
end interface

real(sp), parameter :: r4 = 10*exp(-5.0)
real(dp), parameter :: r8 = 10*exp(-5d0)
real(qp), parameter :: r16 = 10*exp(-5q0)

real(sp) :: h
print *,"enter the grid step"
read(*,*) h    
print *, ""

call euler(r4, h)
call euler(r8, h)
call euler(r16, h)

contains 

subroutine euler_driver_sp(r,h_in)
real(sp), intent(in) :: r
real(sp), intent(in) :: h_in
real(sp) :: h, y, t
integer(i8) :: s, e, rate
integer :: i
    print '(a15,1x,g0)', "kind is ", kind(r)
    h = h_in
    t = 0
    y = 10
    call SYSTEM_CLOCK(s,rate)
    do i=1,999999999
        if(0<=t .and.  t<=25) then
            y=y-h*y/5
            t=t+h
        else
            exit
        end if            
    end do
    call SYSTEM_CLOCK(e,rate)
    print '(a15,1x,g0.15)',"solution is", y 
    print '(a15,1x,g0.15)',"the error is", (r-y)/r
    print '(a15,1x,g0.4,1x,a)',"time taken is", real(e-s)/rate,"seconds"
    print *, ""
end subroutine

subroutine euler_driver_dp(r, h_in)
real(dp), intent(in) :: r
real(sp), intent(in) :: h_in
real(dp) :: h, y, t
integer(i8) :: s, e, rate
integer :: i
    print '(a15,1x,g0)', "kind is ", kind(r)
    h = h_in    !! convert sp=>dp
    t = 0
    y = 10
    call SYSTEM_CLOCK(s,rate)
    do i=1,999999999
        if(0<=t .and.  t<=25) then
            y=y-h*y/5
            t=t+h
        else
            exit
        end if            
    end do
    call SYSTEM_CLOCK(e,rate)
    print '(a15,1x,g0.15)',"solution is", y 
    print '(a15,1x,g0.15)',"the error is", (r-y)/r
    print '(a15,1x,g0.4,1x,a)',"time taken is", real(e-s)/rate,"seconds"
    print *, ""
end subroutine

subroutine euler_driver_qp(r, h_in)
real(qp), intent(in) :: r
real(sp), intent(in) :: h_in
real(qp) :: h, y, t
integer(i8) :: s, e, rate
integer :: i
    print '(a15,1x,g0)', "kind is ", kind(r)
    h = h_in ! convert sp=>qp
    t = 0
    y = 10
    call SYSTEM_CLOCK(s,rate)
    do i=1,999999999
        if(0<=t .and.  t<=25) then
            y=y-h*y/5
            t=t+h
        else
            exit
        end if            
    end do
    call SYSTEM_CLOCK(e,rate)
    print '(a15,1x,g0.15)',"solution is", y 
    print '(a15,1x,g0.15)',"the error is", (r-y)/r
    print '(a15,1x,g0.4,1x,a)',"time taken is", real(e-s)/rate,"seconds"
    print *, ""
end subroutine


end program

here is some sample output of the procedure

 enter the grid step
0.000002

       kind is  4
    solution is .547848604619503E-01
   the error is .186920538544655
  time taken is .1020 seconds

       kind is  8
    solution is .673793765102040E-01
   the error is .138737586862949E-05
  time taken is .7200E-01 seconds

       kind is  16
    solution is .673793765102226E-01
   the error is .138737559174033E-05
  time taken is 1.535 seconds

Note that I am compiling in 64bit release mode, and have floating-point model not fast, but strict as well as the option to extend the precision of real constants.

John Alexiou
  • 28,472
  • 11
  • 77
  • 133