public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/37236]  New: internal compiler error: in mark_operand_necessary, at tree-ssa-dce.c:242
@ 2008-08-25 19:40 ronis at ronispc dot chem dot mcgill dot ca
  2008-08-25 19:58 ` [Bug middle-end/37236] " burnus at gcc dot gnu dot org
                   ` (14 more replies)
  0 siblings, 15 replies; 16+ messages in thread
From: ronis at ronispc dot chem dot mcgill dot ca @ 2008-08-25 19:40 UTC (permalink / raw)
  To: gcc-bugs

I've got some old fortran code that has compiled with dozens of gcc versions. 
I tried recompiling with 4.3.1 and I get an internal compiler error if I try to
compile with my usual compiler flags for this project.

Building with -O1 works.  I've also played around with removing various
combinations of the -f flags and -malign-double, but this didn't seem to change
anything.

/usr/bin/gfortran -O3 -march=pentium4 -ffast-math -funroll-loops
-fomit-frame-pointer -malign-double -fPIC -c -o fftrc.lo fftrc.f
fftrc.f:98.8:

      X(2) = DCMPLX(THETA-TP,ZERO)                                      
       1
Warning: Array reference at (1) is out of bounds (2 > 1) in dimension 1
fftrc.f: In function 'fftrc':
fftrc.f:78: internal compiler error: in mark_operand_necessary, at
tree-ssa-dce.c:242
Please submit a full bug report,
with preprocessed source if appropriate.
See <http://gcc.gnu.org/bugs.html> for instructions.
make: *** [fftrc.lo] Error 1

Here's some detail about my gcc installation:

gcc -v
Using built-in specs.
Target: i686-pc-linux-gnu
Configured with: ../gcc/configure --host=i686-pc-linux-gnu --prefix=/usr
--with-gnu-as --enable-shared --with-gnu-ld --enable-threads=posix
--with-ecj-jar=/usr/share/java/ecj.jar
--enable-languages=c,c++,fortran,java,objc --disable-bootstrap
Thread model: posix
gcc version 4.3.1 (GCC) 

Here's the source code that triggered the bug:

C
      SUBROUTINE FFTRC  (A,N,X,IWK,WK)
C                                  SPECIFICATIONS FOR ARGUMENTS
      INTEGER            N,IWK(1)
      REAL*8             A(N),WK(1)
      COMPLEX*16         X(1)
C                                  SPECIFICATIONS FOR LOCAL VARIABLES
      INTEGER            ND2P1,ND2,I,MTWO,M,IMAX,ND4,NP2,K,NMK,J
      REAL*8             RPI,ZERO,ONE,HALF,THETA,TP,G(2),B(2),Z(2),AI,
     1                   AR
      COMPLEX*16         XIMAG,ALPH,BETA,GAM,S1,ZD
      EQUIVALENCE        (GAM,G(1)),(ALPH,B(1)),(Z(1),AR),(Z(2),AI),
     1                   (ZD,Z(1))
      DATA               ZERO/0.0D0/,HALF/0.5D0/,ONE/1.0D0/,IMAX/24/
      DATA               RPI/3.141592653589793D0/
C                                  FIRST EXECUTABLE STATEMENT
      IF (N .NE. 2) GO TO 5
C                                  N EQUAL TO 2
      ZD = DCMPLX(A(1),A(2))
      THETA = AR
      TP = AI
      X(2) = DCMPLX(THETA-TP,ZERO)
      X(1) = DCMPLX(THETA+TP,ZERO)
      GO TO 9005
    5 CONTINUE
C                                  N GREATER THAN 2
      ND2 = N/2
      ND2P1 = ND2+1
C                                  MOVE A TO X
      J = 1
      DO 6 I=1,ND2
         X(I) = DCMPLX(A(J),A(J+1))
         J = J+2
    6 CONTINUE
C                                  COMPUTE THE CENTER COEFFICIENT
      GAM = DCMPLX(ZERO,ZERO)
      DO 10 I=1,ND2
         GAM = GAM + X(I)
   10 CONTINUE
      TP = G(1)-G(2)
      GAM = DCMPLX(TP,ZERO)
