SCALE-RM
scale_random.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
10 #include "scalelib.h"
12  !-----------------------------------------------------------------------------
13  !
14  !++ used modules
15  !
16  use scale_precision
17  use scale_io
18  !-----------------------------------------------------------------------------
19  implicit none
20  private
21  !-----------------------------------------------------------------------------
22  !
23  !++ Public procedure
24  !
25  public :: random_setup
26  public :: random_uniform
27  public :: random_normal
28 
29  interface random_uniform
30  module procedure random_uniform_1d
31  module procedure random_uniform_2d
32  module procedure random_uniform_3d
33  end interface
34 
35  interface random_normal
36  module procedure random_normal_1d
37  module procedure random_normal_2d
38  module procedure random_normal_3d
39  end interface random_normal
40 
41  !-----------------------------------------------------------------------------
42  !
43  !++ Public parameters & variables
44  !
45  !-----------------------------------------------------------------------------
46  !
47  !++ Private procedure
48  !
49  private :: random_reset
50 
51  !-----------------------------------------------------------------------------
52  !
53  !++ Private parameters & variables
54  !
55  logical, private :: RANDOM_FIX = .false.
56 
57  integer, private, allocatable :: RANDOM_seedvar(:)
58 
59  !-----------------------------------------------------------------------------
60 contains
61  !-----------------------------------------------------------------------------
63  subroutine random_setup
64  use scale_prc, only: &
65  prc_abort
66  implicit none
67 
68  namelist / param_random / &
69  random_fix
70 
71  integer :: nseeds, ierr
72  !---------------------------------------------------------------------------
73 
74  log_newline
75  log_info("RANDOM_setup",*) 'Setup'
76 
77  !--- read namelist
78  rewind(io_fid_conf)
79  read(io_fid_conf,nml=param_random,iostat=ierr)
80  if( ierr < 0 ) then !--- missing
81  log_info("RANDOM_setup",*) 'Not found namelist. Default used.'
82  elseif( ierr > 0 ) then !--- fatal error
83  log_error("RANDOM_setup",*) 'Not appropriate names in namelist PARAM_RANDOM. Check!'
84  call prc_abort
85  endif
86  log_nml(param_random)
87 
88  call random_seed
89  call random_seed(size=nseeds)
90 
91  allocate( random_seedvar(nseeds))
92 
93  log_newline
94  log_info("RANDOM_setup",*) 'Array size for random seed:', nseeds
95  if ( random_fix ) then
96  log_info("RANDOM_setup",*) 'random seed is fixed.'
97  endif
98 
99  call random_reset
100 
101  return
102  end subroutine random_setup
103 
104  !-----------------------------------------------------------------------------
106  subroutine random_reset
107  use scale_prc, only: &
108  prc_myrank
109  implicit none
110 
111  integer :: time1(8) ! date and time information
112  real(rp) :: time2 ! CPU time
113  !---------------------------------------------------------------------------
114 
115  if ( random_fix ) then
116  ! birthday of SCALE
117  time1(1) = 2011 ! The year
118  time1(2) = 12 ! The month
119  time1(3) = 5 ! The day of the month
120  time1(4) = 9 ! Time difference with UTC in minutes
121  time1(5) = 10 ! The hour of the day
122  time1(6) = 20 ! The minutes of the hour
123  time1(7) = 41 ! The seconds of the minute
124  time1(8) = 0 ! The milliseconds of the second
125  time2 = 0.0_rp
126  else
127  call date_and_time(values=time1)
128  call cpu_time(time2)
129  endif
130 
131  random_seedvar(:) = prc_myrank &
132  + ( time1(1) - 1970 ) * 32140800 &
133  + time1(2) * 2678400 &
134  + time1(3) * 86400 &
135  + time1(5) * 60 &
136  + time1(6) * 3600 &
137  + time1(7) * 60 &
138  + time1(8) &
139  + int(time2*1.e6_rp)
140 
141  call random_seed(put=random_seedvar)
142 
143  return
144  end subroutine random_reset
145 
146  !-----------------------------------------------------------------------------
148  subroutine random_uniform_1d( var )
149  implicit none
150  real(RP), intent(out) :: var(:)
151  !---------------------------------------------------------------------------
152 
153  call random_number(var)
154 
155  return
156  end subroutine random_uniform_1d
157 
158  !-----------------------------------------------------------------------------
160  subroutine random_uniform_2d( var )
161  implicit none
162  real(RP), intent(out) :: var(:,:)
163  !---------------------------------------------------------------------------
164 
165  call random_number(var)
166 
167  return
168  end subroutine random_uniform_2d
169 
170  !-----------------------------------------------------------------------------
172  subroutine random_uniform_3d( var )
173  implicit none
174  real(RP), intent(out) :: var(:,:,:)
175  !---------------------------------------------------------------------------
176 
177  call random_number(var)
178 
179  return
180  end subroutine random_uniform_3d
181 
182  !-----------------------------------------------------------------------------
184  subroutine random_normal_1d( var )
185  implicit none
186  real(RP), intent(out) :: var(:)
187  integer :: n
188 
189  n = size(var)
190  call get_normal( n, var(:) )
191 
192  return
193  end subroutine random_normal_1d
194 
196  subroutine random_normal_2d( var )
197  implicit none
198  real(RP), intent(out) :: var(:,:)
199  integer :: n
200 
201  n = size(var)
202  call get_normal( n, var(:,:) )
203 
204  return
205  end subroutine random_normal_2d
206 
208  subroutine random_normal_3d( var )
209  implicit none
210  real(RP), intent(out) :: var(:,:,:)
211  integer :: n
212 
213  n = size(var)
214  call get_normal( n, var(:,:,:) )
215 
216  return
217  end subroutine random_normal_3d
218 
219  ! private
220 
221  subroutine get_normal( n, var )
222  use scale_const, only: &
223  pi => const_pi
224  implicit none
225  integer, intent(in) :: n
226  real(RP), intent(out) :: var(n)
227 
228  real(RP) :: rnd(n+1)
229  real(RP) :: fact
230  real(RP) :: theta
231  integer :: i
232  !---------------------------------------------------------------------------
233 
234  call random_number(rnd)
235 
236  !$omp parallel do &
237  !$omp private(fact,theta)
238  do i = 1, n/2
239  fact = sqrt(-2.0_rp * log( 1.0_rp - rnd(i*2-1) ) ) ! 0 <= rnd < 1
240  theta = 2.0_rp * pi * rnd(i*2)
241  var(i*2-1) = fact * cos(theta)
242  var(i*2 ) = fact * sin(theta)
243  end do
244  if ( mod(n,2) == 1 ) then
245  fact = sqrt(-2.0_rp * log( 1.0_rp - rnd(n) ) )
246  theta = 2.0_rp * pi * rnd(n+1)
247  var(n) = fact * cos(theta)
248  end if
249 
250  return
251  end subroutine get_normal
252 
253 end module scale_random
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:342
scale_random::random_uniform_1d
subroutine random_uniform_1d(var)
Get uniform random number ( 1D )
Definition: scale_random.F90:149
scale_precision
module PRECISION
Definition: scale_precision.F90:14
scale_prc::prc_myrank
integer, public prc_myrank
process num in local communicator
Definition: scale_prc.F90:90
scale_random
module RANDOM
Definition: scale_random.F90:11
scale_random::random_setup
subroutine, public random_setup
Setup.
Definition: scale_random.F90:64
scale_prc
module PROCESS
Definition: scale_prc.F90:11
scale_const::const_pi
real(rp), public const_pi
pi
Definition: scale_const.F90:31
scale_precision::rp
integer, parameter, public rp
Definition: scale_precision.F90:41
scale_io
module STDIO
Definition: scale_io.F90:10
scale_const
module CONSTANT
Definition: scale_const.F90:11
scale_io::io_fid_conf
integer, public io_fid_conf
Config file ID.
Definition: scale_io.F90:56