This is the mail archive of the gcc-bugs@gcc.gnu.org mailing list for the GCC project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]
Other format: [Raw text]

[Bug fortran/30113] New: ICE in trunc_int_for_mode


The following Fortran code, from the gamess CPU2006 benchmark, fails with an
ICE on the 4.1 branch when compiled with -m32 -O3.


      SUBROUTINE RD2PDM(INFILE,TPDM,GBUF,LABS,NINTMX,IPIN)
C
      IMPLICIT DOUBLE PRECISION(A-H,O-Z)
      LOGICAL READMORE
      INTEGER LABS(*),IPIN(*)
      DOUBLE PRECISION  TPDM(*),GBUF(*)
      COMMON /PCKLAB/ LABSIZ
C
C      CALL SEQREW(INFILE)
      READMORE = .TRUE.
      DO WHILE (READMORE)
        NG = 0
        CALL PREAD(INFILE,GBUF,LABS,NG,NINTMX)
        IF (NG.LE.0) READMORE = .FALSE.
        MG = IABS(NG)
        DO M = 1, MG
C
C  UNPACK LABELS
C
                       NPACK = M
                       IF (LABSIZ .EQ. 2) THEN
                         LABEL = LABS( 2*NPACK - 1 )
                         IPACK = ISHFT( LABEL, -16 )
                         JPACK = IAND(  LABEL, 65535 )
                         LABEL = LABS( 2*NPACK     )
                         KPACK = ISHFT( LABEL, -16 )
                         LPACK = IAND(  LABEL, 65535 )
                       ELSE IF (LABSIZ .EQ. 1) THEN
                         LABEL = LABS(NPACK)
                         IPACK = ISHFT( LABEL, -24 )
                         JPACK = IAND( ISHFT( LABEL, -16 ), 255 )
                         KPACK = IAND( ISHFT( LABEL,  -8 ), 255 )
                         LPACK = IAND( LABEL, 255 )
                       END IF
                       I = IPACK
                       J = JPACK
                       K = KPACK
                       L = LPACK
          IJ = IPIN(MAX(I,J)) + MIN(I,J)
          KL = IPIN(MAX(K,L)) + MIN(K,L)
          IJKL = IPIN(MAX(IJ,KL)) + MIN(IJ,KL)
          TPDM(IJKL) = GBUF(M)
        END DO  ! CURRENT BATCH 
      END DO  ! NEXT BATCH
      RETURN
      END


temp> gfortran -c -O3 -m32 gamess-failure.f
gamess-failure.f: In function #rd2pdm#:
gamess-failure.f:45: internal compiler error: in trunc_int_for_mode, at
explow.c:54
Please submit a full bug report,


-- 
           Summary: ICE in trunc_int_for_mode
           Product: gcc
           Version: 4.1.2
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: pthaugen at us dot ibm dot com
 GCC build triplet: powerpc64-linux
  GCC host triplet: powerpc64-linux
GCC target triplet: powerpc64-linux


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30113


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]