[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
gcc-bugzilla@gcc.gnu.org
Mon Aug 25 19:40:00 GMT 2008
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
More information about the Gcc-bugs
mailing list