Separation of declaration and initiation of variables

real :: x = 0.5
!vs
real :: x
x = 0.5

I kind of remember someone mentioned before that the declaration and initiation of variables should be separated. I can’t remember the reason behind this.

The reason is to avoid implicit save when such code appears in a procedure. Here is an example.

module save_mod
implicit none
contains
!
function bad_factorial(n) result(nfac)
integer, intent(in) :: n
integer             :: nfac
integer             :: j
integer             :: i = 1 ! has same effect as line below
! integer, save       :: i = 1
do j=2,n
   i = i*j
end do
nfac = i
end function bad_factorial
!
function factorial(n) result(nfac)
integer, intent(in) :: n
integer             :: nfac
integer             :: i,j
i = 1
do j=2,n
   i = i*j
end do
nfac = i
end function factorial
end module save_mod
!
program test_save
use save_mod, only: factorial, bad_factorial
implicit none
print*,bad_factorial(3),bad_factorial(3) ! 6 36
print*,factorial(3),factorial(3) ! 6 6
end program test_save
2 Likes

“initialization” is a somewhat ambiguous word, and can mean several things.

1, Initialization can be performed by the compiler or linker; a constant, such as 32.174, or a constant expression, such as acos(-1.0), can be placed into a read-only program section.

  1. When the program starts running, it can call an initialization subroutine, in which data files are read, expressions calculated, various device readings taken such as the clock, fan speed, temperature of CPU, etc. Such an initialization subroutine would not be invoked again.

  2. Some initializations may have to done every time a function or subroutine is entered.

  3. Other initializations may be formed every time that a block of code is entered. For example, we write blocks such as

sumx = 0.0
do i = 1, n
   sumx = sumx + ...
end do

Just as we have finalization routines as components of derived types, we could have (if the language some day provides for it) initialization routines as components of derived types. In such a routine, we might allocate arrays, open files, check that sufficient memory and disk space are available, etc.

Is this explained in the Fortran best practice? I couldn’t find it.

In the tutorial, the section on variables says

Watch out for assignment at declaration: integer :: amount = 1 . This is NOT a normal initialisation; it implies the save attribute which means that the variable retains its value between procedure calls. Good practice is to initialise your variables separately to their declaration.

2 Likes

My bad. Since this is a correctness issue instead of a best practice issue, it makes sense to stay in the tutorial.

IMHO this implicit saving is controversial. For people coming from C world (where it requires static) can be pretty misleading. We fight implicit mapping of types (the implicit none issue) and nobody seems to contest implicit save.

@jacobwilliams has on several occasions (I’m too lazy to dig them out now). Personally, I learned Fortran before C so it never bothered me. One problem of using save is it can interfere with multi-threading; some legacy ODE solvers rely upon saved variables between calls making them thread-unsafe.

I disagree :grin:

See here: Deprecate and remove implicit save behavior · Issue #40 · j3-fortran/fortran_proposals · GitHub

Implicit save is terrible and has to go!

@msz59 , “nobody” is entirely inaccurate, but the number of people who contest is low but I have long been among the few who have been trying to find a way to address this in the language standard. I have posted a lot on online forums on this.

See the latest comment here where I even indicate this is an aspect where I will be entirely supportive of breaking the backward compatibility position with the language standard. For the benefits of doing so will far exceed the consequences of breaking some existing code. On the latter, I even contest the existence of any code that employs the implicit save feature on purpose. So I see little value in holding on to it. Mistakes happen, on this I think the overall community should bear the cost and move on by ridding the language of this abominable semantics.

Well, for module variables, implicit save is more acceptable than for the local variables in a procedure. Modules are like sort of libraries, with the code (procedures, methods) and data (the state).

Ok, sorry for that nobody. Let it be few.

I can say two things without exaggeration:

  • I have never seen anyone intentionally use the implicit save feature. Only by accident.
  • Everyone I’ve ever worked with or introduced Fortran to has introduced implicit save bugs into Fortran code at one time or another. One remained unnoticed for a decade at NASA. I hate this stupid feature.
1 Like

In some old codes (or new codes mechanically translated from old codes), some variables that function as named constants are initialized in the declaration and have the implicit save behavior. This could be faster than setting them in executable statements, although making them PARAMETERs is preferable. For example, in this code by Alan Miller, who was an experienced Fortran 77 and Fortran 90 programmer, I think the implicit save is intentional:

SUBROUTINE ppnd16 (p, normal_dev, ifault)

! ALGORITHM AS241  APPL. STATIST. (1988) VOL. 37, NO. 3

! Produces the normal deviate Z corresponding to a given lower
! tail area of P; Z is accurate to about 1 part in 10**16.

! The hash sums below are the sums of the mantissas of the
! coefficients.   They are included for use in checking
! transcription.

! This ELF90-compatible version by Alan Miller - 20 August 1996
! N.B. The original algorithm is as a function; this is a subroutine

REAL (dp), INTENT(IN)   :: p
INTEGER, INTENT(OUT)    :: ifault
REAL (dp), INTENT(OUT)  :: normal_dev

! Local variables

REAL (dp) :: zero = 0.d0, one = 1.d0, half = 0.5d0, split1 = 0.425d0,  &
             split2 = 5.d0, const1 = 0.180625d0, const2 = 1.6d0, q, r

! Coefficients for P close to 0.5

