This is the mail archive of the fortran@gcc.gnu.org mailing list for the GNU Fortran project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]
Other format: [Raw text]

Re: Weird optimization bug


Ignacio Fernández Galván wrote:
Hi all,

Before filling a bug report, I'd like to have some comments here, at
least so I can write a better test case and description.

This test case is from lapack. I noticed that I had to compile a
particular subroutine (dlamc1) with -O0, otherwise the programs using
it would hang. So I made this program that just uses dlamc1 (it's
fixed-format, I hope the mailing system preserves spaces):

C=============================================
      PROGRAM Test
        IMPLICIT NONE
        LOGICAL :: LIEEE1, LRND
        INTEGER :: LBETA, LT

CALL DLAMC1( LBETA, LT, LRND, LIEEE1 )

WRITE(6,*) LBETA, LT, LRND, LIEEE1

END PROGRAM Test

      SUBROUTINE DLAMC1( BETA, T, RND, IEEE1 )
      LOGICAL            IEEE1, RND
      INTEGER            BETA, T
      LOGICAL            FIRST, LIEEE1, LRND
      INTEGER            LBETA, LT
      DOUBLE PRECISION   A, B, C, F, ONE, QTR, SAVEC, T1, T2
      DOUBLE PRECISION   DLAMC3
      EXTERNAL           DLAMC3
      SAVE               FIRST, LIEEE1, LBETA, LRND, LT
      DATA               FIRST / .TRUE. /
      INTEGER I
      IF( FIRST ) THEN
         FIRST = .FALSE.
         ONE = 1
         A = 1
         C = 1
   10    CONTINUE
         IF( C.EQ.ONE ) THEN
            A = 2*A
            C = DLAMC3( A, ONE )
            C = DLAMC3( C, -A )
            GO TO 10
         END IF
         B = 1
         C = DLAMC3( A, B )
C         WRITE(6,*) 'Hi'
   20    CONTINUE
         IF( C.EQ.A ) THEN
            B = 2*B
            C = DLAMC3( A, B )
            GO TO 20
         END IF
         QTR = ONE / 4
         SAVEC = C
         C = DLAMC3( C, -A )
         LBETA = C + QTR
         B = LBETA
         F = DLAMC3( B / 2, -B / 100 )
         C = DLAMC3( F, A )
         IF( C.EQ.A ) THEN
            LRND = .TRUE.
         ELSE
            LRND = .FALSE.
         END IF
         F = DLAMC3( B / 2, B / 100 )
         C = DLAMC3( F, A )
         IF( ( LRND ) .AND. ( C.EQ.A ) )
     $      LRND = .FALSE.
         T1 = DLAMC3( B / 2, A )
         T2 = DLAMC3( B / 2, SAVEC )
         LIEEE1 = ( T1.EQ.A ) .AND. ( T2.GT.SAVEC ) .AND. LRND
         LT = 0
         A = 1
         C = 1
   30    CONTINUE
         IF( C.EQ.ONE ) THEN
            LT = LT + 1
            A = A*LBETA
            C = DLAMC3( A, ONE )
            C = DLAMC3( C, -A )
            GO TO 30
         END IF
      END IF
      BETA = LBETA
      T = LT
      RND = LRND
      IEEE1 = LIEEE1
      RETURN
      END

      DOUBLE PRECISION FUNCTION DLAMC3( A, B )
      DOUBLE PRECISION   A, B
      DLAMC3 = A + B
      RETURN
      END
C=============================================

$ gfortran -O0 test.f ; ./a.out
           2          53 T T

This is fine, but then:

$ gfortran -O1 test.f ; ./a.out
[the program runs with 100% cpu for at least one minute, ctrl+C]

Oddly enough, if I now uncomment the WRITE just before line labeled 20:

$ gfortran -O1 test.f ; ./a.out
 Hi
           2          53 F F


Well, gfortran on my system conveniently finds my lapack library that comes with Fedora 7 and the program works fine with -m64. This is on an x86-64 intel box.


I see that in your build you have --build=i386-pc-linux-gnu.

I can reproduce the problem as you described using -m32.

I don't think my lapack is 32 bit compiled so there may be an incompatibility there.

I will experiment some more here, but I think this is a bug. Please file a bug report if you can.

Regards,

Jerry


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]