1

I implemented the following code in Fortran 90, where I want a parameter tau to be calculated using logarithms of some parameters, only if these are within appropriate ranges.

MODULE nrtype
    INTEGER, PARAMETER :: SP=KIND(1.0)
    INTEGER, PARAMETER :: DP=KIND(1.0d0)
    INTEGER, PARAMETER :: I4B=SELECTED_INT_KIND(9)
    INTEGER, PARAMETER :: I2B=SELECTED_INT_KIND(4)
    INTEGER, PARAMETER :: I1B=SELECTED_INT_KIND(2)
    INTEGER, PARAMETER :: SPC=KIND((1.0,1.0))
    INTEGER, PARAMETER :: DPC=KIND((1.0D0,1.0D0))
    INTEGER, PARAMETER :: LGT=KIND(.TRUE.)
END MODULE

MODULE parameters
USE nrtype
    REAL(DP), PARAMETER :: beta=.98_dp
    REAL(DP), PARAMETER :: maxtol=1.0e-6_dp
    REAL(DP), PARAMETER :: theta=1.0_dp
    REAL(DP), PARAMETER :: delta=0.0_dp
END MODULE

PROGRAM mainp
    USE parameters
    USE nrtype

    IMPLICIT NONE

    INTEGER(I4B) :: tau
    REAL(DP) :: taustar

    IF (theta > 1.0_dp .AND. (delta > 0.0_dp .AND. delta < 1.0_dp)) THEN
        taustar=LOG(maxtol/(beta*(1.0_dp-delta)*(theta-1.0_dp)))/LOG(beta*delta)
        tau=CEILING(taustar,REAL(DP))
    ENDIF

    IF (theta > 1.0_dp .AND. delta==0.0_dp) THEN
        tau=1
    ELSEIF (theta == 1.0_DP .OR. delta==1.0_DP) THEN
        tau=0
    ENDIF

END PROGRAM main

However, when compiling using gfortran 6.1 in a MacBook Air 2013 with OSX El Capitan, I get the following error:

program.f90:30:69:

    taustar=LOG(maxtol/(beta*(1.0_dp-delta)*(theta-1.0_dp)))/LOG(beta*delta)
                                                                 1
Error: Argument of LOG at (1) cannot be less than or equal to zero

What mistake am I doing on the code? It looks as if the IF statement is not being recognised.

3 Answers3

0

The expression LOG(beta*delta) is considered invalid by gfortran when delta is 0 constant. It doesn't matter that it is in an unreachable part of code. It is invalid. You can't just put it in an if condition or anywhere else.

A solution might be to not declare delta as parameter or to use some preprocessor. Other compilers might accept it (I tried ifort). I am not sure about the standard.

  • Thank you very much, my apologies for not adding the fortran tag before. – David Moreno Aug 05 '16 at 22:27
  • 1
    How do you come to this conclusion? I'd just consider this a compiler bug. Beyond type, restrictions on the value of the actual argument to LOG apply when the procedure is invoked - which requires execution of the statement containing the procedure reference, and that should not happen. There are other issues with the example that should prevent it from compiling though. – IanH Aug 05 '16 at 22:47
  • From my experience with that compiler. It is possible, that it is allowed, but that compiler doesn't accept it. That's why all the hassle (workarounds) in http://stackoverflow.com/questions/31971836/having-parameter-constant-variable-with-nan-value-in-fortran – Vladimir F Героям слава Aug 05 '16 at 23:12
0

(Though this is something like a long comment...) gfortran-6.1 on Mac OSX10.9 gave the following information when compiled with -fdump-fortran-original or -fdump-fortran-optimized:

  code:
  IF .false.
    ASSIGN mainp:taustar (/ log[(((/ 9.9999999999999995e-7_8
                            (parens (* (* 9.7999999999999998e-1_8 
                            (parens 1.0000000000000000_8))
                            (parens 0_8))))))] log[((0_8))])
    ASSIGN mainp:tau ceiling[((mainp:taustar) (8.00000000))]
  ENDIF
  IF .false.
    ASSIGN mainp:tau 1  ELSE
    IF .true.
      ASSIGN mainp:tau 0
    ENDIF
  ENDIF

The result was the same for all -O0, -O2, -O3, and -O5.

ifort-14.0 compiled the program without complaining the unreachable log line (while complaining about tau=CEILING(...)). The third IF block corresponding to theta == 1.0_DP .OR. delta==1.0_DP was executed.

Oracle fortran 12.4 was a bit interesting because it gave a warning like this:

taustar=LOG(maxtol/(beta*(1.0_dp-delta)*(theta-1.0_dp)))/LOG(beta*delta)
                  ^                                     ^        ^                                        
"test.f90", Line = 31, Column = 27: WARNING: A divisor of zero was detected in an expression.                                                        
"test.f90", Line = 31, Column = 65: WARNING: Evaluation of this constant expression produced a NaN or other abnormal value.
"test.f90", Line = 31, Column = 74: WARNING: The argument is not in the valid range for this intrinsic.

but again the third IF block was executed.

Also, if I declared delta as a usual variable (not with the PARAMETER attribute), gfortran also executed the third IF block after removing the CEILING(...) (this line seems problematic for a different reason).


A workaround may be to assign the constants to local variables once and pass them to LOG(...)/LOG(...) (in a sense, to cheat gfortran!):

REAL(DP) :: arg1, arg2, tmp

IF (theta > 1.0_dp .AND. (delta > 0.0_dp .AND. delta < 1.0_dp)) THEN
    tmp = beta * (1.0_dp - delta) * (theta - 1.0_dp)
    arg1 = maxtol / tmp
    arg2 = beta * delta
    taustar = LOG( arg1 ) / LOG( arg2 )
ENDIF

This seems to work when theta and delta have the above corner-case values and give correct results for other cases. In the former case, the output of gfortran -fdump-fortran-original becomes like this:

code:
IF .false.
    ASSIGN mainp:tmp 0_8
    ASSIGN mainp:arg1 (/ 9.9999999999999995e-7_8 mainp:tmp)
    ASSIGN mainp:arg2 0_8
    ASSIGN mainp:taustar (/ __log_r8[[((mainp:arg1))]] __log_r8[[((mainp:arg2))]])
ENDIF
roygvib
  • 7,218
  • 2
  • 19
  • 36
0

This error is being thrown at compile time, not run-time.

Since beta and delta are constants, the compiler is taking a shortcut and evaluating the log before the program runs. Since it is a log of zero, it is throwing an error, as it should.

I'm not sure what you are trying to do. The compiler is right, this will always be a log of zero. Are you sure you want delta to be a constant?

NuclearFission
  • 251
  • 2
  • 5