Testing concepts

Sorry for the very basic nature of this question (and it’s general scope) but I have now re-organised the 7000+ lines of code and want to start migrating this across to an F90 file slowly.

To explore this idea I decided to build a basic program file (first few stages of my wrapper program) and came across a few errors/concerns I can’t resolve easily (just ordered 3 books on Fortran, based upon earlier recommendation). Would appreciate pointers…

  1. I have separated out each variable into it’s own definition; is this the best approach?
  2. Is it okay to move the module into a separate file and include it, where I need it?
  3. Why is epsilon highlighted? I’m assuming a reserved word but the program works!?
  4. I believe I have defined the argument for record_time correctly (and setting it’s default value), yet I get an error message
   87 | subroutine record_time(sf)
      |                         1
Error: Dummy ‘sf’ at (1) cannot have an initializer
  1. I also get an error in relation to the calling of this subroutine; why?
   79 |     record_time("begin")
      |     1
Error: Unclassifiable statement at (1)

I have given the whole listing (in case you see something else I should pay attention to)…

module stellar_values

	implicit none
	
	integer, parameter			::	MJ    		= 4000
	integer, parameter			::	MH    		= 4
	integer, parameter			::	ME    		= 9
	integer, parameter			::  MTAU  		= 20000
	
	double precision, parameter	::	sig   		= 5.67051d-5
	double precision, parameter	::	pi    		= 3.14159265359d0
    double precision, parameter	::	grav  		= 6.6704d-8
    double precision, parameter	::	cc    		= 2.99792458d10
    double precision, parameter	::	hmass 		= 1.6732d-24
    double precision, parameter	::	xm_sun      = 1.989d33      ! Solar Mass (g)
    double precision, parameter ::	r_sun       = 6.9599d10   	! Solar Radius (cm)
    double precision, parameter ::	xl_sun      = 3.83d33     	! Solar Luminosity (erg/s)
    double precision, parameter ::	yr          = 3.1556736d+7	! yr in sec
    double precision, parameter ::	xmdot_sunyr = 6.30268d25	! acc. Rate in M_sun/yr
    
end module

program main

	double precision :: fluxM
	double precision :: fluxM1
	double precision :: fluxM2
    double precision :: deetee
    double precision :: tpeak
    double precision :: mdotzero
    double precision :: mdotstar
    double precision :: epsilon
    double precision :: tnaught
    double precision :: tostar
    double precision :: rateunit
    double precision :: fluxmin
    double precision :: fluxold
    double precision :: decel
    double precision :: decelr
    double precision :: initialrate
    double precision :: finalmass
    double precision :: fsolmass
    double precision :: numru
    double precision :: solmass
    double precision :: yearins
    double precision :: acc
    double precision :: mdotstarramped
    double precision :: divpart
    double precision :: taur
    double precision :: tauf
    double precision :: taueee
    double precision :: tburst
    double precision :: fburst
    
    integer 		 :: accmethod
    integer 		 :: iacc
    integer 		 :: ic
    integer 		 :: im
    integer 		 :: im1
    integer 		 :: steps
    integer 		 :: late_evolve
    
    character (1)  	 :: temp1		 = ""
    
    logical			 ::	massonly	 = .FALSE.
    
    if (command_argument_count() == 1) then

        call get_command_argument(1, temp1)

        if (temp1 == '1') then
        
            massonly = .TRUE.
        
        endif
    
    endif
    
    record_time("begin")
    
    record_time("end")

end program



