Fortran Best Practice Minibook

Some practices I suggest are
(1) Don’t use SAVed variables unless necessary.
(2) Use the explicit SAVE attribute when such variables are necessary. Especially programmers coming from other languages will thank you.
(3) If a variable will not change during a procedure, declare it as a PARAMETER
(4) Declare procedures PURE or ELEMENTAL if possible

I recently looked at a subroutine of Alan Miller

SUBROUTINE f1max(ndf, nf, f1, f5, f10, ier)
! Calculates approximations to the 1%, 5% & 10% points of the distribution
! of the maximum of NF values of an F-ratio with 1 d.f. for the numerator
! and NDF d.f. for the denominator.
IMPLICIT NONE
INTEGER, INTENT(IN)  :: ndf, nf
REAL, INTENT(OUT)    :: f1, f5, f10
INTEGER, INTENT(OUT) :: ier

! Local variables
REAL :: a1(6) = (/ 1.67649, 6.94330,  1.22627, 0.25319,  0.06136, -2.41097 /)
REAL :: a5(6) = (/ 1.28152, 4.93268, -0.29583, 0.28518, -0.23566, -1.60581 /)
REAL :: a10(6) = (/1.06642, 3.96276, -0.62483, 0.30228, -0.52843, -1.04499 /)

REAL :: log_nf, one = 1.0

IF (ndf < 4 .OR. nf < 1) THEN
  ier = 1
  RETURN
END IF
ier = 0

log_nf = LOG(DBLE(nf))

f1 = one + EXP(a1(1) + (a1(3)/ndf + a1(2))/ndf + a1(4)*log_nf          &
               + (a1(6)/ndf + a1(5))/nf)

f5 = one + EXP(a5(1) + (a5(3)/ndf + a5(2))/ndf + a5(4)*log_nf          &
               + (a5(6)/ndf + a5(5))/nf)

f10 = one + EXP(a10(1) + (a10(3)/ndf + a10(2))/ndf + a10(4)*log_nf     &
                + (a10(6)/ndf + a10(5))/nf)

RETURN
END SUBROUTINE f1max

Incorporating the guidelines above, I think it’s better to write it like this:

elemental subroutine f1max(ndf, nf, f1, f5, f10, ier)
! Calculates approximations to the 1%, 5% & 10% points of the distribution
! of the maximum of NF values of an F-ratio with 1 d.f. for the numerator
! and NDF d.f. for the denominator.
implicit none
integer      , intent(in)  :: ndf, nf
real(kind=dp), intent(out) :: f1, f5, f10
integer      , intent(out) :: ier
! Local variables
real(kind=dp), parameter ::  a1(6) =  [ 1.67649, 6.94330,  1.22627, 0.25319,  0.06136, -2.41097], &
                             a5(6) =  [ 1.28152, 4.93268, -0.29583, 0.28518, -0.23566, -1.60581], &
                            a10(6) =  [ 1.06642, 3.96276, -0.62483, 0.30228, -0.52843, -1.04499], &
                            one = 1.0_dp
real(kind=dp) :: log_nf
if (ndf < 4 .or. nf < 1) then
  ier = 1
  return
end if
ier = 0
log_nf = log(real(nf,kind=dp))
f1  = one + exp(a1(1) + (a1(3)/ndf + a1(2))/ndf + a1(4)*log_nf + (a1(6)/ndf + a1(5))/nf)
f5  = one + exp(a5(1) + (a5(3)/ndf + a5(2))/ndf + a5(4)*log_nf + (a5(6)/ndf + a5(5))/nf)
f10 = one + exp(a10(1) + (a10(3)/ndf + a10(2))/ndf + a10(4)*log_nf + (a10(6)/ndf + a10(5))/nf)
end subroutine f1max

The original subroutine could not be declared ELEMENTAL because of the implicitly SAVE’d variables.

5 Likes