C                                  DETERMINE THE SMALLEST M SUCH THAT
C                                  N IS LESS THAN OR EQUAL TO 2**M
      MTWO = 2
      M = 1
      DO 15 I=1,IMAX
         IF (ND2 .LE. MTWO) GO TO 20
         MTWO = MTWO+MTWO
         M = M+1
   15 CONTINUE
   20 IF (ND2 .EQ. MTWO) GO TO 25
C                                  N IS NOT A POWER OF TWO, CALL FFTCC
      CALL FFTCC (X,ND2,IWK,WK)
      GO TO 30
C                                  N IS A POWER OF TWO, CALL FFT2C
   25 CALL FFT2C (X,M,IWK)
   30 ALPH = X(1)
      X(1) = B(1) + B(2)
      ND4 = (ND2+1)/2
      IF (ND4 .LT. 2) GO TO 40
      NP2 = ND2 + 2
      THETA = RPI/ND2
      TP = THETA
      XIMAG = DCMPLX(ZERO,ONE)
C                                  DECOMPOSE THE COMPLEX VECTOR X
C                                  INTO THE COMPONENTS OF THE TRANSFORM
C                                  OF THE INPUT DATA.
      DO 35 K = 2,ND4
         NMK = NP2 - K
         S1 = DCONJG(X(NMK))
         ALPH = X(K) + S1
         BETA = XIMAG*(S1-X(K))
         S1 = DCMPLX(DCOS(THETA),DSIN(THETA))
         X(K) = (ALPH+BETA*S1)*HALF
         X(NMK) = DCONJG(ALPH-BETA*S1)*HALF
         THETA = THETA + TP
   35 CONTINUE
   40 CONTINUE
      X(ND2P1) = GAM
 9005 RETURN
      END


-- 
           Summary: internal compiler error: in mark_operand_necessary, at
                    tree-ssa-dce.c:242
           Product: gcc
           Version: 4.3.1
            Status: UNCONFIRMED
          Severity: critical
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: ronis at ronispc dot chem dot mcgill dot ca
 GCC build triplet: i686-pc-linux-gnu
  GCC host triplet: Linux-pentium4-gnu
GCC target triplet: i686-pc-linux-gnu


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


^ permalink raw reply	[flat|nested] 16+ messages in thread

* [Bug middle-end/37236] internal compiler error: in mark_operand_necessary, at tree-ssa-dce.c:242
  2008-08-25 19:40 [Bug fortran/37236] New: internal compiler error: in mark_operand_necessary, at tree-ssa-dce.c:242 ronis at ronispc dot chem dot mcgill dot ca
@ 2008-08-25 19:58 ` burnus at gcc dot gnu dot org
  2008-08-25 20:05 ` dominiq at lps dot ens dot fr
                   ` (13 subsequent siblings)
  14 siblings, 0 replies; 16+ messages in thread
From: burnus at gcc dot gnu dot org @ 2008-08-25 19:58 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from burnus at gcc dot gnu dot org  2008-08-25 19:57 -------
Using 4.4 I get the following:

aa.f: In function 'fftrc':
aa.f:2: error: expected an SSA_NAME object
aa.f:2: error: in statement
# NMT.31 = VDEF <NMT.31> { NMT.31 }
IMAGPART_EXPR <(*x_29(D))[1]> = 0.0;
aa.f:2: internal compiler error: verify_ssa failed

while with 4.3:

aa.f: In function 'fftrc':
aa.f:2: internal compiler error: Segmentation fault


-- 

burnus at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |burnus at gcc dot gnu dot
                   |                            |org
          Component|fortran                     |middle-end


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


^ permalink raw reply	[flat|nested] 16+ messages in thread

* [Bug middle-end/37236] internal compiler error: in mark_operand_necessary, at tree-ssa-dce.c:242
  2008-08-25 19:40 [Bug fortran/37236] New: internal compiler error: in mark_operand_necessary, at tree-ssa-dce.c:242 ronis at ronispc dot chem dot mcgill dot ca
  2008-08-25 19:58 ` [Bug middle-end/37236] " burnus at gcc dot gnu dot org
