pgfortran: -O2 -Ktrap=fp gives FPE with 15.1, not 14.1

I have a case where pgfortran 14.1 with -O2 -Ktrap=fp has no problem,
but pgfortran 15.1 with the same flags gives a floating point exception.
Here is the code, comments at the start explain things.
Is this a problem with pgfortran 15.1?

C
C   Is there a bug in the PGI 15.1 Fortran compiler?
C   Look at this:
C     % pgfortran -g -O1 -Ktrap=fp -o bndf bndf.F
C     % ./bndf
C     DBNI(NBNDR-1)=    8.11920E-01
C
C     % pgfortran -g -O2 -o bndf bndf.F
C     % ./bndf
C     DBNI(NBNDR-1)=    8.11920E-01
C
C     % pgfortran -g -Ktrap=fp -o bndf bndf.F
C     % ./bndf
C     DBNI(NBNDR-1)=    8.11920E-01
C
C     % pgfortran -g -O2 -Ktrap=fp -o bndf bndf.F
C     % ./bndf
C     Floating point exception (core dumped)
C
C     % pgfortran -g -fast -Ktrap=fp -o bndf bndf.F
C     % ./bndf
C     Floating point exception (core dumped)
C
C   The combination of -O2 and -Ktrap=fp causes a floating-point exception?
C
C   Compiler used:
C     % pgfortran -V
C     pgfortran 15.1-0 64-bit target on x86-64 Linux -tp sandybridge
C
C   Hardware is: Intel Xeon CPU E5-2630 0 @ 2.30GHz
C
C   This problem does not occur with the 14.1 compiler.
C   This code is a small extract from a much larger program, I have
C   not tried to clean it up or boil it down to the smallest possible size.
C
      PROGRAM BNDF
      IMPLICIT NONE
      INTEGER :: NDM,NNODE,NNODE1,NFACE,NFBND,NBNDR,MXPPF
      REAL(KIND=8), DIMENSION(:), ALLOCATABLE   :: FBN,DBNI,FBF
      REAL(KIND=8), DIMENSION(:,:), ALLOCATABLE :: COORD
      REAL(KIND=8), DIMENSION(:), ALLOCATABLE   :: XFC,YFC,ZFC
      INTEGER, DIMENSION(:), ALLOCATABLE   :: NUMPPF
      INTEGER, DIMENSION(:,:), ALLOCATABLE :: IFACE,IPNT
      INTEGER :: I,J
      REAL(KIND=8) :: S
C
C
C   Just make up some numbers here.
C
      NDM     = 3
      NNODE   = 810
      NNODE1  = 900
      NFACE   = 925
      NFBND   = 129
      NBNDR   = 133
      MXPPF   = 3
      ALLOCATE ( XFC(NFBND),YFC(NFBND),ZFC(NFBND) )
      DO I = 1,NFBND
         XFC(I)  = I - 0.5
         YFC(I)  = 2.
         ZFC(I)  = 3.
      ENDDO
      ALLOCATE ( IFACE(NFACE,2),NUMPPF(NFACE),IPNT(NFACE,MXPPF),
     &           COORD(NNODE1,NDM),FBN(NBNDR),DBNI(NBNDR),FBF(NFBND) )
      IFACE(1:NFACE,1)  = 0
      IFACE(1:NFACE,2)  = 4
      NUMPPF(1:NFACE)   = 3
      DO J = 1,MXPPF
         DO I = 1,NFACE
C
C   IPNT(I,J)  = quasi-random number between 1 and NBNDR
C   Not using random for portability/repeatability/checkability reasons.
C   Instead use something with cosine function.
C
            S          = ABS(COS( REAL(I + (J-1)*NFACE) ))
            IPNT(I,J)  = REAL(NBNDR)*S
            IPNT(I,J)  = MAX(IPNT(I,J),1)
            IPNT(I,J)  = MIN(IPNT(I,J),NBNDR)
         ENDDO
      ENDDO
      DO I = 1,NFBND
         FBF(I)  = I
      ENDDO
      DO I = 1,NNODE1
         COORD(I,1)   = I
         COORD(I,2)   = 2.
         COORD(I,3)   = 3.
      ENDDO
      CALL BNDF_TO_BNDN( NDM,NNODE,NNODE1,NFACE,NFBND,NBNDR,MXPPF,
     &                   COORD,FBN,DBNI,IFACE,NUMPPF,IPNT,FBF,
     &                   XFC,YFC,ZFC )
C
C   Phony printout here so compiler doesn't optimize everything away.
C
      WRITE(*,"('DBNI(NBNDR-1)=',ES15.5)") DBNI(NBNDR-1)
      END PROGRAM BNDF
C
C
      SUBROUTINE BNDF_TO_BNDN( NDM,NNODE,NNODE1,NFACE,NFBND,NBNDR,MXPPF,
     &                         COORD,FBN,DBNI,IFACE,NUMPPF,IPNT,FBF,
     &                         XFC,YFC,ZFC )
      IMPLICIT NONE
      INTEGER :: NDM,NNODE,NNODE1,NFACE,NFBND,NBNDR,MXPPF
      INTEGER :: IFACE(NFACE,2),NUMPPF(NFACE),IPNT(NFACE,MXPPF)
      REAL(8) :: COORD(NNODE1,NDM),FBN(NBNDR),DBNI(NBNDR),FBF(NFBND)
      REAL(8), DIMENSION(NFBND) :: XFC,YFC,ZFC
C
      INTEGER :: NF,MTYPE,K,IP,I
      REAL(8) :: DX,DY,DZ,RBND
C
      DBNI(:) = 0.0
      FBN(:)  = 0.0
C
      LOOP1: DO NF = 1,NFBND
         MTYPE = IFACE(NF,2)
         IF (MTYPE.NE.4 .AND. MTYPE.NE.44) CYCLE LOOP1
         DO K = 1,NUMPPF(NF)
            IP       = IPNT(NF,K)
            DX       = XFC(NF) - COORD(IP,1)
            DY       = YFC(NF) - COORD(IP,2)
            DZ       = ZFC(NF) - COORD(IP,3)
            RBND     = 1.0/SQRT(DX*DX+DY*DY+DZ*DZ)
            FBN(IP)  = FBN(IP) + RBND*FBF(NF)
            DBNI(IP) = DBNI(IP) + RBND
         ENDDO
      ENDDO LOOP1
      DO I = 1,NBNDR
         IF (DBNI(I).NE.0.) FBN(I) = FBN(I)/DBNI(I)
      ENDDO
C
      RETURN
      END SUBROUTINE BNDF_TO_BNDN

Hi Dennis,

Thanks for the report. What’s happening is with AVX, we are now able to vectorize conditional loop such as your “DO I = 1,NBNDR” loop. The loop is vecortized but when/if the condition is false, the value isn’t used and you get the expected answers.

What shouldn’t be happening is the “invalid” exception being thrown with a AXV divide instruction when -Ktrap is set. We set a mask bit to prevent this from occurring but accidently missed it in one spot when the loop is unrolled. I’ve added a problem report (TPR#21343) and sent it to engineering.

Best Regards,
Mat

TPR 21343 - UF: pgfortran: -O2 -Ktrap=fp gives FPE with 15.1, not 14.1

has been corrected in the current 15.3 release.

thanks,
dave