V3FIT
drandn.f
1 C**********************************************************************
2 C
3  SUBROUTINE drandn (N,DX,SEED)
4  USE stel_kinds, ONLY: rprec
5  IMPLICIT NONE
6 C
7 C Purpose:
8 C Fills the vector DX with random numbers between 0 and 1. If the
9 C SEED is given, it should be odd and positive. The generator is a
10 C fairly unsophisticated one, from Pearson's "Numerical methods in
11 C engineering and science" book.
12 C
13 C Parameters:
14 C N = the dimension of the vector (input).
15 C DX = the vector to fill with random numbers (output).
16 C SEED = the seed for the generator (input).
17 C
18 C Noel M. Nachtigal
19 C April 23, 1993
20 C
21 C**********************************************************************
22 C
23  INTRINSIC dble, abs, mod
24 C
25  INTEGER N, SEED
26  REAL(rprec) DX(N)
27 C
28 C Local variables.
29 C
30  INTEGER I, J
31 C
32 C Local variables that are saved from one call to the next.
33 C
34  REAL(rprec) DMAX
35  INTEGER :: IM=0, imax, is
36  SAVE dmax, im, imax, is
37 C DATA IM/0/
38 C
39 C Initialize the generator data.
40 C
41  IF (im.EQ.0) THEN
42  j = 0
43  im = 1
44  DO 10 i = 1, 31
45  j = j + 1
46  IF (im*2.LE.im) GO TO 20
47  im = im * 2
48  10 CONTINUE
49  20 imax = (im-1) * 2 + 1
50  dmax = imax
51  DO 30 i = 1, mod(j,3)
52  j = j - 1
53  im = im / 2
54  30 CONTINUE
55  im = im + 5
56  is = abs(mod(im*30107,imax))
57  END IF
58 C
59 C Check whether we have a new seed.
60 C
61  IF (seed.GT.0) is = (seed / 2) * 2 + 1
62 C
63 C Here goes the rest.
64 C
65  DO 40 i = 1, n
66  dx(i) = dble(is) / dmax
67  is = abs(mod(im*is,imax))
68  40 CONTINUE
69 C
70  RETURN
71  END
72 C
73 C**********************************************************************