@ 2008-08-25 20:05 ` dominiq at lps dot ens dot fr
  2008-08-25 20:39 ` [Bug middle-end/37236] [4.3, 4.4 Regression] ICE: " kargl at gcc dot gnu dot org
                   ` (12 subsequent siblings)
  14 siblings, 0 replies; 16+ messages in thread
From: dominiq at lps dot ens dot fr @ 2008-08-25 20:05 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from dominiq at lps dot ens dot fr  2008-08-25 20:04 -------
Confirmed on i686-apple-darwin9. Works with 4.2.3, latest trunk (revision
139571) gives:

pr37236.f: In function 'fftrc':
pr37236.f:2: error: expected an SSA_NAME object
pr37236.f:2: error: in statement
# NMT.31 = VDEF <NMT.31> { NMT.31 }
IMAGPART_EXPR <(*x_29(D))[1]> = 0.0;
pr37236.f:2: internal compiler error: verify_ssa failed

Work around: replace X(1) by X(*).


-- 


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


^ permalink raw reply	[flat|nested] 16+ messages in thread

* [Bug middle-end/37236] [4.3, 4.4 Regression] ICE: in mark_operand_necessary, at tree-ssa-dce.c:242
  2008-08-25 19:40 [Bug fortran/37236] New: internal compiler error: in mark_operand_necessary, at tree-ssa-dce.c:242 ronis at ronispc dot chem dot mcgill dot ca
  2008-08-25 19:58 ` [Bug middle-end/37236] " burnus at gcc dot gnu dot org
  2008-08-25 20:05 ` dominiq at lps dot ens dot fr
@ 2008-08-25 20:39 ` kargl at gcc dot gnu dot org
  2008-08-25 20:40 ` burnus at gcc dot gnu dot org
                   ` (11 subsequent siblings)
  14 siblings, 0 replies; 16+ messages in thread
