public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/27069]  New: -ffast-math crash
@ 2006-04-06 23:27 nuno dot bandeira at ist dot utl dot pt
  2006-04-06 23:47 ` [Bug fortran/27069] " kargl at gcc dot gnu dot org
                   ` (14 more replies)
  0 siblings, 15 replies; 17+ messages in thread
From: nuno dot bandeira at ist dot utl dot pt @ 2006-04-06 23:27 UTC (permalink / raw)
  To: gcc-bugs

gfortran crashes when I use -ffast-math in this subroutine:

C     ==================================================================
      SUBROUTINE GRADEN(RHOE,V,GRAD,VTMP)
C     ==--------------------------------------------------------------==
C     ==   SMOOTHING OF THE DENSITY AND CALCULATION OF |nabla.RHO|    ==
C     ==   ON INPUT : RHOE : DENSITY IN REAL SPACE                    ==
C     ==              V    : UNDEFINED                                ==
C     ==              GRAD : UNDEFINED                                ==
C     ==              VTMP : UNDEFINED                                ==
C     ==   ON OUTPUT: RHOE : DENSITY IN REAL SPACE (SMOOTH)           ==
C     ==              V    : UNDEFINED                                ==
C     ==              GRAD : (GRADIENT OF RHO)^2 IN REAL SPACE        ==
C     ==              VTMP : DENSITY IN G SPACE (SMOOTH)              ==
C     ==--------------------------------------------------------------==
      IMPLICIT NONE
      INCLUDE 'system.h'
      INCLUDE 'cnst.inc'
      INCLUDE 'fft.inc'
      INCLUDE 'cppt.inc'
C     Arguments
      COMPLEX*16 V(MAXFFT),VTMP(NHG)
      REAL*8     RHOE(NNR1),GRAD(NNR1,4)
C     Variables
      REAL*8     GMAX,GCS,SMFAC,EG
      INTEGER    ISUB,IR,IG
C     ==--------------------------------------------------------------==
C     ==  TRANSFORM DENSITY TO G SPACE                                ==
C     ==--------------------------------------------------------------==
      CALL TISET('    GRADEN',ISUB)
C$OMP parallel do private(IR)
      DO IR=1,NNR1
        V(IR) = DCMPLX(RHOE(IR),0.0D0)
      ENDDO
      CALL FWFFT(V)
C     ==--------------------------------------------------------------==
C     ==  SMOOTHING                                                   ==
C     ==--------------------------------------------------------------==
      IF(TSMOOTH) THEN
        GMAX=HG(NHG)



        GCS=SMF*GMAX
C$OMP parallel do private(IG,EG,SMFAC)




        DO IG=1,NHG
          EG=(HG(IG)-GCS)/(SDELTA*GMAX)
          SMFAC=1.0D0/(1.0D0+EXP(EG))
          VTMP(IG)=V(NZH(IG))*SMFAC
        ENDDO
      ELSE
        CALL ZGTHR(NHG,V,VTMP,NZH)
      ENDIF
C     ==--------------------------------------------------------------==
C     ==  FFT OF RHO AND NABLA(X)*RHOE                                ==
C     ==--------------------------------------------------------------==



      CALL ZAZZERO(V,MAXFFT)

C$OMP parallel do private(IG)
      DO IG=1,NHG
        V(NZH(IG))=VTMP(IG)-TPIBA*GK(1,IG)*VTMP(IG)
        V(INDZ(IG))=DCONJG(VTMP(IG)+TPIBA*GK(1,IG)*VTMP(IG))
      ENDDO
      CALL INVFFT(V)
C$OMP parallel do private(IR)




      DO IR=1,NNR1
        RHOE(IR)=DREAL(V(IR))
        GRAD(IR,1)=DIMAG(V(IR))*DIMAG(V(IR))
        GRAD(IR,2)=DIMAG(V(IR))
      ENDDO
C     ==--------------------------------------------------------------==
C     ==  FFT OF NABLA(Y)*RHO AND NABLA(Z)*RHOE                       ==
C     ==--------------------------------------------------------------==



      CALL ZAZZERO(V,MAXFFT)