subroutine record_time(sf)

	character (5), intent(in), optional	::	sf = "begin"

	character (8) 	:: curdate      = "000000:00"
    character (10)  :: curtime		= "000000:00"

	logical			:: fileexist	= .FALSE.

	real, save		:: start		= 0.00
    real, save 		:: finish		= 0.00
    
    
    inquire (file = "data.lst", exist = fileexist)

    if (fileexist) then
    
        open(7, file = "data.lst", status = "old", position = "append")
        
    else
        
        open(7, file = "data.lst", status = "new")
        
    end if

    call date_and_time(DATE = curdate, TIME = curtime)

	if (sf == "begin") then
			
		write (7, *) "Date of run (yyyymmdd) = ", curdate
		write (7, *) "Time of run (hhmmss.mmm) = ", curtime
			
		call cpu_time (start)
        
    else
        
		call cpu_time (finish)

		open (7, file = "data.lst", position = "append")
		write (7, *) "Execution time (s) = ", finish - start
        
    end if
        
	call flush (7)
    close (7)
    
end subroutine

Thank you in advance for any and all advice given (including “Stop asking questions!” or “Give up!” :laughing: )

record_time("begin")

should be

call record_time("begin")

subroutine record_time(sf)
	character (5), intent(in), optional	::	sf = "begin"

is not legal, as the compiler says, and should be something like

subroutine record_time(sf)
	character (len=*), intent(in), optional	::	sf
        character (len=100)                 ::    sf_
if (present(sf)) then
   sf_ = sf
else
   sf_ = "begin"
end if
! use sf_ , not sf in the rest of the subroutine

It is still allowed to declare variable double precision, but I suggest declaring a real with a kind as described here instead.

Modules files are linked by the linker. You should not use include like in FORTRAN 77 anymore. The epsilon is highlighted because of the intrinsic epsilon() function that returns the smallest number of a given type.

Thank you (DOH! I missed call!)

In terms of double precision and real, isn’t there a difference in precision?

Yes, and at the page I linked, it is explained that one way to declare a double precision variable is

!> Double precision real numbers, 15 digits, range 10⁻³⁰⁷ to 10³⁰⁷-1; 64 bits
integer, parameter :: dp = selected_real_kind(15, 307)
real(kind=dp) :: x

It’s a matter of taste. Unless you want to add a comment describing what a variable represents, I suggest that declaring multiple variable of the same type on a single line, since that will reduce the number of lines in a code. It is easier to understand a code if more of it fits on your screen. I suggest that the result of a function always be declared on a separate line, since it is neither an argument or a local variable.

Sorry but what is the advantage of doing it this way?

I note that you said "it is still allowed to declare variable double precision "; this implies it is not recommended.

I did (finally) read your link (I wasn’t able to originally, due to my employer’s firewall) and this does not appear to explain WHY this might be ‘best practice’.

I’m listing them like this primarily because I want to identify which ones are actually used (probably all of them) and for what purpose. I might then condense them down and do the assignment afterwards.

Thank you. :slight_smile:

In relation to your earlier example…

character (len=*), intent(in), optional	::	sf
character (len=100)                 ::    sf_

I notice you use len =, whilst many of the examples I have seen they reduce this to just the value (not sure you can do that with the *).

Is this just a personal preference?

When you use “DOUBLE PRECISION”, you are asking for the higher of the two precisions (REAL and DOUBLE PRECISION) guaranteed to be available in standard Fortran. But you don’t know HOW MUCH precision (and range) that type gives you. You can do a runtime check using the intrinsic functions PRECISION(1.0d0) and RANGE(1.0d0) and stop the program if they are not sufficient for your problem. You also don’t know if the operations are supported by hardware or are provided in software (would run perhaps x100 slower). On some past machines (and perhaps future ones too) REAL was the highest precision type available on the hardware and DOUBLE PRECISION was done in software.

With a REAL(wp) declaration, where wp=SELECTED_REAL_KIND(RANGE=required_range, PRECISION=required_precision) for constants required_range and required_precision, you are asking for specific properties of the real type and you are either going to get them and your program will compile, or you are not and the program will not compile. You still don’t know if it’s done in hardware or software, though.

Thank you so much, this explains precisely the reasoning behind moving from one to the other.

I am testing the code (where I can) with all double precision variables (and parameters) swapped to real.

The results so far seem good, so thank you so much; very enlightening.