From: kargl at gcc dot gnu dot org @ 2008-08-25 20:39 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from kargl at gcc dot gnu dot org  2008-08-25 20:37 -------
(In reply to comment #0)
> I've got some old fortran code that has compiled with dozens of gcc versions. 
> I tried recompiling with 4.3.1 and I get an internal compiler error if I try to
> compile with my usual compiler flags for this project.
> 
> Building with -O1 works.  I've also played around with removing various
> combinations of the -f flags and -malign-double, but this didn't seem to change
> anything.
> 
> /usr/bin/gfortran -O3 -march=pentium4 -ffast-math -funroll-loops
> -fomit-frame-pointer -malign-double -fPIC -c -o fftrc.lo fftrc.f
> fftrc.f:98.8:
> 
>       X(2) = DCMPLX(THETA-TP,ZERO)                                      
>        1
> Warning: Array reference at (1) is out of bounds (2 > 1) in dimension 1

While gcc should never have an ICE, what happens if you actually fix
the code?

> C
>       SUBROUTINE FFTRC  (A,N,X,IWK,WK)
> C                                  SPECIFICATIONS FOR ARGUMENTS
>       INTEGER            N,IWK(1)
>       REAL*8             A(N),WK(1)
>       COMPLEX*16         X(1)

Are these really rank 1 arrays with only a single element?  Try
changing these to IWK(*), WK(*), X(*).


-- 

kargl at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Severity|critical                    |normal


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


^ permalink raw reply	[flat|nested] 16+ messages in thread

* [Bug middle-end/37236] [4.3, 4.4 Regression] ICE: in mark_operand_necessary, at tree-ssa-dce.c:242
  2008-08-25 19:40 [Bug fortran/37236] New: internal compiler error: in mark_operand_necessary, at tree-ssa-dce.c:242 ronis at ronispc dot chem dot mcgill dot ca
                   ` (2 preceding siblings ...)
  2008-08-25 20:39 ` [Bug middle-end/37236] [4.3, 4.4 Regression] ICE: " kargl at gcc dot gnu dot org
@ 2008-08-25 20:40 ` burnus at gcc dot gnu dot org
  2008-08-25 20:41 ` kargl at gcc dot gnu dot org
                   ` (10 subsequent siblings)
  14 siblings, 0 replies; 16+ messages in thread
From: burnus at gcc dot gnu dot org @ 2008-08-25 20:40 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from burnus at gcc dot gnu dot org  2008-08-25 20:39 -------
Note: Using
  COMPLEX*16 X(1)
defines a rank-one array with a single argument. Accessing then
  X(2)
is invalid according to the Fortran standard - there is no such element. (I
know that several old Fortran programs use such a wrong syntax both as actual
as well as as formal argument even though a complete array is meant.)

As Dominique wrote, one can use:
  COMPLEX*16 X(*)
which is the correct syntax.


-- 

burnus at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Severity|normal                      |critical


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


^ permalink raw reply	[flat|nested] 16+ messages in thread

* [Bug middle-end/37236] [4.3, 4.4 Regression] ICE: in mark_operand_necessary, at tree-ssa-dce.c:242
  2008-08-25 19:40 [Bug fortran/37236] New: internal compiler error: in mark_operand_necessary, at tree-ssa-dce.c:242 ronis at ronispc dot chem dot mcgill dot ca
                   ` (3 preceding siblings ...)
  2008-08-25 20:40 ` burnus at gcc dot gnu dot org
@ 2008-08-25 20:41 ` kargl at gcc dot gnu dot org
  2008-08-25 20:50 ` [Bug middle-end/37236] [4.3/4.4 " dominiq at lps dot ens dot fr
                   ` (9 subsequent siblings)
  14 siblings, 0 replies; 16+ messages in thread
From: kargl at gcc dot gnu dot org @ 2008-08-25 20:41 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from kargl at gcc dot gnu dot org  2008-08-25 20:40 -------
(In reply to comment #2)

> Work around: replace X(1) by X(*).

It's not a work around.  It is the *Fix*.
The code as written is invalid.


-- 

kargl at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Severity|critical                    |normal


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


^ permalink raw reply	[flat|nested] 16+ messages in thread

* [Bug middle-end/37236] [4.3/4.4 Regression] ICE: in mark_operand_necessary, at tree-ssa-dce.c:242
  2008-08-25 19:40 [Bug fortran/37236] New: internal compiler error: in mark_operand_necessary, at tree-ssa-dce.c:242 ronis at ronispc dot chem dot mcgill dot ca
                   ` (4 preceding siblings ...)
  2008-08-25 20:41 ` kargl at gcc dot gnu dot org
@ 2008-08-25 20:50 ` dominiq at lps dot ens dot fr
  2008-08-25 21:46 ` ronis at ronispc dot chem dot mcgill dot ca
                   ` (8 subsequent siblings)
  14 siblings, 0 replies; 16+ messages in thread
From: dominiq at lps dot ens dot fr @ 2008-08-25 20:50 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from dominiq at lps dot ens dot fr  2008-08-25 20:49 -------
> It's not a work around.  It is the *Fix*.

It is not my coding style (I always pass the bounds of the arrays, unless they
have known bounds), but I have seen it a zillion time in f77 codes, so I think
it should work in its usual acceptance by gfortran.


-- 


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


^ permalink raw reply	[flat|nested] 16+ messages in thread

* [Bug middle-end/37236] [4.3/4.4 Regression] ICE: in mark_operand_necessary, at tree-ssa-dce.c:242
  2008-08-25 19:40 [Bug fortran/37236] New: internal compiler error: in mark_operand_necessary, at tree-ssa-dce.c:242 ronis at ronispc dot chem dot mcgill dot ca
                   ` (5 preceding siblings ...)
  2008-08-25 20:50 ` [Bug middle-end/37236] [4.3/4.4 " dominiq at lps dot ens dot fr
@ 2008-08-25 21:46 ` ronis at ronispc dot chem dot mcgill dot ca
  2008-08-25 22:33 ` kargl at gcc dot gnu dot org
                   ` (7 subsequent siblings)
  14 siblings, 0 replies; 16+ messages in thread
From: ronis at ronispc dot chem dot mcgill dot ca @ 2008-08-25 21:46 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from ronis at ronispc dot chem dot mcgill dot ca  2008-08-25 21:45 -------
As per the suggestions, I replaced the all instances of array declarations like
X(1) to X(*) and the problem goes away.  Whether it is the current standard or
not, it was legal years ago, and tons of legacy code (like this one) have it. 
Note that this is only one part of a large (ancient) fortran library, which as
far as I can tell, uses syntax like X(1) to declare function/subroutine
arguments all over the place.  The regression was triggered only by this file. 
 Also note, as I mentioned in the initial report, that this code compiled just
fine under earlier versions of gfortran.

Like Dominique in Comment #6, I'd urge you to fix this.   Most of the
programming many scientists and engineers do today is in C or C++, and we rely
on fortran for legacy applications.   Indeed, in my university, fortran is not
taught any more.





-- 


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


^ permalink raw reply	[flat|nested] 16+ messages in thread

* [Bug middle-end/37236] [4.3/4.4 Regression] ICE: in mark_operand_necessary, at tree-ssa-dce.c:242
  2008-08-25 19:40 [Bug fortran/37236] New: internal compiler error: in mark_operand_necessary, at tree-ssa-dce.c:242 ronis at ronispc dot chem dot mcgill dot ca
                   ` (6 preceding siblings ...)
  2008-08-25 21:46 ` ronis at ronispc dot chem dot mcgill dot ca
@ 2008-08-25 22:33 ` kargl at gcc dot gnu dot org
  2008-08-27 11:55 ` rguenth at gcc dot gnu dot org
                   ` (6 subsequent siblings)
  14 siblings, 0 replies; 16+ messages in thread
From: kargl at gcc dot gnu dot org @ 2008-08-25 22:33 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from kargl at gcc dot gnu dot org  2008-08-25 22:32 -------
(In reply to comment #7)
>  Whether it is the current standard or
> not, it was legal years ago, and tons of legacy code (like this one) have it.

It has never been legal.  Yes, legacy codes abuse the dummy argument 
syntax of X(1) to mean X(*), but it has never been legal to access
X(2) if you declared the dummy argument as X(1).

> Like Dominique in Comment #6, I'd urge you to fix this.

If you re-read my original comment, you'll note that I stated that
gcc should never ICE.  This would imply that, yes, gcc should be 
fixed.


-- 


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


^ permalink raw reply	[flat|nested] 16+ messages in thread

* [Bug middle-end/37236] [4.3/4.4 Regression] ICE: in mark_operand_necessary, at tree-ssa-dce.c:242
  2008-08-25 19:40 [Bug fortran/37236] New: internal compiler error: in mark_operand_necessary, at tree-ssa-dce.c:242 ronis at ronispc dot chem dot mcgill dot ca
                   ` (7 preceding siblings ...)
  2008-08-25 22:33 ` kargl at gcc dot gnu dot org
@ 2008-08-27 11:55 ` rguenth at gcc dot gnu dot org
  2008-08-27 22:13 ` jsm28 at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  14 siblings, 0 replies; 16+ messages in thread
From: rguenth at gcc dot gnu dot org @ 2008-08-27 11:55 UTC (permalink / raw)
  To: gcc-bugs



-- 

rguenth at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
           Keywords|                            |ice-on-invalid-code
   Last reconfirmed|0000-00-00 00:00:00         |2008-08-27 11:53:51
               date|                            |
   Target Milestone|---                         |4.3.2


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


^ permalink raw reply	[flat|nested] 16+ messages in thread

* [Bug middle-end/37236] [4.3/4.4 Regression] ICE: in mark_operand_necessary, at tree-ssa-dce.c:242
  2008-08-25 19:40 [Bug fortran/37236] New: internal compiler error: in mark_operand_necessary, at tree-ssa-dce.c:242 ronis at ronispc dot chem dot mcgill dot ca
                   ` (8 preceding siblings ...)
  2008-08-27 11:55 ` rguenth at gcc dot gnu dot org
@ 2008-08-27 22:13 ` jsm28 at gcc dot gnu dot org
  2008-08-29  9:32 ` rguenth at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  14 siblings, 0 replies; 16+ messages in thread
From: jsm28 at gcc dot gnu dot org @ 2008-08-27 22:13 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #9 from jsm28 at gcc dot gnu dot org  2008-08-27 22:05 -------
4.3.2 is released, changing milestones to 4.3.3.


-- 

jsm28 at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Target Milestone|4.3.2                       |4.3.3


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


^ permalink raw reply	[flat|nested] 16+ messages in thread

* [Bug middle-end/37236] [4.3/4.4 Regression] ICE: in mark_operand_necessary, at tree-ssa-dce.c:242
  2008-08-25 19:40 [Bug fortran/37236] New: internal compiler error: in mark_operand_necessary, at tree-ssa-dce.c:242 ronis at ronispc dot chem dot mcgill dot ca
                   ` (9 preceding siblings ...)
  2008-08-27 22:13 ` jsm28 at gcc dot gnu dot org
@ 2008-08-29  9:32 ` rguenth at gcc dot gnu dot org
  2008-08-29 11:43 ` rguenth at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  14 siblings, 0 replies; 16+ messages in thread
From: rguenth at gcc dot gnu dot org @ 2008-08-29  9:32 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #10 from rguenth at gcc dot gnu dot org  2008-08-29 09:30 -------
Mine.


-- 

rguenth at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|unassigned at gcc dot gnu   |rguenth at gcc dot gnu dot
                   |dot org                     |org
             Status|NEW                         |ASSIGNED
   Last reconfirmed|2008-08-27 11:53:51         |2008-08-29 09:30:59
               date|                            |


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


^ permalink raw reply	[flat|nested] 16+ messages in thread

* [Bug middle-end/37236] [4.3/4.4 Regression] ICE: in mark_operand_necessary, at tree-ssa-dce.c:242
  2008-08-25 19:40 [Bug fortran/37236] New: internal compiler error: in mark_operand_necessary, at tree-ssa-dce.c:242 ronis at ronispc dot chem dot mcgill dot ca
                   ` (10 preceding siblings ...)
  2008-08-29  9:32 ` rguenth at gcc dot gnu dot org
@ 2008-08-29 11:43 ` rguenth at gcc dot gnu dot org
  2008-08-29 11:51 ` [Bug middle-end/37236] [4.3 " rguenth at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  14 siblings, 0 replies; 16+ messages in thread
From: rguenth at gcc dot gnu dot org @ 2008-08-29 11:43 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #11 from rguenth at gcc dot gnu dot org  2008-08-29 11:42 -------
Subject: Bug 37236

Author: rguenth
Date: Fri Aug 29 11:40:47 2008
New Revision: 139763

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=139763
Log:
2008-08-29  Richard Guenther  <rguenther@suse.de>

        PR middle-end/37236
        * tree-ssa-structalias.c (intra_create_variable_infos): Mark
        PARAM_NOALIAS tags with is_heapvar.
        * tree-ssa-operands.c (access_can_touch_variable): Offset
        based tests do not apply for heapvars.  Fix offset test.

        * gfortran.fortran-torture/compile/pr37236.f: New testcase.

Added:
    trunk/gcc/testsuite/gfortran.fortran-torture/compile/pr37236.f
Modified:
    trunk/gcc/ChangeLog
    trunk/gcc/testsuite/ChangeLog
    trunk/gcc/tree-ssa-operands.c
    trunk/gcc/tree-ssa-structalias.c


-- 


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


^ permalink raw reply	[flat|nested] 16+ messages in thread

* [Bug middle-end/37236] [4.3 Regression] ICE: in mark_operand_necessary, at tree-ssa-dce.c:242
  2008-08-25 19:40 [Bug fortran/37236] New: internal compiler error: in mark_operand_necessary, at tree-ssa-dce.c:242 ronis at ronispc dot chem dot mcgill dot ca
                   ` (11 preceding siblings ...)
  2008-08-29 11:43 ` rguenth at gcc dot gnu dot org
@ 2008-08-29 11:51 ` rguenth at gcc dot gnu dot org
  2008-09-20 15:42 ` rguenth at gcc dot gnu dot org
  2008-09-20 15:42 ` rguenth at gcc dot gnu dot org
  14 siblings, 0 replies; 16+ messages in thread
From: rguenth at gcc dot gnu dot org @ 2008-08-29 11:51 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #12 from rguenth at gcc dot gnu dot org  2008-08-29 11:49 -------
Fixed for the trunk.


-- 

rguenth at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
      Known to fail|                            |4.3.2
      Known to work|                            |4.4.0
            Summary|[4.3/4.4 Regression] ICE: in|[4.3 Regression] ICE: in
                   |mark_operand_necessary, at  |mark_operand_necessary, at
                   |tree-ssa-dce.c:242          |tree-ssa-dce.c:242


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


^ permalink raw reply	[flat|nested] 16+ messages in thread

* [Bug middle-end/37236] [4.3 Regression] ICE: in mark_operand_necessary, at tree-ssa-dce.c:242
  2008-08-25 19:40 [Bug fortran/37236] New: internal compiler error: in mark_operand_necessary, at tree-ssa-dce.c:242 ronis at ronispc dot chem dot mcgill dot ca
                   ` (12 preceding siblings ...)
  2008-08-29 11:51 ` [Bug middle-end/37236] [4.3 " rguenth at gcc dot gnu dot org
@ 2008-09-20 15:42 ` rguenth at gcc dot gnu dot org
  2008-09-20 15:42 ` rguenth at gcc dot gnu dot org
  14 siblings, 0 replies; 16+ messages in thread
From: rguenth at gcc dot gnu dot org @ 2008-09-20 15:42 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #14 from rguenth at gcc dot gnu dot org  2008-09-20 15:41 -------
Subject: Bug 37236

Author: rguenth
Date: Sat Sep 20 15:40:15 2008
New Revision: 140515

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=140515
Log:
2008-09-20  Richard Guenther  <rguenther@suse.de>

        Backport from mainline:
        2008-08-29  Richard Guenther  <rguenther@suse.de>

        PR middle-end/37236
        * tree-ssa-structalias.c (intra_create_variable_infos): Mark
        PARAM_NOALIAS tags with is_heapvar.
        * tree-ssa-operands.c (access_can_touch_variable): Offset
        based tests do not apply for heapvars.  Fix offset test.

        * gfortran.fortran-torture/compile/pr37236.f: New testcase.

Added:
   
branches/gcc-4_3-branch/gcc/testsuite/gfortran.fortran-torture/compile/pr37236.f
Modified:
    branches/gcc-4_3-branch/gcc/ChangeLog
    branches/gcc-4_3-branch/gcc/testsuite/ChangeLog
    branches/gcc-4_3-branch/gcc/tree-ssa-operands.c
    branches/gcc-4_3-branch/gcc/tree-ssa-structalias.c


-- 


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


^ permalink raw reply	[flat|nested] 16+ messages in thread

* [Bug middle-end/37236] [4.3 Regression] ICE: in mark_operand_necessary, at tree-ssa-dce.c:242
  2008-08-25 19:40 [Bug fortran/37236] New: internal compiler error: in mark_operand_necessary, at tree-ssa-dce.c:242 ronis at ronispc dot chem dot mcgill dot ca
                   ` (13 preceding siblings ...)
  2008-09-20 15:42 ` rguenth at gcc dot gnu dot org
@ 2008-09-20 15:42 ` rguenth at gcc dot gnu dot org
  14 siblings, 0 replies; 16+ messages in thread
From: rguenth at gcc dot gnu dot org @ 2008-09-20 15:42 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #13 from rguenth at gcc dot gnu dot org  2008-09-20 15:41 -------
Fixed.


-- 

rguenth at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|ASSIGNED                    |RESOLVED
         Resolution|                            |FIXED


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


^ permalink raw reply	[flat|nested] 16+ messages in thread

end of thread, other threads:[~2008-09-20 15:42 UTC | newest]

Thread overview: 16+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2008-08-25 19:40 [Bug fortran/37236] New: internal compiler error: in mark_operand_necessary, at tree-ssa-dce.c:242 ronis at ronispc dot chem dot mcgill dot ca
2008-08-25 19:58 ` [Bug middle-end/37236] " burnus at gcc dot gnu dot org
2008-08-25 20:05 ` dominiq at lps dot ens dot fr
2008-08-25 20:39 ` [Bug middle-end/37236] [4.3, 4.4 Regression] ICE: " kargl at gcc dot gnu dot org
2008-08-25 20:40 ` burnus at gcc dot gnu dot org
2008-08-25 20:41 ` kargl at gcc dot gnu dot org
2008-08-25 20:50 ` [Bug middle-end/37236] [4.3/4.4 " dominiq at lps dot ens dot fr
2008-08-25 21:46 ` ronis at ronispc dot chem dot mcgill dot ca
2008-08-25 22:33 ` kargl at gcc dot gnu dot org
2008-08-27 11:55 ` rguenth at gcc dot gnu dot org
2008-08-27 22:13 ` jsm28 at gcc dot gnu dot org
2008-08-29  9:32 ` rguenth at gcc dot gnu dot org
2008-08-29 11:43 ` rguenth at gcc dot gnu dot org
2008-08-29 11:51 ` [Bug middle-end/37236] [4.3 " rguenth at gcc dot gnu dot org
2008-09-20 15:42 ` rguenth at gcc dot gnu dot org
2008-09-20 15:42 ` rguenth at gcc dot gnu dot org

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).