C$OMP parallel do private(IG)
      DO IG=1,NHG
        V(NZH(IG))=TPIBA*(UIMAG*GK(2,IG)-GK(3,IG))*VTMP(IG)
        V(INDZ(IG))=TPIBA*(-UIMAG*GK(2,IG)+GK(3,IG))*DCONJG(VTMP(IG))
      ENDDO

      CALL INVFFT(V)
C$OMP parallel do private(IR)




      DO IR=1,NNR1
        GRAD(IR,1)=GRAD(IR,1)+DREAL(V(IR)*DCONJG(V(IR)))
        GRAD(IR,3)=DREAL(V(IR))
        GRAD(IR,4)=DIMAG(V(IR))
      ENDDO
      CALL TIHALT('    GRADEN',ISUB)
C     ==--------------------------------------------------------------==
      RETURN
      END
C     ==================================================================


-- 
           Summary: -ffast-math crash
           Product: gcc
           Version: 4.2.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: nuno dot bandeira at ist dot utl dot pt


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


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

* [Bug fortran/27069] -ffast-math crash
  2006-04-06 23:27 [Bug fortran/27069] New: -ffast-math crash nuno dot bandeira at ist dot utl dot pt
@ 2006-04-06 23:47 ` kargl at gcc dot gnu dot org
  2006-04-06 23:56 ` nuno dot bandeira at ist dot utl dot pt
                   ` (13 subsequent siblings)
  14 siblings, 0 replies; 17+ messages in thread
From: kargl at gcc dot gnu dot org @ 2006-04-06 23:47 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from kargl at gcc dot gnu dot org  2006-04-06 23:47 -------
Don't use --fast-math.


-- 


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


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

* [Bug fortran/27069] -ffast-math crash
  2006-04-06 23:27 [Bug fortran/27069] New: -ffast-math crash nuno dot bandeira at ist dot utl dot pt
  2006-04-06 23:47 ` [Bug fortran/27069] " kargl at gcc dot gnu dot org
@ 2006-04-06 23:56 ` nuno dot bandeira at ist dot utl dot pt
  2006-04-07  0:06   ` Jerry DeLisle
  2006-04-07  0:06 ` jvdelisle at verizon dot net
                   ` (12 subsequent siblings)
  14 siblings, 1 reply; 17+ messages in thread
From: nuno dot bandeira at ist dot utl dot pt @ 2006-04-06 23:56 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from nuno dot bandeira at ist dot utl dot pt  2006-04-06 23:56 -------
Subject: Re:  -ffast-math crash

kargl at gcc dot gnu dot org wrote:

> ------- Comment #1 from kargl at gcc dot gnu dot org  2006-04-06 23:47 -------
> Don't use --fast-math.

Is there a valid reason for it or is the implementation of the 
-ffast-math still uncertain ?


-- 


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


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

* [Bug fortran/27069] -ffast-math crash
  2006-04-06 23:27 [Bug fortran/27069] New: -ffast-math crash nuno dot bandeira at ist dot utl dot pt
  2006-04-06 23:47 ` [Bug fortran/27069] " kargl at gcc dot gnu dot org
  2006-04-06 23:56 ` nuno dot bandeira at ist dot utl dot pt
@ 2006-04-07  0:06 ` jvdelisle at verizon dot net
  2006-04-07  0:07 ` kargl at gcc dot gnu dot org
                   ` (11 subsequent siblings)
  14 siblings, 0 replies; 17+ messages in thread
From: jvdelisle at verizon dot net @ 2006-04-07  0:06 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from jvdelisle at verizon dot net  2006-04-07 00:06 -------
Subject: Re:  -ffast-math crash

nuno dot bandeira at ist dot utl dot pt wrote:
> ------- Comment #2 from nuno dot bandeira at ist dot utl dot pt  2006-04-06 23:56 -------
> Subject: Re:  -ffast-math crash
> 
> kargl at gcc dot gnu dot org wrote:
> 
> 
>>------- Comment #1 from kargl at gcc dot gnu dot org  2006-04-06 23:47 -------
>>Don't use --fast-math.
> 
> 
> Is there a valid reason for it or is the implementation of the 
> -ffast-math still uncertain ?
> 
> 
-ffast-math is uncertain, not related to gfortran.


-- 


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


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

* Re: [Bug fortran/27069] -ffast-math crash
  2006-04-06 23:56 ` nuno dot bandeira at ist dot utl dot pt
