CosmicFish  Reference documentation for version 1.0
Looking into future Cosmology
002_Random_utilities.f90
Go to the documentation of this file.
1 !----------------------------------------------------------------------------------------
2 !
3 ! This file is part of CosmicFish.
4 !
5 ! Copyright (C) 2015-2016 by the CosmicFish authors
6 !
7 ! The CosmicFish code is free software;
8 ! You can use it, redistribute it, and/or modify it under the terms
9 ! of the GNU General Public License as published by the Free Software Foundation;
10 ! either version 3 of the License, or (at your option) any later version.
11 ! The full text of the license can be found in the file LICENSE at
12 ! the top level of the CosmicFish distribution.
13 !
14 !----------------------------------------------------------------------------------------
15 
19 
20 
21 !----------------------------------------------------------------------------------------
26 
28 
30 
31  use precision
32 
33  implicit none
34 
35  integer :: rand_inst = 0
36  integer, parameter :: krand = kind(1.d0)
37  integer :: rand_feedback = 1
38 
39 contains
40 
41  subroutine initrandom(i, i2)
42  implicit none
43  integer, optional, intent(in) :: i
44  integer, optional, intent(in) :: i2
45  integer seed_in,kl,ij
46  character(len=10) :: fred
47  real(krand) :: klr
48 
49  if (present(i)) then
50  seed_in = i
51  else
52  seed_in = -1
53  end if
54  if (seed_in /=-1) then
55  if (present(i2)) then
56  kl=i2
57  if (i2 > 30081) stop 'initRandom:second seed too large'
58  else
59  kl = 9373
60  end if
61  ij = i
62  else
63  call system_clock(count=ij)
64  ij = mod(ij + rand_inst*100, 31328)
65  call date_and_time(time=fred)
66  read (fred,'(e10.3)') klr
67  kl = mod(int(klr*1000), 30081)
68  end if
69 
70  if (rand_feedback > 0 ) write(*,'(" Random seeds:",1I6,",",1I6," rand_inst:",1I4)') ij,kl,rand_inst
71  call rmarin(ij,kl)
72 
73  end subroutine initrandom
74 
75  ! ---------------------------------------------------------------------------------------------
79  real(dl) function random_uniform(a,b)
80 
81  implicit none
82 
83  real(dl), intent(in) :: a
84  real(dl), intent(in) :: b
85 
86 
87  random_uniform = (b-a)*ranmar() + a
88 
89  end function random_uniform
90 
91  ! ---------------------------------------------------------------------------------------------
96  real(dl) function gaussian_1()
97 
98  implicit none
99 
100  real(dl) :: R, V1, V2, FAC
101  integer , save :: iset = 0
102  real(dl), save :: gset
103 
104  if ( iset==0 ) then
105  r = 2._dl
106  do while (r >= 1._dl)
107  v1 = 2.d0*ranmar()-1.d0
108  v2 = 2.d0*ranmar()-1.d0
109  r = v1**2+v2**2
110  end do
111  fac = sqrt(-2.d0*log(r)/r)
112  gset = v1*fac
113  gaussian_1 = v2*fac
114  iset = 1
115  else
116  gaussian_1 = gset
117  iset = 0
118  endif
119 
120  end function gaussian_1
121 
122  ! ---------------------------------------------------------------------------------------------
127  real(dl) function random_gaussian( mu, sigma )
129  implicit none
130 
131  real(dl), intent(in) :: mu
132  real(dl), intent(in) :: sigma
133 
134  random_gaussian = gaussian_1()*sigma + mu
135 
136  end function random_gaussian
137 
138 
139  ! This random number generator originally appeared in ''Toward a Universal
140  ! Random Number Generator'' by George Marsaglia and Arif Zaman.
141  ! Florida State University Report: FSU-SCRI-87-50 (1987)
142  !
143  ! It was later modified by F. James and published in ''A Review of Pseudo-
144  ! random Number Generators''
145  !
146  ! THIS IS THE BEST KNOWN RANDOM NUMBER GENERATOR AVAILABLE.
147  ! (However, a newly discovered technique can yield
148  ! a period of 10^600. But that is still in the development stage.)
149  !
150  ! It passes ALL of the tests for random number generators and has a period
151  ! of 2^144, is completely portable (gives bit identical results on all
152  ! machines with at least 24-bit mantissas in the floating point
153  ! representation).
154  !
155  ! The algorithm is a combination of a Fibonacci sequence (with lags of 97
156  ! and 33, and operation "subtraction plus one, modulo one") and an
157  ! "arithmetic sequence" (using subtraction).
158  !
159  ! On a Vax 11/780, this random number generator can produce a number in
160  ! 13 microseconds.
161  !========================================================================
162  !
163  ! PROGRAM TstRAN
164  ! INTEGER IJ, KL, I
165  ! Thee are the seeds needed to produce the test case results
166  ! IJ = 1802
167  ! KL = 9373
168  !
169  !
170  ! Do the initialization
171  ! call rmarin(ij,kl)
172  !
173  ! Generate 20000 random numbers
174  ! do 10 I = 1, 20000
175  ! x = RANMAR()
176  !10 continue
177  !
178  ! If the random number generator is working properly, the next six random
179  ! numbers should be:
180  ! 6533892.0 14220222.0 7275067.0
181  ! 6172232.0 8354498.0 10633180.0
182  !
183  !
184  !
185  ! write(6,20) (4096.0*4096.0*RANMAR(), I=1,6)
186  !20 format (3f12.1)
187  ! end
188  !
189  subroutine rmarin(IJ,KL)
190  ! This is the initialization routine for the random number generator RANMAR()
191  ! NOTE: The seed variables can have values between: 0 <= IJ <= 31328
192  ! 0 <= KL <= 30081
193  !The random number sequences created by these two seeds are of sufficient
194  ! length to complete an entire calculation with. For example, if sveral
195  ! different groups are working on different parts of the same calculation,
196  ! each group could be assigned its own IJ seed. This would leave each group
197  ! with 30000 choices for the second seed. That is to say, this random
198  ! number generator can create 900 million different subsequences -- with
199  ! each subsequence having a length of approximately 10^30.
200  !
201  ! Use IJ = 1802 & KL = 9373 to test the random number generator. The
202  ! subroutine RANMAR should be used to generate 20000 random numbers.
203  ! Then display the next six random numbers generated multiplied by 4096*4096
204  ! If the random number generator is working properly, the random numbers
205  ! should be:
206  ! 6533892.0 14220222.0 7275067.0
207  ! 6172232.0 8354498.0 10633180.0
208  double precision U(97), C, CD, CM, S, T
209  integer I97, J97,i,j,k,l,m
210  integer ij,kl
211  integer ii,jj
212 
213 
214  ! INTEGER IRM(103)
215 
216  common /raset1/ u, c, cd, cm, i97, j97
217  if( ij < 0 .or. ij > 31328 .or. &
218  kl < 0 .or. kl > 30081 ) then
219  print '(A)', ' The first random number seed must have a value between 0 and 31328'
220  print '(A)',' The second seed must have a value between 0 and 30081'
221  stop
222  endif
223  i = mod(ij/177, 177) + 2
224  j = mod(ij , 177) + 2
225  k = mod(kl/169, 178) + 1
226  l = mod(kl, 169)
227  do ii = 1, 97
228  s = 0.0
229  t = 0.5
230  do jj = 1, 24
231  m = mod(mod(i*j, 179)*k, 179)
232  i = j
233  j = k
234  k = m
235  l = mod(53*l+1, 169)
236  if (mod(l*m, 64) >= 32) then
237  s = s + t
238  endif
239  t = 0.5 * t
240 3 continue
241  end do
242  u(ii) = s
243 2 continue
244  end do
245  c = 362436.0 / 16777216.0
246  cd = 7654321.0 / 16777216.0
247  cm = 16777213.0 /16777216.0
248  i97 = 97
249  j97 = 33
250 
251  end subroutine rmarin
252 
253  ! ---------------------------------------------------------------------------------------------
259  double precision function ranmar()
261  double precision U(97), C, CD, CM
262  integer I97, J97
263  double precision uni
264 
265  common /raset1/ u, c, cd, cm, i97, j97
266  ! INTEGER IVEC
267  uni = u(i97) - u(j97)
268  if( uni < 0.0 ) uni = uni + 1.0
269  u(i97) = uni
270  i97 = i97 - 1
271  if(i97 == 0) i97 = 97
272  j97 = j97 - 1
273  if(j97 == 0) j97 = 97
274  c = c - cd
275  if( c < 0.d0 ) c = c + cm
276  uni = uni - c
277  if( uni < 0.d0 ) uni = uni + 1.0
278  ranmar = uni
279 
280  end function ranmar
281 
282 end module random_utilities
This module contains the subroutine and functions to generate random numbers from different distribut...
real(dl) function random_uniform(a, b)
This function returns a random number generated from the uniform distribution in [a,b(. To improve performances no check is done in order to ensure that the random number generator is initialised.
real(dl) function random_gaussian(mu, sigma)
This function returns a random number generated from the gaussian distribution with mean mu and varia...
double precision function ranmar()
This function returns a random number generated from the uniform distribution in [0,1( This is the random number generator proposed by George Marsaglia in Florida State University Report: FSU-SCRI-87-50 It was slightly modified by F. James to produce an array of pseudorandom numbers.
real(dl) function gaussian_1()
This function returns a random number generated from the gaussian distribution with mean zero and var...