------- Comment #7 from dominiq at lps dot ens dot fr  2010-03-06 17:09 -------
With the following patch the test in comment #6 is hopefully valid (it compiles
with '-O2 -fwhole-file', but gives an ICE with '-O3 -fwhole-file'):

--- pr41056.f90 2010-02-24 17:38:27.000000000 +0100
+++ pr41056_db.f90      2010-02-24 17:55:51.000000000 +0100
@@ -1,16 +1,19 @@
-! { dg-do compile }
       MODULE MAIN1
       INTEGER :: INCSET , IXYSET , IEVSET , IHLSET , IFGSET, DBGUNT
+      INTEGER, PARAMETER :: NLVLS = 20
       LOGICAL ISTA , IEND , NEWID , UNSTAB , STABLE , DEBUG
       LOGICAL ::  PVMRM=.FALSE.
       CHARACTER SRCTYP*8 
       ALLOCATABLE :: SRCTYP(:)
+      REAL :: GRIDHT(NLVLS) , GRIDWS(NLVLS), GRIDSV(NLVLS), GRIDSW(NLVLS) ,
GRIDEPS(NLVLS)
       END
       USE MAIN1
+      allocate(SRCTYP(2))
+      ISRC = 1
       IF ( STABLE .OR. (UNSTAB .AND. (HS.GE.ZI)) ) THEN
          IF ( PPF.LT.1.0 ) THEN
             CALL GINTRP(GRIDHT(NDXEFF),GRIDSV(NDXEFF),GRIDHT(NDXEFF+1), &
-     &                               HTEFF,EPSEFF3)
+     &                               HTEFF,EPSEFF3,VALUE)
          ENDIF
       ENDIF
       IF ( SRCTYP(ISRC).EQ.'POINT' ) THEN
@@ -53,3 +56,7 @@
       IF ( STABLE .OR. (UNSTAB .AND. (HS.GE.ZI)) ) THEN
         ENDIF
       END
+      SUBROUTINE GINTRP(HTBELO,VBELOW,HTABOV,VABOVE,REQDHT,VALUE)
+      REAL VALUE , HTBELO , VBELOW , HTABOV , VABOVE , REQDHT
+      END
+

[macbook] f90/bug% gfc -O3 -fwhole-file pr41056_db.f90
pr41056_db.f90: In function 'anyavg_.clone.0':
pr41056_db.f90:47:0: error: type mismatch between an SSA_NAME and its symbol
while verifying SSA_NAME hts_1 in statement
hts_1 = (real(kind=4)[0:D.1596] * restrict) &gridht;
pr41056_db.f90:47:0: error: type mismatch between an SSA_NAME and its symbol
pr41056_db.f90:47:0: error: in statement
hts_1 = (real(kind=4)[0:D.1596] * restrict) &gridht;
pr41056_db.f90:47:0: internal compiler error: verify_ssa failed


-- 


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

Reply via email to