@ 2006-04-07  0:06   ` Jerry DeLisle
  0 siblings, 0 replies; 17+ messages in thread
From: Jerry DeLisle @ 2006-04-07  0:06 UTC (permalink / raw)
  To: gcc-bugzilla; +Cc: gcc-bugs

nuno dot bandeira at ist dot utl dot pt wrote:
> ------- Comment #2 from nuno dot bandeira at ist dot utl dot pt  2006-04-06 23:56 -------
> Subject: Re:  -ffast-math crash
> 
> kargl at gcc dot gnu dot org wrote:
> 
> 
>>------- Comment #1 from kargl at gcc dot gnu dot org  2006-04-06 23:47 -------
>>Don't use --fast-math.
> 
> 
> Is there a valid reason for it or is the implementation of the 
> -ffast-math still uncertain ?
> 
> 
-ffast-math is uncertain, not related to gfortran.


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

* [Bug fortran/27069] -ffast-math crash
  2006-04-06 23:27 [Bug fortran/27069] New: -ffast-math crash nuno dot bandeira at ist dot utl dot pt
                   ` (2 preceding siblings ...)
  2006-04-07  0:06 ` jvdelisle at verizon dot net
@ 2006-04-07  0:07 ` kargl at gcc dot gnu dot org
  2006-04-07  0:10 ` nuno dot bandeira at ist dot utl dot pt
                   ` (10 subsequent siblings)
  14 siblings, 0 replies; 17+ messages in thread
