The following codes from pr29921 and pr35770:

ibook-dhum] f90/bug% cat pr29921.f90
! { dg-do compile }
      SUBROUTINE foo
      IMPLICIT DOUBLE PRECISION (A-H,O-Z)
      LOGICAL MASWRK
      COMMON /FRAME / W1,W2,W3
      COMMON /FRAMES/ X1,Y1,Z1,X2,Y2,Z2,X3,Y3,Z3
      PARAMETER (ZERO=0.0D+00, ONE=1.0D+00)
      IF (IGROUP .EQ. 1) GO TO 600
      IF (IGROUP .EQ. 2) GO TO 620
  600 NT = 1
  620 CONTINUE
      IF (RHO .GT. TOL) THEN
         Y3 = RFIND('Y3      ',IERR)
            IF(IERR.NE.0) CALL ABRT
         Z3 = RFIND('Z3      ',IERR)
            IF(IERR.NE.0) CALL ABRT
         IF (MASWRK) WRITE (IP,9048) X3,Y3,Z3
      ELSE
         X1 = ZERO
         Y1 = ZERO
         Z1 = ZERO
         Z3 = ZERO
         X2 = ONE
         Y3 = ONE
      END IF
      W2 = (Z2-Z1)*(X3-X1)-(Z3-Z1)*(X2-X1)
 9048 FORMAT(9F10.5)
      END
[ibook-dhum] f90/bug% cat pr35770.f90
! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]
!maybe also see 34784?


      implicit character (s)  ! removing this fixes the problem
      REAL RDA(10)
      RDA = 0

      RDA(J1) = S_REAL_SQRT_I(RDA(J1))

      CONTAINS

      ELEMENTAL FUNCTION S_REAL_SQRT_I(X) RESULT (R)
      REAL, INTENT(IN)  ::  X
      REAL              ::  R
        R = 0.0
      END FUNCTION S_REAL_SQRT_I     !internal procedure

      END

gives "f951: internal compiler error: Bus error" after revision 134867. The bus
errors disappear if I revert the revision, while pr35770 gives:

      RDA(J1) = S_REAL_SQRT_I(RDA(J1))
               1
Error: Can't convert CHARACTER(1) to REAL(4) at (1)


-- 
           Summary: [4.4 Regression] "f951: internal compiler error: Bus
                    error" due to revision 134867
           Product: gcc
           Version: 4.4.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: dominiq at lps dot ens dot fr
 GCC build triplet: *-apple-darwin9
  GCC host triplet: *-apple-darwin9
GCC target triplet: *-apple-darwin9


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

Reply via email to