- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Compiler Used: Intel Fortran 10.1
Operating system: Fedora core 3.0
Problem :
At some places in the code where there are multiple additions and multiplications we get a NAN even though all of its arguments are well defined numbers.
The above problem was noticed with the above operations for both real and complex numbers.
Example:
----------------------------------------------------------------------------------------------------------------------------------------
SUBROUTINE CQCSUM(RESP,DAMP,FREQ,SDVA,AMODS,TEMP,COEF,NMODES,NRSP,NCQC,IDRKEY)
IMPLICIT REAL*8(A-H,O-Z)
DIMENSION RESP(NRSP),SDVA(NMODES,NCQC),AMODS(NRSP,NMODES),
* COEF(NMODES),DAMP(NMODES),FREQ(NMODES),TEMP(NRSP)
DO 50 I=1,NMODES
COEF(I)=0.0D0
50 CONTINUE
DO 100 I=1,NRSP
TEMP(I)=0.0D0
100 CONTINUE
DO 1000 JCQC=1,NCQC
DO 200 I=1,NRSP
RESP(I)=0.0D0
200 CONTINUE
DO 700 IMODE=1,NMODES
DAMPI=DAMP(IMODE)
FREQI=FREQ(IMODE)
DO 300 J=IMODE+1,NMODES
DAMPJ=DAMP(J)
FREQJ=FREQ(J)
IF(FREQI.GT.0.0D0)THEN
R = FREQJ/F REQI
S2 = DAMPI*DAMPJ
R2 = R*R
TEMP1=8.0D0*DSQRT(S2)*(DAMPJ+DAMPI*R)*DSQRT(R2*R)
CON1=(1.0D0-R2)*(1.0D0-R2)+4.0D0*S2*R*(1.0D0+R2)
TEMP2=CON1+4.0D0*(DAMPI*DAMPI+DAMPJ*DAMPJ)*R2
COEF(J)=TEMP1/TEMP2
ENDIF
300 CONTINUE
700 CONTINUE
1000 CONTINUE
RETURN
END
-----------------------------------------------------------------------------------------------------------------------------------
In this subroutine CON1 and TEMP2 are getting NaN.
We are unable to trace the source of the problem. The above code works fine when compiled with a GNU compiler.
Other Observations:
Breaking up the operations into series of smaller operations seems to get around the problem until the same problem surfaces at some other part of the code.
The above problems are not noticed in Windows environment (XP)
Example:
In the same subroutine if I broke up the computation as below then it works.
----------------------------------------------------------------------------------------------------------------------------------------
TEMP1=8.0D0*DSQRT(S2)*(DAMPJ+DAMPI*R)*DSQRT(R2*R)
omr2=(1.0D0-R2)
opr2=(1.0D0+R2)
CON1=(omr2)*(omr2)+4.0D0*S2*R*(opr2)
DIDJ = ((DAMPI*DAMPI)+(DAMPJ*DAMPJ))
&n bsp; TEMP2=CON1+(4.0D0*DIDJ*R2)
COEF(J)=TEMP1/TEMP2
-----------------------------------------------------------------------------------------------------------------------------------------------
It would be helpful if you could help us throw some light as to what could be the source of the problem and a possible procedure to fix it.
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
is this the 32-bit compiler? Which options? Which specific version of ifort 10.1? A full test case?
I would have thought that
R*SQRT
would be more stable than
DSQRT(R2*R).
It is also possible that
(1+R)*(1-R)
may be more stable than
1.0D0-R2.
If it is necessary to perform operations in the order you have specified, rather than permitting standard optimizations, you should try -fp-model precise -assume protect_parens, if you haven't done so.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
http://www.intel.com/support/performancetools/fortran/sb/cs-007783.htm
If numbers are close to becoming NaNs, different math options can change the result either way for a given set of data.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content

- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page