Ignore:
Timestamp:
Mar 20, 2014 8:40:49 AM (10 years ago)
Author:
raasch
Message:

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

File:
1 edited

Legend:

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

    r1310 r1320  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! ONLY-attribute added to USE-statements,
     23! kind-parameters added to all INTEGER and REAL declaration statements,
     24! kinds are defined in new module kinds,
     25! old module precision_kind is removed,
     26! revision history before 2012 removed,
     27! comment fields (!:) to be used for variable explanations added to
     28! all variable declaration statements
    2329!
    2430! Former revisions:
     
    3440! RCS Log replace by Id keyword, revision history cleaned up
    3541!
    36 ! Revision 1.3  2003/10/29 09:06:57  raasch
    37 ! Former function changed to a module.
    38 !
    3942! Revision 1.1  1998/02/04 16:09:45  raasch
    4043! Initial revision
     
    4750!------------------------------------------------------------------------------!
    4851
     52    USE kinds
     53
    4954    IMPLICIT NONE
    5055
     
    5358    PUBLIC random_function, random_function_ini
    5459
    55     INTEGER, PUBLIC, SAVE ::  random_iv(32), random_iy
     60    INTEGER(iwp), PUBLIC, SAVE ::  random_iv(32)  !:
     61    INTEGER(iwp), PUBLIC, SAVE ::  random_iy      !:
    5662
    5763    INTERFACE random_function_ini
     
    7985       IMPLICIT NONE
    8086
    81        INTEGER ::  ia, idum, im, iq, ir, ndiv, ntab
    82        REAL    ::  am, eps, random_function, rnmx
     87       INTEGER(iwp) ::  ia               !:
     88       INTEGER(iwp) ::  idum             !:
     89       INTEGER(iwp) ::  im               !:
     90       INTEGER(iwp) ::  iq               !:
     91       INTEGER(iwp) ::  ir               !:
     92       INTEGER(iwp) ::  ndiv             !:
     93       INTEGER(iwp) ::  ntab             !:
     94
     95       INTEGER(iwp) ::  j                !:
     96       INTEGER(iwp) ::  k                !:
     97
     98       REAL(wp)     ::  am               !:
     99       REAL(wp)     ::  eps              !:
     100       REAL(wp)     ::  random_function  !:
     101       REAL(wp)     ::  rnmx             !:
    83102
    84103       PARAMETER ( ia=16807, im=2147483647, am=1.0/im, iq=127773, ir=2836, &
    85104                   ntab=32, ndiv=1+(im-1)/ntab, eps=1.2e-7, rnmx=1.0-eps )
    86 
    87        INTEGER ::  j, k
    88 
    89105
    90106       IF ( idum .le. 0  .or.  random_iy .eq. 0 )  THEN
Note: See TracChangeset for help on using the changeset viewer.