REAL (dp) :: a0 = 3.3871328727963666080D0, &
             a1 = 1.3314166789178437745D+2, &
             a2 = 1.9715909503065514427D+3, &
             a3 = 1.3731693765509461125D+4, &
             a4 = 4.5921953931549871457D+4, &
             a5 = 6.7265770927008700853D+4, &
             a6 = 3.3430575583588128105D+4, &
             a7 = 2.5090809287301226727D+3, &
             b1 = 4.2313330701600911252D+1, &
             b2 = 6.8718700749205790830D+2, &
             b3 = 5.3941960214247511077D+3, &
             b4 = 2.1213794301586595867D+4, &
             b5 = 3.9307895800092710610D+4, &
             b6 = 2.8729085735721942674D+4, &
             b7 = 5.2264952788528545610D+3
! HASH SUM AB    55.8831928806149014439

! Coefficients for P not close to 0, 0.5 or 1.

REAL (dp) :: c0 = 1.42343711074968357734D0, &
             c1 = 4.63033784615654529590D0, &
             c2 = 5.76949722146069140550D0, &
             c3 = 3.64784832476320460504D0, &
             c4 = 1.27045825245236838258D0, &
             c5 = 2.41780725177450611770D-1, &
             c6 = 2.27238449892691845833D-2, &
             c7 = 7.74545014278341407640D-4, &
             d1 = 2.05319162663775882187D0, &
             d2 = 1.67638483018380384940D0, &
             d3 = 6.89767334985100004550D-1, &
             d4 = 1.48103976427480074590D-1, &
             d5 = 1.51986665636164571966D-2, &
             d6 = 5.47593808499534494600D-4, &
             d7 = 1.05075007164441684324D-9
! HASH SUM CD    49.33206503301610289036

! Coefficients for P near 0 or 1.

REAL (dp) :: e0 = 6.65790464350110377720D0, &
             e1 = 5.46378491116411436990D0, &
             e2 = 1.78482653991729133580D0, &
             e3 = 2.96560571828504891230D-1, &
             e4 = 2.65321895265761230930D-2, &
             e5 = 1.24266094738807843860D-3, &
             e6 = 2.71155556874348757815D-5, &
             e7 = 2.01033439929228813265D-7, &
             f1 = 5.99832206555887937690D-1, &
             f2 = 1.36929880922735805310D-1, &
             f3 = 1.48753612908506148525D-2, &
             f4 = 7.86869131145613259100D-4, &
             f5 = 1.84631831751005468180D-5, &
             f6 = 1.42151175831644588870D-7, &
             f7 = 2.04426310338993978564D-15
! HASH SUM EF    47.52583317549289671629

ifault = 0
q = p - half
IF (ABS(q) <= split1) THEN
  r = const1 - q * q
  normal_dev = q * (((((((a7*r + a6)*r + a5)*r + a4)*r + a3)*r + a2)*r + a1)*r + a0) / &
           (((((((b7*r + b6)*r + b5)*r + b4)*r + b3)*r + b2)*r + b1)*r + one)
  RETURN
ELSE
  IF (q < zero) THEN
    r = p
  ELSE
    r = one - p
  END IF
  IF (r <= zero) THEN
    ifault = 1
    normal_dev = zero
    RETURN
  END IF
  r = SQRT(-LOG(r))
  IF (r <= split2) THEN
    r = r - const2
    normal_dev = (((((((c7*r + c6)*r + c5)*r + c4)*r + c3)*r + c2)*r + c1)*r + c0) / &
             (((((((d7*r + d6)*r + d5)*r + d4)*r + d3)*r + d2)*r + d1)*r + one)
  ELSE
    r = r - split2
    normal_dev = (((((((e7*r + e6)*r + e5)*r + e4)*r + e3)*r + e2)*r + e1)*r + e0) / &
             (((((((f7*r + f6)*r + f5)*r + f4)*r + f3)*r + f2)*r + f1)*r + one)
  END IF
  IF (q < zero) normal_dev = - normal_dev
  RETURN
END IF
RETURN
END SUBROUTINE ppnd16

If you look at the original code, these variables were parameters! :slight_smile: So, this conversion is definitely a step in the wrong direction.

For example, you can see it here: https://csg.sph.umich.edu/abecasis/gas_power_calculator/algorithm-as-241-the-percentage-points-of-the-normal-distribution.pdf

2 Likes

I suggest you think of it as, “Let it be [a few](The Difference Between "Few" and "A Few" | Britannica Dictionary

Appears like an appeal from authority in the wrong direction. The “authority” appears to have had no good reason to do what was done, not a good instance of coding, perhaps inexperience with Fortran 90/95 even, is all that is.

1 Like

Unfortunately removing the “implicitly declaring save by initialization” would turn vaid code into valid code with different behaviour, which is even more problematic than turning valid into invalid code that no longer compiles (as with removing “implicit none”).

To avoid this, one wouls have to enforce the separation of declaration and initialization of local non-parameter variables.

However, I fully agree that this feature is rather a quirk of the language. I also had bugs due to implicit save.

So maybe compilers should warn about the potentially unexpected behaviour (Disclaimer: I have not checked whether such warnings already exist).

I admit I often have to consult a dictionary to understand your ornate phrases but in this particular situation I well know the difference. I meant [few].

I would also opt for non-save, non-parameter declaration+initialisation to be a compile-time error, or at the very least a warning.

1 Like