[Date Prev][Date Next] [Thread Prev][Thread Next] [Date Index] [Thread Index]

Fortran compiler error?



I have a queer problem with the compilation of a 'simple' Fortran
program, which makes me wonder if it could ever be due to a compiler
error?

Machine:             Pentium III

System:              Debian 3.0

Fortran compilers:   fort77 v. 1.15-4,  g77 v. 2.95.4-14

Program:             'nonsense.f' (attached), a destillate of a
                     larger program which has problems

Program description: The program uses the two random number
                     generators ran2 and ran3 from Numerical 
                     Recipes. (In the attached version, ran3 is 
                     used, and ran2 commented out in the main
                     program. The same kind of problem arises
                     if ran2 is used instead)

Compilator calls:    'fort77 nonsense.f' vs. 'g77 nonsense.f',
                     respectively

Execution call:      './a.out', both cases

PROBLEM:             -- With fort77, the program executes OK, and
                     the random numbers produced are OK.

                     -- With g77, the program crashes with any of
                     the generators, evidently because the gener-
                     ator starts spewing out negative numbers!

I would be grateful for an explanation of what is going on, what
type of error is occurring, and what can be done to solve or circum-
vent the problem.


Greetings,

Jan Finjord
UC San Diego, Dept. of Physics
c---------------------------------------------------------------------

      program    nonsense
      implicit   none
      integer    ii,idum,alpha(10)
      real       point,dt,w1,w2,ran2,ran3

      idum=-58211738
c      point= ran2(idum)
      point= ran3(idum)

      do ii=1,1000000
c         point=  ran2(idum)
         point=  ran3(idum)
         if (point.lt.0..or.point.gt.1.) print *,ii,idum
         call sub(alpha,point,dt,w1,w2)
      enddo

      stop
      end

c----------------------------------------------------------------------

      subroutine sub(alpha,point,dt,w1,w2)
      implicit   none
      integer    alpha(10)
      real       point,dt,w1,w2

      if (point.lt.0..or.point.gt.1.)   print *,point
   
      return
      end

c----------------------------------------------------------------------

c     ran2 generator from 'Numerical Recipes'.

      REAL FUNCTION RAN2(IDUM)
      INTEGER IDUM,M,IA,IC,IR,IFF,IY,J
      REAL    RM
      PARAMETER (M=714025,IA=1366,IC=150889,RM=1.4005112E-6)
      DIMENSION IR(97)
      DATA IFF /0/
      IF(IDUM.LT.0.OR.IFF.EQ.0)THEN
        IFF=1
        IDUM=MOD(IC-IDUM,M)
        DO 11 J=1,97
          IDUM=MOD(IA*IDUM+IC,M)
          IR(J)=IDUM
11      CONTINUE
        IDUM=MOD(IA*IDUM+IC,M)
        IY=IDUM
      ENDIF
      J=1+(97*IY)/M
      IF(J.GT.97.OR.J.LT.1)THEN
         WRITE(*,*)J
         PAUSE
         ENDIF
      IY=IR(J)
      RAN2=IY*RM
      IDUM=MOD(IA*IDUM+IC,M)
      IR(J)=IDUM
      RETURN
      END

c----------------------------------------------------------------------

c     ran3 generator from 'Numerical Recipes'.

      REAL FUNCTION RAN3(IDUM)
C         IMPLICIT REAL*4(M)
C         PARAMETER (MBIG=4000000.,MSEED=1618033.,MZ=0.,FAC=2.5E-7)
      INTEGER MBIG,MSEED,MZ,MA,IDUM,IFF,MJ,MK,I,II,K,INEXT,INEXTP
      REAL    FAC
      PARAMETER (MBIG=1000000000,MSEED=161803398,MZ=0,FAC=1.E-9)
      DIMENSION MA(55)
      DATA IFF /0/
      IF(IDUM.LT.0.OR.IFF.EQ.0)THEN
        IFF=1
        MJ=MSEED-IABS(IDUM)
        MJ=MOD(MJ,MBIG)
        MA(55)=MJ
        MK=1
        DO 11 I=1,54
          II=MOD(21*I,55)
          MA(II)=MK
          MK=MJ-MK
          IF(MK.LT.MZ)MK=MK+MBIG
          MJ=MA(II)
11      CONTINUE
        DO 13 K=1,4
          DO 12 I=1,55
            MA(I)=MA(I)-MA(1+MOD(I+30,55))
            IF(MA(I).LT.MZ)MA(I)=MA(I)+MBIG
12        CONTINUE
13      CONTINUE
        INEXT=0
        INEXTP=31
        IDUM=1
      ENDIF
      INEXT=INEXT+1
      IF(INEXT.EQ.56)INEXT=1
      INEXTP=INEXTP+1
      IF(INEXTP.EQ.56)INEXTP=1
      MJ=MA(INEXT)-MA(INEXTP)
      IF(MJ.LT.MZ)MJ=MJ+MBIG
      MA(INEXT)=MJ
      RAN3=MJ*FAC
      RETURN
      END

c----------------------------------------------------------------------

Reply to: