forked from gravitationalwave01/eDDA
-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathgasdev.f90
82 lines (58 loc) · 1.89 KB
/
gasdev.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
FUNCTION GASDEV(IDUM)
USE DDPRECISION,ONLY: WP
IMPLICIT NONE
! arguments:
INTEGER :: IDUM
REAL(WP) :: GASDEV
! local variables:
INTEGER :: ISET
REAL(WP) :: FAC,GSET,ONE,RSQ,TWO,V1,V2,ZERO
! external functions
REAL(WP) :: RAN3
SAVE ISET,GSET
DATA ISET/0/
!=======================================================================
! function GASDEV
!
! given:
! IDUM = seed for random number generator
! if IDUM < 0, reinitialize RAN1 with seed IDUM
! if IDUM .ge. 0, continue sequence from RAN1
! returns:
! GASDEV(IDUM) = gaussian random deviate
! with mean <gasdev>= 0
! and variance <gasdev**2>=1
! This subroutine follows closely the structure of the routine gasdev
! described in Numerical Recipes by Press, W.H., Flannery, B.P.,
! Teukolsky, S.A., and Vetterling, W.T. (Cambridge Univ. Press).
! NR version uses RAN1, but it was found that under RH7.1/pgf77
! gasdev does not have <gasdev> = 0 when we use RAN1.
! Therefore have changed to use RAN3
! Modifications by B.T. Draine, Princeton University Observatory,
! 2003.09.10
! 2007.08.06 (BTD) converted to f90
!=======================================================================
ZERO=0._WP
ONE=1._WP
TWO=2._WP
IF(ISET==0)THEN
! when ISET = 0, we do not have an extra deviate on hand
! so generate two new deviates
0100 CONTINUE
! generate random variates V1 and V2 on interval -1,1
V1=TWO*RAN3(IDUM)-ONE
V2=TWO*RAN3(IDUM)-ONE
RSQ=V1**2+V2**2
IF(RSQ>=ONE.OR.RSQ==ZERO)GOTO 0100
FAC=SQRT(-TWO*LOG(RSQ)/RSQ)
GSET=V1*FAC
GASDEV=V2*FAC
ISET=1
ELSE
! when ISET = 1, we have an extra deviate on hand
! so use it, and change ISET back to 0
GASDEV=GSET
ISET=0
ENDIF
RETURN
END