public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/26524]  New: ICE when compiling with -ffast-math and -O3 clatm5.f (lapack)
@ 2006-03-01 22:53 martin dot audet at imi dot cnrc-nrc dot gc dot ca
  2006-03-01 23:14 ` [Bug tree-optimization/26524] " pinskia at gcc dot gnu dot org
                   ` (11 more replies)
  0 siblings, 12 replies; 13+ messages in thread
From: martin dot audet at imi dot cnrc-nrc dot gc dot ca @ 2006-03-01 22:53 UTC (permalink / raw)
  To: gcc-bugs

Hi,

When I try to build LAPACK (http://www.netlib.org/lapack/) I get the following
ICE when I try to compile clatm5.f:

[audet@fn3 MATGEN]$ gfortran -ffast-math -O3 -c clatm5.f
clatm5.f: In function 'clatm5':
clatm5.f:1: internal compiler error: Segmentation fault
Please submit a full bug report,
with preprocessed source if appropriate.
See <URL:http://gcc.gnu.org/bugs.html> for instructions.

Note:

[audet@fn3 MATGEN]$ gfortran -v
Using built-in specs.
Target: x86_64-unknown-linux-gnu
Configured with: ../../gcc-4.1.0/configure --prefix=/usr/local/gcc41
--enable-shared --enable-threads=posix --with-system-zlib --enable-__cxa_atexit
--enable-languages=c,c++,fortran
Thread model: posix
gcc version 4.1.0

[audet@fn3 MATGEN]$ uname -a
Linux fn3 2.6.12-1.1447_FC4smp #1 SMP Fri Aug 26 21:03:12 EDT 2005 x86_64
x86_64 x86_64 GNU/Linux

(Slightly patched Fedora Core 4 distro)

Note also that the clatm5.f file is not part of the liblapack.a library itself.
It comes in the LAPACK package and it is used by example programs to test the
LAPACK library. We can live without it.

Here it is:

      SUBROUTINE CLATM5( PRTYPE, M, N, A, LDA, B, LDB, C, LDC, D, LDD,
     $                   E, LDE, F, LDF, R, LDR, L, LDL, ALPHA, QBLCKA,
     $                   QBLCKB )
*
*  -- LAPACK test routine (version 3.0) --
*     Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
*     Courant Institute, Argonne National Lab, and Rice University
*     June 30, 1999
*
*     .. Scalar Arguments ..
      INTEGER            LDA, LDB, LDC, LDD, LDE, LDF, LDL, LDR, M, N,
     $                   PRTYPE, QBLCKA, QBLCKB
      REAL               ALPHA
*     ..
*     .. Array Arguments ..
      COMPLEX            A( LDA, * ), B( LDB, * ), C( LDC, * ),
     $                   D( LDD, * ), E( LDE, * ), F( LDF, * ),
     $                   L( LDL, * ), R( LDR, * )
*     ..
*
*  Purpose
*  =======
*
*  CLATM5 generates matrices involved in the Generalized Sylvester
*  equation:
*
*      A * R - L * B = C
*      D * R - L * E = F
*
*  They also satisfy (the diagonalization condition)
*
*   [ I -L ] ( [ A  -C ], [ D -F ] ) [ I  R ] = ( [ A    ], [ D    ] )
*   [    I ] ( [     B ]  [    E ] ) [    I ]   ( [    B ]  [    E ] )
*
*
*  Arguments
*  =========
*
*  PRTYPE  (input) INTEGER
*          "Points" to a certian type of the matrices to generate
*          (see futher details).
*
*  M       (input) INTEGER
*          Specifies the order of A and D and the number of rows in
*          C, F,  R and L.
*
*  N       (input) INTEGER
*          Specifies the order of B and E and the number of columns in
*          C, F, R and L.
*
*  A       (output) COMPLEX array, dimension (LDA, M).
*          On exit A M-by-M is initialized according to PRTYPE.
*
*  LDA     (input) INTEGER
*          The leading dimension of A.
*
*  B       (output) COMPLEX array, dimension (LDB, N).
*          On exit B N-by-N is initialized according to PRTYPE.
*
*  LDB     (input) INTEGER
*          The leading dimension of B.
*
*  C       (output) COMPLEX array, dimension (LDC, N).
*          On exit C M-by-N is initialized according to PRTYPE.
*
*  LDC     (input) INTEGER
*          The leading dimension of C.
*
*  D       (output) COMPLEX array, dimension (LDD, M).
*          On exit D M-by-M is initialized according to PRTYPE.
*
*  LDD     (input) INTEGER
*          The leading dimension of D.
*
*  E       (output) COMPLEX array, dimension (LDE, N).
*          On exit E N-by-N is initialized according to PRTYPE.
*
*  LDE     (input) INTEGER
*          The leading dimension of E.
*
*  F       (output) COMPLEX array, dimension (LDF, N).
*          On exit F M-by-N is initialized according to PRTYPE.
*
*  LDF     (input) INTEGER
*          The leading dimension of F.
*
*  R       (output) COMPLEX array, dimension (LDR, N).
*          On exit R M-by-N is initialized according to PRTYPE.
*
*  LDR     (input) INTEGER
*          The leading dimension of R.
*
*  L       (output) COMPLEX array, dimension (LDL, N).
*          On exit L M-by-N is initialized according to PRTYPE.
*
*  LDL     (input) INTEGER
*          The leading dimension of L.
*
*  ALPHA   (input) REAL
*          Parameter used in generating PRTYPE = 1 and 5 matrices.
*
*  QBLCKA  (input) INTEGER
*          When PRTYPE = 3, specifies the distance between 2-by-2
*          blocks on the diagonal in A. Otherwise, QBLCKA is not
*          referenced. QBLCKA > 1.
*
*  QBLCKB  (input) INTEGER
*          When PRTYPE = 3, specifies the distance between 2-by-2
*          blocks on the diagonal in B. Otherwise, QBLCKB is not
*          referenced. QBLCKB > 1.
*
*
*  Further Details
*  ===============
*
*  PRTYPE = 1: A and B are Jordan blocks, D and E are identity matrices
*
*             A : if (i == j) then A(i, j) = 1.0
*                 if (j == i + 1) then A(i, j) = -1.0
*                 else A(i, j) = 0.0,            i, j = 1...M
*
*             B : if (i == j) then B(i, j) = 1.0 - ALPHA
*                 if (j == i + 1) then B(i, j) = 1.0
*                 else B(i, j) = 0.0,            i, j = 1...N
*
*             D : if (i == j) then D(i, j) = 1.0
*                 else D(i, j) = 0.0,            i, j = 1...M
*
*             E : if (i == j) then E(i, j) = 1.0
*                 else E(i, j) = 0.0,            i, j = 1...N
*
*             L =  R are chosen from [-10...10],
*                  which specifies the right hand sides (C, F).
*
*  PRTYPE = 2 or 3: Triangular and/or quasi- triangular.
*
*             A : if (i <= j) then A(i, j) = [-1...1]
*                 else A(i, j) = 0.0,             i, j = 1...M
*
*                 if (PRTYPE = 3) then
*                    A(k + 1, k + 1) = A(k, k)
*                    A(k + 1, k) = [-1...1]
*                    sign(A(k, k + 1) = -(sin(A(k + 1, k))
*                        k = 1, M - 1, QBLCKA
*
*             B : if (i <= j) then B(i, j) = [-1...1]
*                 else B(i, j) = 0.0,            i, j = 1...N
*
*                 if (PRTYPE = 3) then
*                    B(k + 1, k + 1) = B(k, k)
*                    B(k + 1, k) = [-1...1]
*                    sign(B(k, k + 1) = -(sign(B(k + 1, k))
*                        k = 1, N - 1, QBLCKB
*
*             D : if (i <= j) then D(i, j) = [-1...1].
*                 else D(i, j) = 0.0,            i, j = 1...M
*
*
*             E : if (i <= j) then D(i, j) = [-1...1]
*                 else E(i, j) = 0.0,            i, j = 1...N
*
*                 L, R are chosen from [-10...10],
*                 which specifies the right hand sides (C, F).
*
*  PRTYPE = 4 Full
*             A(i, j) = [-10...10]
*             D(i, j) = [-1...1]    i,j = 1...M
*             B(i, j) = [-10...10]
*             E(i, j) = [-1...1]    i,j = 1...N
*             R(i, j) = [-10...10]
*             L(i, j) = [-1...1]    i = 1..M ,j = 1...N
*
*             L, R specifies the right hand sides (C, F).
*
*  PRTYPE = 5 special case common and/or close eigs.
*
*  =====================================================================
*
*     .. Parameters ..
      COMPLEX            ONE, TWO, ZERO, HALF, TWENTY
      PARAMETER          ( ONE = ( 1.0E+0, 0.0E+0 ),
     $                   TWO = ( 2.0E+0, 0.0E+0 ),
     $                   ZERO = ( 0.0E+0, 0.0E+0 ),
     $                   HALF = ( 0.5E+0, 0.0E+0 ),
     $                   TWENTY = ( 2.0E+1, 0.0E+0 ) )
*     ..
*     .. Local Scalars ..
      INTEGER            I, J, K
      COMPLEX            IMEPS, REEPS
*     ..
*     .. Intrinsic Functions ..
      INTRINSIC          CMPLX, MOD, SIN
*     ..
*     .. External Subroutines ..
      EXTERNAL           CGEMM
*     ..
*     .. Executable Statements ..
*
      IF( PRTYPE.EQ.1 ) THEN
         DO 20 I = 1, M
            DO 10 J = 1, M
               IF( I.EQ.J ) THEN
                  A( I, J ) = ONE
                  D( I, J ) = ONE
               ELSE IF( I.EQ.J-1 ) THEN
                  A( I, J ) = -ONE
                  D( I, J ) = ZERO
               ELSE
                  A( I, J ) = ZERO
                  D( I, J ) = ZERO
               END IF
   10       CONTINUE
   20    CONTINUE
*
         DO 40 I = 1, N
            DO 30 J = 1, N
               IF( I.EQ.J ) THEN
                  B( I, J ) = ONE - ALPHA
                  E( I, J ) = ONE
               ELSE IF( I.EQ.J-1 ) THEN
                  B( I, J ) = ONE
                  E( I, J ) = ZERO
               ELSE
                  B( I, J ) = ZERO
                  E( I, J ) = ZERO
               END IF
   30       CONTINUE
   40    CONTINUE
*
         DO 60 I = 1, M
            DO 50 J = 1, N
               R( I, J ) = ( HALF-SIN( CMPLX( I / J ) ) )*TWENTY
               L( I, J ) = R( I, J )
   50       CONTINUE
   60    CONTINUE
*
      ELSE IF( PRTYPE.EQ.2 .OR. PRTYPE.EQ.3 ) THEN
         DO 80 I = 1, M
            DO 70 J = 1, M
               IF( I.LE.J ) THEN
                  A( I, J ) = ( HALF-SIN( CMPLX( I ) ) )*TWO
                  D( I, J ) = ( HALF-SIN( CMPLX( I*J ) ) )*TWO
               ELSE
                  A( I, J ) = ZERO
                  D( I, J ) = ZERO
               END IF
   70       CONTINUE
   80    CONTINUE
*
         DO 100 I = 1, N
            DO 90 J = 1, N
               IF( I.LE.J ) THEN
                  B( I, J ) = ( HALF-SIN( CMPLX( I+J ) ) )*TWO
                  E( I, J ) = ( HALF-SIN( CMPLX( J ) ) )*TWO
               ELSE
                  B( I, J ) = ZERO
                  E( I, J ) = ZERO
               END IF
   90       CONTINUE
  100    CONTINUE
*
         DO 120 I = 1, M
            DO 110 J = 1, N
               R( I, J ) = ( HALF-SIN( CMPLX( I*J ) ) )*TWENTY
               L( I, J ) = ( HALF-SIN( CMPLX( I+J ) ) )*TWENTY
  110       CONTINUE
  120    CONTINUE
*
         IF( PRTYPE.EQ.3 ) THEN
            IF( QBLCKA.LE.1 )
     $         QBLCKA = 2
            DO 130 K = 1, M - 1, QBLCKA
               A( K+1, K+1 ) = A( K, K )
               A( K+1, K ) = -SIN( A( K, K+1 ) )
  130       CONTINUE
*
            IF( QBLCKB.LE.1 )
     $         QBLCKB = 2
            DO 140 K = 1, N - 1, QBLCKB
               B( K+1, K+1 ) = B( K, K )
               B( K+1, K ) = -SIN( B( K, K+1 ) )
  140       CONTINUE
         END IF
*
      ELSE IF( PRTYPE.EQ.4 ) THEN
         DO 160 I = 1, M
            DO 150 J = 1, M
               A( I, J ) = ( HALF-SIN( CMPLX( I*J ) ) )*TWENTY
               D( I, J ) = ( HALF-SIN( CMPLX( I+J ) ) )*TWO
  150       CONTINUE
  160    CONTINUE
*
         DO 180 I = 1, N
            DO 170 J = 1, N
               B( I, J ) = ( HALF-SIN( CMPLX( I+J ) ) )*TWENTY
               E( I, J ) = ( HALF-SIN( CMPLX( I*J ) ) )*TWO
  170       CONTINUE
  180    CONTINUE
*
         DO 200 I = 1, M
            DO 190 J = 1, N
               R( I, J ) = ( HALF-SIN( CMPLX( J / I ) ) )*TWENTY
               L( I, J ) = ( HALF-SIN( CMPLX( I*J ) ) )*TWO
  190       CONTINUE
  200    CONTINUE
*
      ELSE IF( PRTYPE.GE.5 ) THEN
         REEPS = HALF*TWO*TWENTY / ALPHA
         IMEPS = ( HALF-TWO ) / ALPHA
         DO 220 I = 1, M
            DO 210 J = 1, N
               R( I, J ) = ( HALF-SIN( CMPLX( I*J ) ) )*ALPHA / TWENTY
               L( I, J ) = ( HALF-SIN( CMPLX( I+J ) ) )*ALPHA / TWENTY
  210       CONTINUE
  220    CONTINUE
*
         DO 230 I = 1, M
            D( I, I ) = ONE
  230    CONTINUE
*
         DO 240 I = 1, M
            IF( I.LE.4 ) THEN
               A( I, I ) = ONE
               IF( I.GT.2 )
     $            A( I, I ) = ONE + REEPS
               IF( MOD( I, 2 ).NE.0 .AND. I.LT.M ) THEN
                  A( I, I+1 ) = IMEPS
               ELSE IF( I.GT.1 ) THEN
                  A( I, I-1 ) = -IMEPS
               END IF
            ELSE IF( I.LE.8 ) THEN
               IF( I.LE.6 ) THEN
                  A( I, I ) = REEPS
               ELSE
                  A( I, I ) = -REEPS
               END IF
               IF( MOD( I, 2 ).NE.0 .AND. I.LT.M ) THEN
                  A( I, I+1 ) = ONE
               ELSE IF( I.GT.1 ) THEN
                  A( I, I-1 ) = -ONE
               END IF
            ELSE
               A( I, I ) = ONE
               IF( MOD( I, 2 ).NE.0 .AND. I.LT.M ) THEN
                  A( I, I+1 ) = IMEPS*2
               ELSE IF( I.GT.1 ) THEN
                  A( I, I-1 ) = -IMEPS*2
               END IF
            END IF
  240    CONTINUE
*
         DO 250 I = 1, N
            E( I, I ) = ONE
            IF( I.LE.4 ) THEN
               B( I, I ) = -ONE
               IF( I.GT.2 )
     $            B( I, I ) = ONE - REEPS
               IF( MOD( I, 2 ).NE.0 .AND. I.LT.N ) THEN
                  B( I, I+1 ) = IMEPS
               ELSE IF( I.GT.1 ) THEN
                  B( I, I-1 ) = -IMEPS
               END IF
            ELSE IF( I.LE.8 ) THEN
               IF( I.LE.6 ) THEN
                  B( I, I ) = REEPS
               ELSE
                  B( I, I ) = -REEPS
               END IF
               IF( MOD( I, 2 ).NE.0 .AND. I.LT.N ) THEN
                  B( I, I+1 ) = ONE + IMEPS
               ELSE IF( I.GT.1 ) THEN
                  B( I, I-1 ) = -ONE - IMEPS
               END IF
            ELSE
               B( I, I ) = ONE - REEPS
               IF( MOD( I, 2 ).NE.0 .AND. I.LT.N ) THEN
                  B( I, I+1 ) = IMEPS*2
               ELSE IF( I.GT.1 ) THEN
                  B( I, I-1 ) = -IMEPS*2
               END IF
            END IF
  250    CONTINUE
      END IF
*
*     Compute rhs (C, F)
*
      CALL CGEMM( 'N', 'N', M, N, M, ONE, A, LDA, R, LDR, ZERO, C, LDC )
      CALL CGEMM( 'N', 'N', M, N, N, -ONE, L, LDL, B, LDB, ONE, C, LDC )
      CALL CGEMM( 'N', 'N', M, N, M, ONE, D, LDD, R, LDR, ZERO, F, LDF )
      CALL CGEMM( 'N', 'N', M, N, N, -ONE, L, LDL, E, LDE, ONE, F, LDF )
*
*     End of CLATM5
*
      END


-- 
           Summary: ICE when compiling with -ffast-math and -O3 clatm5.f
                    (lapack)
           Product: gcc
           Version: 4.1.0
            Status: UNCONFIRMED
          Severity: major
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: martin dot audet at imi dot cnrc-nrc dot gc dot ca
  GCC host triplet: x86_64-unknown-linux-gnu


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


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

* [Bug tree-optimization/26524] ICE when compiling with -ffast-math and -O3 clatm5.f (lapack)
  2006-03-01 22:53 [Bug fortran/26524] New: ICE when compiling with -ffast-math and -O3 clatm5.f (lapack) martin dot audet at imi dot cnrc-nrc dot gc dot ca
  2006-03-01 23:14 ` [Bug tree-optimization/26524] " pinskia at gcc dot gnu dot org
@ 2006-03-01 23:14 ` pinskia at gcc dot gnu dot org
  2006-03-01 23:15 ` [Bug fortran/26524] " martin dot audet at imi dot cnrc-nrc dot gc dot ca
                   ` (9 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2006-03-01 23:14 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from pinskia at gcc dot gnu dot org  2006-03-01 23:13 -------
The backtrace goes back to the VRP.


-- 

pinskia at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |pinskia at gcc dot gnu dot
                   |                            |org
           Severity|major                       |normal
          Component|fortran                     |tree-optimization
           Keywords|                            |ice-on-valid-code


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


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

* [Bug tree-optimization/26524] ICE when compiling with -ffast-math and -O3 clatm5.f (lapack)
  2006-03-01 22:53 [Bug fortran/26524] New: ICE when compiling with -ffast-math and -O3 clatm5.f (lapack) martin dot audet at imi dot cnrc-nrc dot gc dot ca
@ 2006-03-01 23:14 ` pinskia at gcc dot gnu dot org
  2006-03-01 23:14 ` pinskia at gcc dot gnu dot org
                   ` (10 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2006-03-01 23:14 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from pinskia at gcc dot gnu dot org  2006-03-01 23:14 -------
And it works on the mainline.


-- 

pinskia at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
      Known to fail|                            |4.1.0
      Known to work|                            |4.2.0


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


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

* [Bug fortran/26524] ICE when compiling with -ffast-math and -O3 clatm5.f (lapack)
  2006-03-01 22:53 [Bug fortran/26524] New: ICE when compiling with -ffast-math and -O3 clatm5.f (lapack) martin dot audet at imi dot cnrc-nrc dot gc dot ca
  2006-03-01 23:14 ` [Bug tree-optimization/26524] " pinskia at gcc dot gnu dot org
  2006-03-01 23:14 ` pinskia at gcc dot gnu dot org
@ 2006-03-01 23:15 ` martin dot audet at imi dot cnrc-nrc dot gc dot ca
  2006-03-01 23:17 ` pinskia at gcc dot gnu dot org
                   ` (8 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: martin dot audet at imi dot cnrc-nrc dot gc dot ca @ 2006-03-01 23:15 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from martin dot audet at imi dot cnrc-nrc dot gc dot ca  2006-03-01 23:15 -------

Version 4.0.1 of gfortran (a Fedora Core 4 update) is able to compile clatm5.f
without any problems. 

[audet@fn3 trunk]$ /usr/bin/gfortran -v
Using built-in specs.
Target: x86_64-redhat-linux
Configured with: ../configure --prefix=/usr --mandir=/usr/share/man
--infodir=/usr/share/info --enable-shared --enable-threads=posix
--enable-checking=release --with-system-zlib --enable-__cxa_atexit
--disable-libunwind-exceptions --enable-libgcj-multifile
--enable-languages=c,c++,objc,java,f95,ada --enable-java-awt=gtk
--with-java-home=/usr/lib/jvm/java-1.4.2-gcj-1.4.2.0/jre
--host=x86_64-redhat-linux
Thread model: posix
gcc version 4.0.1 20050727 (Red Hat 4.0.1-5)


-- 

martin dot audet at imi dot cnrc-nrc dot gc dot ca changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Severity|normal                      |major
          Component|tree-optimization           |fortran
      Known to work|4.2.0                       |4.0.1


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


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

* [Bug fortran/26524] ICE when compiling with -ffast-math and -O3 clatm5.f (lapack)
  2006-03-01 22:53 [Bug fortran/26524] New: ICE when compiling with -ffast-math and -O3 clatm5.f (lapack) martin dot audet at imi dot cnrc-nrc dot gc dot ca
                   ` (2 preceding siblings ...)
  2006-03-01 23:15 ` [Bug fortran/26524] " martin dot audet at imi dot cnrc-nrc dot gc dot ca
@ 2006-03-01 23:17 ` pinskia at gcc dot gnu dot org
  2006-03-01 23:24 ` [Bug tree-optimization/26524] [4.1 Regression] " pinskia at gcc dot gnu dot org
                   ` (7 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2006-03-01 23:17 UTC (permalink / raw)
  To: gcc-bugs



-- 

pinskia at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Severity|major                       |normal
      Known to work|4.0.1                       |4.2.0


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


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

* [Bug tree-optimization/26524] [4.1 Regression] ICE when compiling with -ffast-math and -O3 clatm5.f (lapack)
  2006-03-01 22:53 [Bug fortran/26524] New: ICE when compiling with -ffast-math and -O3 clatm5.f (lapack) martin dot audet at imi dot cnrc-nrc dot gc dot ca
                   ` (3 preceding siblings ...)
  2006-03-01 23:17 ` pinskia at gcc dot gnu dot org
@ 2006-03-01 23:24 ` pinskia at gcc dot gnu dot org
  2006-03-02  0:26 ` janis at gcc dot gnu dot org
                   ` (6 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2006-03-01 23:24 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from pinskia at gcc dot gnu dot org  2006-03-01 23:24 -------
Reduced testcase:
      SUBROUTINE CLATM5( PRTYPE, M, N, A, LDA, B, LDB, C, LDC, D, LDD,
     $                   E, LDE, F, LDF, R, LDR, L, LDL, ALPHA, QBLCKA,
     $                   QBLCKB )
      COMPLEX            A( LDA, * ), B( LDB, * ), C( LDC, * ),
     $                   L( LDL, * ), R( LDR, * )
      COMPLEX            IMEPS, REEPS
         DO 240 I = 1, M
               IF( MOD( I, 2 ).NE.0 .AND. I.LT.M ) THEN
                  A( I, I-1 ) = -IMEPS*2
               END IF
  240    CONTINUE
      END

----

The ICE is scev, I have not looked why yet and what fixed it either on the
mainline.


-- 

pinskia at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
      Known to work|4.2.0                       |4.2.0 4.0.3
   Last reconfirmed|0000-00-00 00:00:00         |2006-03-01 23:24:23
               date|                            |
            Summary|ICE when compiling with -   |[4.1 Regression] ICE when
                   |ffast-math and -O3 clatm5.f |compiling with -ffast-math
                   |(lapack)                    |and -O3 clatm5.f (lapack)
   Target Milestone|---                         |4.1.1


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


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

* [Bug tree-optimization/26524] [4.1 Regression] ICE when compiling with -ffast-math and -O3 clatm5.f (lapack)
  2006-03-01 22:53 [Bug fortran/26524] New: ICE when compiling with -ffast-math and -O3 clatm5.f (lapack) martin dot audet at imi dot cnrc-nrc dot gc dot ca
                   ` (4 preceding siblings ...)
  2006-03-01 23:24 ` [Bug tree-optimization/26524] [4.1 Regression] " pinskia at gcc dot gnu dot org
@ 2006-03-02  0:26 ` janis at gcc dot gnu dot org
  2006-03-02 19:10 ` janis at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: janis at gcc dot gnu dot org @ 2006-03-02  0:26 UTC (permalink / raw)
  To: gcc-bugs

[-- Warning: decoded text below may be mangled, UTF-8 assumed --]
[-- Attachment #1: Type: text/plain, Size: 926 bytes --]



------- Comment #5 from janis at gcc dot gnu dot org  2006-03-02 00:26 -------
Andrew wondered aloud on IRC when this was fixed on mainline, so I'm running a
regression hunt for that (between 20051130 and 20051128) and also for when it
broke on mainline (between 20050730 and 20050828).  If all goes well I'll
report the results in the morning.  The hunts are on powerpc-linux using the
minimized testcase from comment #4.

A 4.1 compiler with checking enabled provides more information for that
testcase:

elm3b11% /opt/gcc-nightly/4.1/bin/gfortran -O3 -ffast-math -c 26524.f
26524.f: In function ‘clatm5’:
26524.f:1: internal compiler error: tree check: expected complex_cst, have
integer_cst in const_binop, at fold-const.c:1575
Please submit a full bug report,
with preprocessed source if appropriate.
See <URL:http://gcc.gnu.org/bugs.html> for instructions.


-- 


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


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

* [Bug tree-optimization/26524] [4.1 Regression] ICE when compiling with -ffast-math and -O3 clatm5.f (lapack)
  2006-03-01 22:53 [Bug fortran/26524] New: ICE when compiling with -ffast-math and -O3 clatm5.f (lapack) martin dot audet at imi dot cnrc-nrc dot gc dot ca
                   ` (5 preceding siblings ...)
  2006-03-02  0:26 ` janis at gcc dot gnu dot org
@ 2006-03-02 19:10 ` janis at gcc dot gnu dot org
  2006-03-02 21:25 ` janis at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: janis at gcc dot gnu dot org @ 2006-03-02 19:10 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from janis at gcc dot gnu dot org  2006-03-02 19:10 -------
The test case starts passing on mainline with this patch:

http://gcc.gnu.org/viewcvs?view=rev&rev=109088

r109088 | sayle | 2005-12-27 23:27:34 +0000 (Tue, 27 Dec 2005) | 11 lines

        * fold-const.c (int_const_binop): Return NULL_TREE when an expression
        can't be evaluated at compile-time (instead of calling abort).
        Return NULL_TREE for division (and modulus) by zero.
        (const_binop):  Return NULL_TREE for floating point operators that
        aren't handled by real_arithmetic.
        (fold_binary):  Eliminate "wins" variable, and "binary" label, by
        folding operators with constant operands early.  Assert that
        operands are non-NULL.


-- 

janis at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |sayle at gcc dot gnu dot org


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


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

* [Bug tree-optimization/26524] [4.1 Regression] ICE when compiling with -ffast-math and -O3 clatm5.f (lapack)
  2006-03-01 22:53 [Bug fortran/26524] New: ICE when compiling with -ffast-math and -O3 clatm5.f (lapack) martin dot audet at imi dot cnrc-nrc dot gc dot ca
                   ` (6 preceding siblings ...)
  2006-03-02 19:10 ` janis at gcc dot gnu dot org
@ 2006-03-02 21:25 ` janis at gcc dot gnu dot org
  2006-03-02 21:39 ` roger at eyesopen dot com
                   ` (3 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: janis at gcc dot gnu dot org @ 2006-03-02 21:25 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from janis at gcc dot gnu dot org  2006-03-02 21:25 -------
The test started failing on mainline (before the 4.1 branch) with this patch:

http://gcc.gnu.org/viewcvs?view=rev&rev=103109

r103109 | spop | 2005-08-15 12:26:12 +0000 (Mon, 15 Aug 2005) | 8 lines

        PR 23391
        * Makefile.in (tree-chrec.o): Depends on real.h.
        * tree-chrec.c: Include real.h.
        (chrec_fold_plus_poly_poly, chrec_fold_multiply_poly_poly,
        chrec_fold_plus_1): Use build_real for SCALAR_FLOAT_TYPE_P.
        * tree-scalar-evolution.c (add_to_evolution_1,
        interpret_rhs_modify_expr): Ditto.


-- 


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


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

* [Bug tree-optimization/26524] [4.1 Regression] ICE when compiling with -ffast-math and -O3 clatm5.f (lapack)
  2006-03-01 22:53 [Bug fortran/26524] New: ICE when compiling with -ffast-math and -O3 clatm5.f (lapack) martin dot audet at imi dot cnrc-nrc dot gc dot ca
                   ` (7 preceding siblings ...)
  2006-03-02 21:25 ` janis at gcc dot gnu dot org
@ 2006-03-02 21:39 ` roger at eyesopen dot com
  2006-03-03 14:35 ` sayle at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: roger at eyesopen dot com @ 2006-03-02 21:39 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from roger at eyesopen dot com  2006-03-02 21:39 -------
I think I've found the problem.  On mainline, its in tree-scalar-evolution.c
at around line 1652, where where handle NEGATE_EXPR in
interpret_rhs_modify_expr.
The code checks whether the type is SCALAR_FLOAT_TYPE_P, in which case it uses
build_real, otherwise it calls build_int_cst_type.  Unfortunately, with a
complex
type, we end up generating a (const_int (complex4) -1) which is very broken.
I believe a suitable fix would be to replace this logic with something like
fold_convert (type, integer_minus_one_node), which will produce the correct
result for integers, reals and complex numbers.

My change to fold-const.c just has stricter error checking and refuses to
fold operations of mismatched types, and return NULL_TREE instead.  It wasn't
a fix, it just hid the problem which is still present but latent on mainline.

I think.


-- 


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


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

* [Bug tree-optimization/26524] [4.1 Regression] ICE when compiling with -ffast-math and -O3 clatm5.f (lapack)
  2006-03-01 22:53 [Bug fortran/26524] New: ICE when compiling with -ffast-math and -O3 clatm5.f (lapack) martin dot audet at imi dot cnrc-nrc dot gc dot ca
                   ` (8 preceding siblings ...)
  2006-03-02 21:39 ` roger at eyesopen dot com
@ 2006-03-03 14:35 ` sayle at gcc dot gnu dot org
  2006-03-10  1:26 ` sayle at gcc dot gnu dot org
  2006-03-10 13:00 ` pinskia at gcc dot gnu dot org
  11 siblings, 0 replies; 13+ messages in thread
From: sayle at gcc dot gnu dot org @ 2006-03-03 14:35 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #9 from sayle at gcc dot gnu dot org  2006-03-03 14:35 -------
Subject: Bug 26524

Author: sayle
Date: Fri Mar  3 14:35:23 2006
New Revision: 111676

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=111676
Log:

        PR tree-optimization/26524
        * tree-scalar-evolution.c (interpret_rhs_modify_expr): Use
        fold_convert to create a constant of the appropriate type.

        * gfortran.dg/pr26524.f: New test case.


Added:
    trunk/gcc/testsuite/gfortran.dg/pr26524.f
Modified:
    trunk/gcc/ChangeLog
    trunk/gcc/testsuite/ChangeLog
    trunk/gcc/tree-scalar-evolution.c


-- 


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


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

* [Bug tree-optimization/26524] [4.1 Regression] ICE when compiling with -ffast-math and -O3 clatm5.f (lapack)
  2006-03-01 22:53 [Bug fortran/26524] New: ICE when compiling with -ffast-math and -O3 clatm5.f (lapack) martin dot audet at imi dot cnrc-nrc dot gc dot ca
                   ` (9 preceding siblings ...)
  2006-03-03 14:35 ` sayle at gcc dot gnu dot org
@ 2006-03-10  1:26 ` sayle at gcc dot gnu dot org
  2006-03-10 13:00 ` pinskia at gcc dot gnu dot org
  11 siblings, 0 replies; 13+ messages in thread
From: sayle at gcc dot gnu dot org @ 2006-03-10  1:26 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #10 from sayle at gcc dot gnu dot org  2006-03-10 01:26 -------
Subject: Bug 26524

Author: sayle
Date: Fri Mar 10 01:26:27 2006
New Revision: 111921

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=111921
Log:

        PR tree-optimization/26524
        * tree-scalar-evolution.c (interpret_rhs_modify_expr): Use
        fold_convert to create a constant of the appropriate type.

        * gfortran.dg/pr26524.f: New test case.


Added:
    branches/gcc-4_1-branch/gcc/testsuite/gfortran.dg/pr26524.f
Modified:
    branches/gcc-4_1-branch/gcc/ChangeLog
    branches/gcc-4_1-branch/gcc/testsuite/ChangeLog
    branches/gcc-4_1-branch/gcc/tree-scalar-evolution.c


-- 


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


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

* [Bug tree-optimization/26524] [4.1 Regression] ICE when compiling with -ffast-math and -O3 clatm5.f (lapack)
  2006-03-01 22:53 [Bug fortran/26524] New: ICE when compiling with -ffast-math and -O3 clatm5.f (lapack) martin dot audet at imi dot cnrc-nrc dot gc dot ca
                   ` (10 preceding siblings ...)
  2006-03-10  1:26 ` sayle at gcc dot gnu dot org
@ 2006-03-10 13:00 ` pinskia at gcc dot gnu dot org
  11 siblings, 0 replies; 13+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2006-03-10 13:00 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #11 from pinskia at gcc dot gnu dot org  2006-03-10 13:00 -------
Fixed.


-- 

pinskia at gcc dot gnu dot org changed:

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


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


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

end of thread, other threads:[~2006-03-10 13:00 UTC | newest]

Thread overview: 13+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2006-03-01 22:53 [Bug fortran/26524] New: ICE when compiling with -ffast-math and -O3 clatm5.f (lapack) martin dot audet at imi dot cnrc-nrc dot gc dot ca
2006-03-01 23:14 ` [Bug tree-optimization/26524] " pinskia at gcc dot gnu dot org
2006-03-01 23:14 ` pinskia at gcc dot gnu dot org
2006-03-01 23:15 ` [Bug fortran/26524] " martin dot audet at imi dot cnrc-nrc dot gc dot ca
2006-03-01 23:17 ` pinskia at gcc dot gnu dot org
2006-03-01 23:24 ` [Bug tree-optimization/26524] [4.1 Regression] " pinskia at gcc dot gnu dot org
2006-03-02  0:26 ` janis at gcc dot gnu dot org
2006-03-02 19:10 ` janis at gcc dot gnu dot org
2006-03-02 21:25 ` janis at gcc dot gnu dot org
2006-03-02 21:39 ` roger at eyesopen dot com
2006-03-03 14:35 ` sayle at gcc dot gnu dot org
2006-03-10  1:26 ` sayle at gcc dot gnu dot org
2006-03-10 13:00 ` pinskia 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).