Ignore:
Timestamp:
Aug 6, 2019 9:11:47 AM (5 years ago)
Author:
raasch
Message:

relational operators .EQ., .NE., etc. replaced by ==, /=, etc.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/random_function_mod.f90

    r3802 r4144  
    2525! -----------------
    2626! $Id$
     27! relational operators .EQ., .NE., etc. replaced by ==, /=, etc.
     28!
     29! 3802 2019-03-17 13:33:42Z raasch
    2730! type conversion added to avoid compiler warning about constant integer
    2831! division truncation
     
    7376! ------------
    7477!> Random number generator, produces numbers equally distributed in interval [0,1]
    75 !> This routine is taken from the "numerical recipies"
     78!> This routine is taken from the "numerical recipes"
    7679!------------------------------------------------------------------------------!
    7780 MODULE random_function_mod
     
    137140                   ntab=32, ndiv=1+INT(REAL(im-1)/ntab), eps=1.2e-7_wp, rnmx=1.0_wp-eps )
    138141
    139        IF ( idum .le. 0  .or.  random_iy .eq. 0 )  THEN
     142       IF ( idum <= 0  .OR.  random_iy == 0 )  THEN
    140143          idum = max (-idum,1)
    141144          DO  j = ntab+8,1,-1
    142145             k    = idum / iq
    143146             idum = ia * ( idum - k * iq ) - ir * k
    144              IF ( idum .lt. 0 )  idum = idum + im
    145              IF ( j .le. ntab )  random_iv(j) = idum
     147             IF ( idum < 0 )  idum = idum + im
     148             IF ( j <= ntab )  random_iv(j) = idum
    146149          ENDDO
    147150          random_iy = random_iv(1)
     
    150153       k    = idum / iq
    151154       idum = ia * ( idum - k * iq ) - ir * k
    152        IF ( idum .lt. 0 )  idum = idum + im
     155       IF ( idum < 0 )  idum = idum + im
    153156       j            = 1 + random_iy / ndiv
    154157       random_iy    = random_iv(j)
    155158       random_iv(j) = idum
    156        random_function  = min ( am * random_iy , rnmx )
     159       random_function  = MIN( am * random_iy , rnmx )
    157160
    158161    END FUNCTION random_function
Note: See TracChangeset for help on using the changeset viewer.