[1] | 1 | MODULE random_function_mod |
---|
[3] | 2 | !------------------------------------------------------------------------------! |
---|
[1] | 3 | ! Actual revisions: |
---|
| 4 | ! ----------------- |
---|
| 5 | ! |
---|
| 6 | ! |
---|
| 7 | ! Former revisions: |
---|
| 8 | ! ----------------- |
---|
[3] | 9 | ! $Id: random_function.f90 4 2007-02-13 11:33:16Z raasch $ |
---|
| 10 | ! RCS Log replace by Id keyword, revision history cleaned up |
---|
| 11 | ! |
---|
[1] | 12 | ! Revision 1.3 2003/10/29 09:06:57 raasch |
---|
| 13 | ! Former function changed to a module. |
---|
| 14 | ! |
---|
| 15 | ! Revision 1.1 1998/02/04 16:09:45 raasch |
---|
| 16 | ! Initial revision |
---|
| 17 | ! |
---|
| 18 | ! |
---|
| 19 | ! Description: |
---|
| 20 | ! ------------ |
---|
| 21 | ! Random number generator, produces numbers equally distributed in interval [0,1] |
---|
| 22 | ! This routine is taken from the "numerical recipies" |
---|
[3] | 23 | !------------------------------------------------------------------------------! |
---|
[1] | 24 | |
---|
| 25 | IMPLICIT NONE |
---|
| 26 | |
---|
| 27 | PRIVATE |
---|
| 28 | |
---|
| 29 | PUBLIC random_function, random_function_ini |
---|
| 30 | |
---|
| 31 | INTEGER, PUBLIC, SAVE :: random_iv(32), random_iy |
---|
| 32 | |
---|
| 33 | INTERFACE random_function_ini |
---|
| 34 | MODULE PROCEDURE random_function_ini |
---|
| 35 | END INTERFACE random_function_ini |
---|
| 36 | |
---|
| 37 | INTERFACE random_function |
---|
| 38 | MODULE PROCEDURE random_function |
---|
| 39 | END INTERFACE random_function |
---|
| 40 | |
---|
| 41 | CONTAINS |
---|
| 42 | |
---|
| 43 | SUBROUTINE random_function_ini |
---|
| 44 | |
---|
| 45 | IMPLICIT NONE |
---|
| 46 | |
---|
| 47 | random_iv = 0 |
---|
| 48 | random_iy = 0 |
---|
| 49 | |
---|
| 50 | END SUBROUTINE random_function_ini |
---|
| 51 | |
---|
| 52 | FUNCTION random_function( idum ) |
---|
| 53 | |
---|
| 54 | |
---|
| 55 | IMPLICIT NONE |
---|
| 56 | |
---|
| 57 | INTEGER :: ia, idum, im, iq, ir, ndiv, ntab |
---|
| 58 | REAL :: am, eps, random_function, ranf, rnmx |
---|
| 59 | |
---|
| 60 | PARAMETER ( ia=16807, im=2147483647, am=1.0/im, iq=127773, ir=2836, & |
---|
| 61 | ntab=32, ndiv=1+(im-1)/ntab, eps=1.2e-7, rnmx=1.0-eps ) |
---|
| 62 | |
---|
| 63 | INTEGER :: j, k |
---|
| 64 | |
---|
| 65 | |
---|
| 66 | IF ( idum .le. 0 .or. random_iy .eq. 0 ) THEN |
---|
| 67 | idum = max (-idum,1) |
---|
| 68 | DO j = ntab+8,1,-1 |
---|
| 69 | k = idum / iq |
---|
| 70 | idum = ia * ( idum - k * iq ) - ir * k |
---|
| 71 | IF ( idum .lt. 0 ) idum = idum + im |
---|
| 72 | IF ( j .le. ntab ) random_iv(j) = idum |
---|
| 73 | ENDDO |
---|
| 74 | random_iy = random_iv(1) |
---|
| 75 | ENDIF |
---|
| 76 | |
---|
| 77 | k = idum / iq |
---|
| 78 | idum = ia * ( idum - k * iq ) - ir * k |
---|
| 79 | IF ( idum .lt. 0 ) idum = idum + im |
---|
| 80 | j = 1 + random_iy / ndiv |
---|
| 81 | random_iy = random_iv(j) |
---|
| 82 | random_iv(j) = idum |
---|
| 83 | random_function = min ( am * random_iy , rnmx ) |
---|
| 84 | |
---|
| 85 | END FUNCTION random_function |
---|
| 86 | |
---|
| 87 | END MODULE random_function_mod |
---|