From: kargl at gcc dot gnu dot org @ 2006-04-07  0:07 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from kargl at gcc dot gnu dot org  2006-04-07 00:07 -------
(In reply to comment #2)
>
> kargl at gcc dot gnu dot org wrote:
>
>> Don't use --fast-math.
> 
> Is there a valid reason for it or is the implementation of the 
> -ffast-math still uncertain ?
>

Does your code work correctly if you omit -ffast-math?
Have you audited your code to ensure all floating points operations
meet the expectations of -ffast-math?

I note that your computing an FFT and doing some complex arithmetic
with numbers from the fft. I won't use -ffast-math in this situation.


-- 


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


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

* [Bug fortran/27069] -ffast-math crash
  2006-04-06 23:27 [Bug fortran/27069] New: -ffast-math crash nuno dot bandeira at ist dot utl dot pt
                   ` (3 preceding siblings ...)
  2006-04-07  0:07 ` kargl at gcc dot gnu dot org
@ 2006-04-07  0:10 ` nuno dot bandeira at ist dot utl dot pt
  2006-04-07  0:18 ` pinskia at gcc dot gnu dot org
                   ` (9 subsequent siblings)
  14 siblings, 0 replies; 17+ messages in thread
From: nuno dot bandeira at ist dot utl dot pt @ 2006-04-07  0:10 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from nuno dot bandeira at ist dot utl dot pt  2006-04-07 00:10 -------
Subject: Re:  -ffast-math crash

jvdelisle at verizon dot net wrote:

> 
> -ffast-math is uncertain, not related to gfortran.

I notice speedups of up to 50% for my binary at the cost of some 
numerical error though... in every way this card works miracles.


-- 


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


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

* [Bug fortran/27069] -ffast-math crash
  2006-04-06 23:27 [Bug fortran/27069] New: -ffast-math crash nuno dot bandeira at ist dot utl dot pt
                   ` (4 preceding siblings ...)
  2006-04-07  0:10 ` nuno dot bandeira at ist dot utl dot pt
@ 2006-04-07  0:18 ` pinskia at gcc dot gnu dot org
  2006-04-07  0:20 ` [Bug middle-end/27069] " pinskia at gcc dot gnu dot org
                   ` (8 subsequent siblings)
  14 siblings, 0 replies; 17+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2006-04-07  0:18 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from pinskia at gcc dot gnu dot org  2006-04-07 00:18 -------
What do you mean by crash?  Aka What is the error you get?

Also this source is no where near compilable by itself because of the includes.

Also what is the exact version of GCC you are using?  (use gcc -v to get that).

-ffast-math can do unwantted stuff with complex if you don't understand what it
does.


-- 


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


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

* [Bug middle-end/27069] -ffast-math crash
  2006-04-06 23:27 [Bug fortran/27069] New: -ffast-math crash nuno dot bandeira at ist dot utl dot pt
                   ` (5 preceding siblings ...)
  2006-04-07  0:18 ` pinskia at gcc dot gnu dot org
@ 2006-04-07  0:20 ` pinskia at gcc dot gnu dot org
  2006-04-07  0:20 ` pinskia at gcc dot gnu dot org
                   ` (7 subsequent siblings)
  14 siblings, 0 replies; 17+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2006-04-07  0:20 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from pinskia at gcc dot gnu dot org  2006-04-07 00:20 -------
What are the full options you are passing to gcc anyways since I see you have
some openmp markers here too.


-- 


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


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

* [Bug middle-end/27069] -ffast-math crash
  2006-04-06 23:27 [Bug fortran/27069] New: -ffast-math crash nuno dot bandeira at ist dot utl dot pt
                   ` (6 preceding siblings ...)
  2006-04-07  0:20 ` [Bug middle-end/27069] " pinskia at gcc dot gnu dot org
@ 2006-04-07  0:20 ` pinskia at gcc dot gnu dot org
  2006-04-07  0:32 ` nuno dot bandeira at ist dot utl dot pt
                   ` (6 subsequent siblings)
  14 siblings, 0 replies; 17+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2006-04-07  0:20 UTC (permalink / raw)
  To: gcc-bugs



-- 

pinskia at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |WAITING


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


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

* [Bug middle-end/27069] -ffast-math crash
  2006-04-06 23:27 [Bug fortran/27069] New: -ffast-math crash nuno dot bandeira at ist dot utl dot pt
                   ` (7 preceding siblings ...)
  2006-04-07  0:20 ` pinskia at gcc dot gnu dot org
@ 2006-04-07  0:32 ` nuno dot bandeira at ist dot utl dot pt
  2006-04-07  0:34 ` pinskia at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  14 siblings, 0 replies; 17+ messages in thread
From: nuno dot bandeira at ist dot utl dot pt @ 2006-04-07  0:32 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from nuno dot bandeira at ist dot utl dot pt  2006-04-07 00:32 -------
Subject: Re:  -ffast-math crash

This is what I get from the compiler:

$ gfortran -I../SOURCE -c -fdefault-real-8 -O3 -fforce-addr 
-march=pentium4 -fcray-pointer -ffast-math ./graden.f -o  ./graden.o
./graden.f: In function 'graden':
./graden.f:2: internal compiler error: in find_lattice_value, at 
tree-complex.c:133
Please submit a full bug report,
with preprocessed source if appropriate.
See <URL:http://gcc.gnu.org/bugs.html> for instructions.

Attached are also the include files for the compilation. Thank you all 
for such a quick reply ! The code is not mine by the way hence my 
ignorance...


C     ==================================================================
C     ==           DYNAMIC ALLOCATION OF PERMANENT ARRAYS             ==
C     ==================================================================
C     == TSHELS = FALSE if all TSHEL(IS) false                        ==
C     ==--------------------------------------------------------------==
      LOGICAL       TSHELS,TSHEL(MAXSP)
      COMMON/CPPSW/ TSHELS,TSHEL
C     ==================================================================
C     == INYH(3,NHG) coordinates +NHI (I=1,2,3) for G-vectors         ==
C     == IGL(NHG)    the index of the shell for each G-vector         ==
C     == NZH(NHG)    index in PSI or RHO array (IG1>=0)               ==
C     == INDZ(NHG)   index in PSI or RHO array (IG1<=0)               ==
C     == ISPTR(NHGL+1) last index IG for the shell                    ==
C     == INDZS(NGW)  index for G-compon. of wavefunction in PSI (I1<0)==
C     == NZH(NGW)    index for G-compon. of wavefunction in PSI (I1>0)==
C     ==--------------------------------------------------------------==
      INTEGER       INYH(3,NHG),IGL(NHG),NZH(NHG),INDZ(NHG),
     &              ISPTR(*),INDZS(NGW),NZHS(NGW)
      POINTER       (IP_INYH,INYH),
     &              (IP_IGL,IGL),
     &              (IP_NZH,NZH),
     &              (IP_INDZ,INDZ),
     &              (IP_ISPTR,ISPTR),
     &              (IP_INDZS,INDZS),
     &              (IP_NZHS,NZHS)
      COMMON/CPPTI/ IP_INYH,IP_IGL,IP_NZH,IP_INDZ,IP_ISPTR,IP_INDZS,
     &              IP_NZHS
C     ==================================================================
C     == HG(1:NHG) Square norm of G-vectors                           ==
C     == GK(1:3,1:NHG) Components of G-vectors                        ==
C     == GL(1:NHGL) Square norm of G-vectors for each shell           ==
C     == VPS(1:NSP,1:NHG) Local pseudopotential per species in G space==
C     == RHOPS: smeared ionic charge density in G space               ==
C     ==        ionic point charges replaced by Gaussian charge       ==
C     ==        distributions (see ener.inc) calculated in PUTPS      ==
C     == TWNL(1:NGW,1:NGH(IS),1:NSP) Non-Local projectors array       ==
C     ==        for each G-components (Kleinman-Bylander form)        ==
C     == USED BY VANDERBILT PSEUDOPOTENTIALS                          ==
C     == QRAD                                                         ==
C     == YLMB(NHGK,LPMAX,NKPNT) Initialized in PUTWNL                 ==
C     ==--------------------------------------------------------------==
      REAL*8        HG(NHG),GK(3,NHG),GL(*),
     &              VPS(NSX,NHG),RHOPS(NSX,NHG),
     &              TWNL,QRAD,TWNLS,YLMB
      POINTER       (IP_HG,HG),
     &              (IP_GK,GK),
     &              (IP_GL,GL),
     &              (IP_VPS,VPS),
     &              (IP_RHOPS,RHOPS),
     &              (IP_TWNL,TWNL),
     &              (IP_QRAD,QRAD),
     &              (IP_TWNLS,TWNLS),
     &              (IP_YLMB,YLMB)
      COMMON/CPPTR/ IP_HG,IP_GK,IP_GL,IP_VPS,IP_RHOPS,
     &              IP_TWNL,IP_TWNLS,IP_QRAD,IP_YLMB
C     ==================================================================
C     == Dimension of HGPOT (for isolated system -- HIP)              ==
C     ==--------------------------------------------------------------==
      INTEGER       NR1H,NR2H,NR3H,NR3PL
      COMMON/ISOSI/ NR1H,NR2H,NR3H,NR3PL
C     ==================================================================
      REAL*8        HGPOT(NR1S+1,NR2S+1,NR3PL),HIPZ(NHG)
      COMPLEX*16    SCG(NHG),SCGX(NHG)
      POINTER       (IP_HGPOT,HGPOT),(IP_HIPZ,HIPZ)
      POINTER       (IP_SCG,SCG),(IP_SCGX,SCGX)
      COMMON/ISOSP/ IP_HGPOT,IP_HIPZ,IP_SCG,IP_SCGX
C     ==================================================================
C     ==================================================================
C     == INCLUDE FILE OF NUMERIC CONSTANTS  (SEE SETCNST.F)           ==
C     ==--------------------------------------------------------------==
C     == UIMAG = DCMPLX(0.D0,1.D0)                                    ==
C     == PI      PI NUMBER                                            ==
C     == FPI     4*PI                                                 ==
C     == RY      RYDBERG IN ELECTRON-VOLT                             ==
C     == FACTEM  1 HARTREE IN KELVIN                                  ==
C     == SCMASS  PROTON MASS (IN ATOMIC UNITS = 1822*ELECTRON MASS)   ==
C     == FBOHR   ANGSTROM TO ATOMIC UNITS (BOHR)                      ==
C     == AU_K    ATOMIC UNITS TO KBAR                                 ==
C     == KB_AU   KBAR TO ATOMIC UNITS                                 ==
C     ==================================================================
      COMPLEX*16 UIMAG
      REAL*8 PI,FPI,RY,FACTEM,SCMASS,FBOHR,AU_KB,KB_AU
      COMMON/CNST/ UIMAG,PI,FPI,RY,FACTEM,SCMASS,FBOHR,
     *             AU_KB,KB_AU
C     ==================================================================
C     ==================================================================
      INTEGER        MG,MS,MZ,NAUX1,NAUX2
      REAL*8         AUX1,AUX2
      COMPLEX*16     XF,YF,ZF
      POINTER        (IP_AUX1,AUX1), (IP_AUX2,AUX2),
     *               (IP_MG,MG), (IP_MS,MS), (IP_MZ,MZ),
     *               (IP_XF,XF), (IP_YF,YF), (IP_ZF,ZF)
      COMMON/CFFT_X/ IP_AUX1,IP_AUX2,
     *               IP_MG,IP_MS,IP_MZ,
     *               IP_XF,IP_YF,IP_ZF
      COMMON/CFFT_Y/ NAUX1,NAUX2
C     ==================================================================
      INTEGER        MAXFFT,NR1M,NR2M,NR3M,KR1M,KR2M,KR3M,NHRM,NGRM,
     *               KR2MIN,KR2MAX,KR3MIN,KR3MAX,
     *               MXY(MAXCPU),MAXRPT
      COMMON/DFFT_X/ MAXFFT,NR1M,NR2M,NR3M,KR1M,KR2M,KR3M,NHRM,NGRM,
     *               KR2MIN,KR2MAX,KR3MIN,KR3MAX,
     *               MXY,MAXRPT
C     ==================================================================
C     ==   GATHER/SCATTER ARRAYS                                      ==
C     ==================================================================
      INTEGER      MSP
      POINTER      (IP_MSP,MSP)
      COMMON/GSAR/ IP_MSP
C     ==================================================================
C     NEW GENERAL PARALLEL FFT CODE
C     ==================================================================
      INTEGER       MSRAYS,MFRAYS,LLR1
      INTEGER       QR1S,QR2S,QR3S,QR1,QR2,QR3
      INTEGER       LR1S,LR2S,LR3S,LR1,LR2,LR3
      INTEGER       QR2MAX,QR2MIN,QR3MAX,QR3MIN
      INTEGER       LSRM,LFRM,LR1M,LMSQ,MAXFFTN
      INTEGER       JGW,JGWS,JHG,JHGS
      COMMON/FFTN1/ MSRAYS,MFRAYS,LLR1,QR1S,QR2S,QR3S,QR1,QR2,QR3,
     *              LR1S,LR2S,LR3S,LR1,LR2,LR3,
     *              QR2MAX,QR2MIN,QR3MAX,QR3MIN,LSRM,LFRM,LMSQ,MAXFFTN,
     *              LR1M,JGW,JGWS,JHG,JHGS
      INTEGER       LRXPL(0:MAXCPU,2)
      INTEGER       SP5(0:MAXCPU),SP8(0:MAXCPU),SP9(0:MAXCPU)
      COMMON/FFTN2/ LRXPL,SP5,SP8,SP9
      INTEGER       MSQS,MSQF
      POINTER       (IP_MSQS,MSQS),(IP_MSQF,MSQF)
      INTEGER       NZFF(*),NZFS(*),INZF(*),INZS(*),INZH(3,*)
      POINTER       (IP_NZFF,NZFF),(IP_NZFS,NZFS)
      POINTER       (IP_INZF,INZF),(IP_INZS,INZS),(IP_INZH,INZH)
      COMMON/FFTN3/ IP_MSQS,IP_MSQF,IP_NZFF,IP_NZFS,IP_INZF,IP_INZS,
     *              IP_INZH
C     ==================================================================
C     POOL
C     ==================================================================
      INTEGER    FFTPOOLSIZE
      PARAMETER (FFTPOOLSIZE=3)
      INTEGER       FFTPOOL
      COMMON/FFTP0/ FFTPOOL
      INTEGER       FPOOLV(28,FFTPOOLSIZE)
      COMMON/FFTP1/ FPOOLV
      INTEGER       LRXPOOL(0:MAXCPU,2,FFTPOOLSIZE)
      INTEGER       SPM(9,0:MAXCPU,FFTPOOLSIZE)
      COMMON/FFTP2/ LRXPOOL,SPM
      INTEGER       LMSQMAX,LNZF,LNZS
      COMMON/FFTP3/ LMSQMAX,LNZF,LNZS
      INTEGER       MSQSPOOL,MSQFPOOL
      POINTER       (IP_MSQSPOOL,MSQSPOOL),(IP_MSQFPOOL,MSQFPOOL)
      COMMON/FFTP4/ IP_MSQSPOOL,IP_MSQFPOOL
      INTEGER       NZFFP(LNZF,*),NZFSP(LNZS,*),
     *              INZFP(LNZF,*),INZSP(LNZS,*),INZHP(3,LNZF,*)
      POINTER       (IP_NZFFP,NZFFP),(IP_NZFSP,NZFSP)
      POINTER       (IP_INZFP,INZFP),(IP_INZSP,INZSP),(IP_INZHP,INZHP)
      COMMON/FFTP5/ IP_NZFFP,IP_NZFSP,IP_INZFP,IP_INZSP,IP_INZHP
C     ==================================================================


-- 


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


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

* [Bug middle-end/27069] -ffast-math crash
  2006-04-06 23:27 [Bug fortran/27069] New: -ffast-math crash nuno dot bandeira at ist dot utl dot pt
                   ` (8 preceding siblings ...)
  2006-04-07  0:32 ` nuno dot bandeira at ist dot utl dot pt
@ 2006-04-07  0:34 ` pinskia at gcc dot gnu dot org
  2006-04-07  0:37 ` pinskia at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  14 siblings, 0 replies; 17+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2006-04-07  0:34 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #9 from pinskia at gcc dot gnu dot org  2006-04-07 00:34 -------
Still need the version number?
gfortran -v will give it to you.


-- 


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


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

* [Bug middle-end/27069] -ffast-math crash
  2006-04-06 23:27 [Bug fortran/27069] New: -ffast-math crash nuno dot bandeira at ist dot utl dot pt
                   ` (9 preceding siblings ...)
  2006-04-07  0:34 ` pinskia at gcc dot gnu dot org
@ 2006-04-07  0:37 ` pinskia at gcc dot gnu dot org
  2006-04-07  0:38 ` nuno dot bandeira at ist dot utl dot pt
                   ` (3 subsequent siblings)
  14 siblings, 0 replies; 17+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2006-04-07  0:37 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #10 from pinskia at gcc dot gnu dot org  2006-04-07 00:37 -------
I bet this is a dup of bug 26717 which was fixed a week or so ago.


-- 


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


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

* [Bug middle-end/27069] -ffast-math crash
  2006-04-06 23:27 [Bug fortran/27069] New: -ffast-math crash nuno dot bandeira at ist dot utl dot pt
                   ` (10 preceding siblings ...)
  2006-04-07  0:37 ` pinskia at gcc dot gnu dot org
@ 2006-04-07  0:38 ` nuno dot bandeira at ist dot utl dot pt
  2006-04-07  0:42 ` nuno dot bandeira at ist dot utl dot pt
                   ` (2 subsequent siblings)
  14 siblings, 0 replies; 17+ messages in thread
From: nuno dot bandeira at ist dot utl dot pt @ 2006-04-07  0:38 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #11 from nuno dot bandeira at ist dot utl dot pt  2006-04-07 00:38 -------
Subject: Re:  -ffast-math crash

kargl at gcc dot gnu dot org wrote:

> Does your code work correctly if you omit -ffast-math?

Yes it does albeit slower. The code also compiles well if I omit the 
-ffast-math in the buggy routines (only 3 of them in 581) and use them 
in all the rest.

> I note that your computing an FFT and doing some complex arithmetic
> with numbers from the fft. I won't use -ffast-math in this situation.

Ok, point taken. A speedup is always welcome though.


-- 


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


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

* [Bug middle-end/27069] -ffast-math crash
  2006-04-06 23:27 [Bug fortran/27069] New: -ffast-math crash nuno dot bandeira at ist dot utl dot pt
                   ` (11 preceding siblings ...)
  2006-04-07  0:38 ` nuno dot bandeira at ist dot utl dot pt
@ 2006-04-07  0:42 ` nuno dot bandeira at ist dot utl dot pt
  2006-04-07  0:53 ` pinskia at gcc dot gnu dot org
  2006-04-07  6:10 ` uros at kss-loka dot si
  14 siblings, 0 replies; 17+ messages in thread
From: nuno dot bandeira at ist dot utl dot pt @ 2006-04-07  0:42 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #12 from nuno dot bandeira at ist dot utl dot pt  2006-04-07 00:42 -------
Subject: Re:  -ffast-math crash

pinskia at gcc dot gnu dot org wrote:

> ------- Comment #9 from pinskia at gcc dot gnu dot org  2006-04-07 00:34 -------
> Still need the version number?
> gfortran -v will give it to you.

The very latest (1st of April, 4.0.2). I submitted the version in my bug 
application may be it didn't get through.


-- 


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


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

* [Bug middle-end/27069] -ffast-math crash
  2006-04-06 23:27 [Bug fortran/27069] New: -ffast-math crash nuno dot bandeira at ist dot utl dot pt
                   ` (12 preceding siblings ...)
  2006-04-07  0:42 ` nuno dot bandeira at ist dot utl dot pt
@ 2006-04-07  0:53 ` pinskia at gcc dot gnu dot org
  2006-04-07  6:10 ` uros at kss-loka dot si
  14 siblings, 0 replies; 17+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2006-04-07  0:53 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #13 from pinskia at gcc dot gnu dot org  2006-04-07 00:53 -------
Still not enough to compile it, we need you to attach (not copy and paste) the
following files:
system.h
cnst.inc
fft.inc
cppt.inc


-- 


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


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

* [Bug middle-end/27069] -ffast-math crash
  2006-04-06 23:27 [Bug fortran/27069] New: -ffast-math crash nuno dot bandeira at ist dot utl dot pt
                   ` (13 preceding siblings ...)
  2006-04-07  0:53 ` pinskia at gcc dot gnu dot org
@ 2006-04-07  6:10 ` uros at kss-loka dot si
  14 siblings, 0 replies; 17+ messages in thread
From: uros at kss-loka dot si @ 2006-04-07  6:10 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #14 from uros at kss-loka dot si  2006-04-07 06:10 -------
This is a duplicate of PR 26869.

*** This bug has been marked as a duplicate of 26869 ***


-- 

uros at kss-loka dot si changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|WAITING                     |RESOLVED
         Resolution|                            |DUPLICATE


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


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

end of thread, other threads:[~2006-04-07  6:10 UTC | newest]

Thread overview: 17+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2006-04-06 23:27 [Bug fortran/27069] New: -ffast-math crash nuno dot bandeira at ist dot utl dot pt
2006-04-06 23:47 ` [Bug fortran/27069] " kargl at gcc dot gnu dot org
2006-04-06 23:56 ` nuno dot bandeira at ist dot utl dot pt
2006-04-07  0:06   ` Jerry DeLisle
2006-04-07  0:06 ` jvdelisle at verizon dot net
2006-04-07  0:07 ` kargl at gcc dot gnu dot org
2006-04-07  0:10 ` nuno dot bandeira at ist dot utl dot pt
2006-04-07  0:18 ` pinskia at gcc dot gnu dot org
2006-04-07  0:20 ` [Bug middle-end/27069] " pinskia at gcc dot gnu dot org
2006-04-07  0:20 ` pinskia at gcc dot gnu dot org
2006-04-07  0:32 ` nuno dot bandeira at ist dot utl dot pt
2006-04-07  0:34 ` pinskia at gcc dot gnu dot org
2006-04-07  0:37 ` pinskia at gcc dot gnu dot org
2006-04-07  0:38 ` nuno dot bandeira at ist dot utl dot pt
2006-04-07  0:42 ` nuno dot bandeira at ist dot utl dot pt
2006-04-07  0:53 ` pinskia at gcc dot gnu dot org
2006-04-07  6:10 ` uros at kss-loka dot si

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).