Incorrect floating point exception from nvfortran 22.5

Hello,
I think I’ve found a bug in nvfortran 22.5, when compiling and running the following code

MODULE m1
    IMPLICIT NONE
    SAVE
    LOGICAL :: l1, l2, l3(1)
    TYPE t1
        INTEGER :: i
        TYPE (t1), POINTER :: n
    ENDTYPE t1
    TYPE (t1), TARGET :: t2
CONTAINS
    SUBROUTINE s1
        TYPE(t1),POINTER :: t3
        DOUBLE PRECISION :: r1, r2, r3, r4, r5, r6, r7(2,1), r8(1)
        LOGICAL :: l4
        INTEGER :: i1(1)
        l4 = .FALSE.
        r7 = 0
        IF ( l1 ) THEN
            IF ( l2 ) l4 = r7(2,1) > 0
            IF( l4 ) THEN
                CALL s2
            ENDIF
        ENDIF
        t3 => t2
        DO WHILE ( ASSOCIATED(t3) )
            IF ( l3(t3%i) ) THEN
                r2  = r3 / r4
                r5 = r2**3
                r5 = r5 * r6
            ENDIF
        t3 => t3%n
        ENDDO
    CONTAINS
        SUBROUTINE s2
        END SUBROUTINE
    END SUBROUTINE
END MODULE
PROGRAM p1
    use m1
    IMPLICIT NONE
    l1 = .FALSE.
    l2 = .FALSE.
    l3 = .FALSE.
    t2%i = 1
    NULLIFY(t2%n)
    CALL s1
END PROGRAM
$ nvfortran -V
nvfortran 22.5-0 64-bit target on x86-64 Linux -tp haswell
$ nvfortran -Ktrap=fp -Kieee -O2 code.f90
$ ./a.out 
Floating point exception (core dumped)

None of the floating point operations should be executed, so the floating point exception shouldn’t occur. The problem goes away when compiling without “-Kieee” or with “-O0” instead of “-O2”.

Hi Andrew,

I think what’s happening is that since “r2”, “r3”, and “r4” are invariant in the do while loop, it’s safe for the compiler to hoist this line so it’s only computed once. However since they are uninitialized, the “invalid” floating point exception is getting triggered. If “r3” and “r4” as initialized, then the FP exception goes away.

Is it your intent to have these variables be uninitialized?

-Mat

Hi Mat,

Thanks for the response.

Is it your intent to have these variables be uninitialized?

In the original function, r3 and r4 are both initialised within the loop and they are not invariant, but I still get a floating point exception.

You’re right that the problem goes away if they’re initialised in the simplified code I posted. The original code is much more complex. I’ll see if I can produce another example that reproduces the problem and get back to you.

I’ve tweaked the original example so that r2 is no longer invariant. (Strictly speaking r2 isn’t invariant in the original either unleass l3(t3%i) == .TRUE. on the first iteration of the loop.)

It still shows the same problem.

MODULE m1
    IMPLICIT NONE
    SAVE
    LOGICAL :: l1, l2, l3(1)
    TYPE t1
        INTEGER :: i
        DOUBLE PRECISION :: r9
        TYPE (t1), POINTER :: n
    ENDTYPE t1
    TYPE (t1), TARGET :: t2
CONTAINS
    SUBROUTINE s1
        TYPE(t1),POINTER :: t3
        DOUBLE PRECISION :: r1, r2, r3, r4, r5, r6, r7(2,1), r8(1)
        LOGICAL :: l4
        INTEGER :: i1(1)
        l4 = .FALSE.
        r7 = 0
        IF ( l1 ) THEN
            IF ( l2 ) l4 = r7(2,1) > 0
            IF( l4 ) THEN
                CALL s2
            ENDIF
        ENDIF
        IF ( ANY(l3) ) THEN
            r3 = 1D0
            r4 = 1D0
            r6 = 1D0
        ENDIF
        t3 => t2
        DO WHILE ( ASSOCIATED(t3) )
            IF ( l3(t3%i) ) THEN
                r2  = r3 / r4 / t3%r9
                r5 = r2**3
                r5 = r5 * r6
            ENDIF
        t3 => t3%n
        ENDDO
    CONTAINS
        SUBROUTINE s2
        END SUBROUTINE
    END SUBROUTINE
END MODULE
PROGRAM p1
    use m1
    IMPLICIT NONE
    l1 = .FALSE.
    l2 = .FALSE.
    l3 = .FALSE.
    t2%i = 1
    t2%r9 = 1D0
    NULLIFY(t2%n)
    CALL s1
END PROGRAM

I tried a few different systems (Haswell, Epyc, Skylake) and compiler versions (22.3, 22.5), but unfortunately I’m not able to reproduce the error.

% nvfortran -V22.5 -Kieee -Ktrap=fp -O2 code.f90  ; a.out
%

I think I posted the wrong version.
Try changing the line

r2  = r3 / r4 / t3%r9

to

r2  = r3 / r4 / (1D0 + t3%r9)

Looks to be a similar issue where “r3/r4” gets hoisted and since they are uninitialized variables, the invalid exception is being triggered. If “l3” gets initialized to true, and therefore r3 and r4 are set, then the error goes away.

I can submit an issue report. Though I’m concerned that the “fix” would be to disable invariant hoisting which is generally very useful for performance. Especially here given divides are expensive. Granted, they might be able to limit disabling to when -Kieee is used, given “-Kieee” deoptimizes code anyway.

Then again the “invalid” exception is extraneous in this case and shouldn’t impact the execution of the code Would it be ok for you to ignore this by not using the aggregate “fp” sub-option and instead use “-Ktrap=divz,ovf” to check just for overflows and divide-by-zero?

Thanks for your help.

I need to be able to trap all floating point exceptions, so -Ktrap=divz,ovf isn’t an option, unfortunately.

I can fix the problem either by initialising r3 and r4 with dummy values when .NOT.ANY(l3) or by hoisting the invariant r3/r4 and placing it in the IF statement by hand.

Could you submit an issue report, please? I have to say that I’m bothered that the compiler can produce an incorrect binary from correct code for any choice of optimisations. This problem doesn’t occur with pgfortran 20.4, gfortran or Intel. I don’t think the developers should have to take account of what the compiler might do when it’s optimising a loop.

Couldn’t the compiler check whether it’s safe to hoist an invariant and, if it’s unsafe, print a warning instead?

Done. Filed TPR #31984 and sent it engineering for further investigation.

-Mat