updated top-level README and version_decl for V4.4.2 (#1795)
[WRF.git] / share / module_random.F
blob3d9df9fc3dfde1269cf96c26b0a292e66493c381
1 module module_random
2   ! This module implements an array of pseudo-random number 
3   ! generators (PRNGs).  The internal state of the PRNGs is stored 
4   ! in state1, state2, state3, and state4 arrays.  The rand_grid
5   ! routines will produce grids of random numbers from these 
6   ! generators.  The sequence of random numbers will not vary with
7   ! processor decomposition, operating system, computer, compiler or
8   ! compiler optimizations, and will be the same every time the
9   ! model is run (if the seed is unchanged).  Each gridpoint will 
10   ! produce its own independent sequence of random numbers.
11   
12   ! The srand_grid routine seeds the random number generators, given
13   ! an optional "seed" argument.  Each random number generator in
14   ! the grid is given a different seed, but those seeds are based on
15   ! the seed you provide.  If you do not provide one, the same value
16   ! (0) will be used every time the model is run.  That is chosen
17   ! intentionally to ensure reproducability of results.  
19   ! The rand_grid routines will produce random numbers using the
20   ! arrays of random number generators.  The floating-point
21   ! versions of rand_grid produce numbers between 0, inclusive, and 1, 
22   ! exclusive.  The integer versions produce numbers that span the
23   ! entire range of values representable by the datatype.  The full
24   ! precision of the floating-point values are generated.
26   ! Also, this module is not dependent on dimension ordering.
27   ! Arrays are defined as i,j,k, but the code still works if
28   ! the dimensions have a different ordering
30   ! The implementation of the PRNG is in bobrand.c
32   ! Author: Sam Trahan, October 2011
34   interface rand_grid
35      module procedure rand_grid_i4
36      module procedure rand_grid_r4
37      module procedure rand_grid_i8
38      module procedure rand_grid_r8
39   end interface
41 contains
42   subroutine srand_grid(state1,state2,state3,state4, &
43                            IDS,IDE,JDS,JDE,KDS,KDE, &
44                            IMS,IME,JMS,JME,KMS,KME, &
45                            ITS,ITE,JTS,JTE,KTS,KTE,seed)
47     ! This routine initializes a grid of random number generators,
48     ! using the optional seed argument.  Every random number 
49     ! generator will have its own seed, but the seed you provide
50     ! will be used to modify those seeds.  If you provide the same
51     ! seed, the same sequence of random numbers should be produced,
52     ! regardless of computer, compiler, optimization, or operating
53     ! system.
55     ! If you do not provide a seed, the value 0 will be used,
56     ! ensuring that each simulation will produce identical output.
58     implicit none
59     integer(kind=4), intent(inout) :: state1(ims:ime,jms:jme,kms:kme)
60     integer(kind=4), intent(inout) :: state2(ims:ime,jms:jme,kms:kme)
61     integer(kind=4), intent(inout) :: state3(ims:ime,jms:jme,kms:kme)
62     integer(kind=4), intent(inout) :: state4(ims:ime,jms:jme,kms:kme)
63     integer(kind=4), intent(in), optional :: seed
64     integer(kind=4) :: iseed
65     integer :: i,j,k
66     INTEGER, intent(in) :: IDS,IDE,JDS,JDE,KDS,KDE, &
67                            IMS,IME,JMS,JME,KMS,KME, &
68                            ITS,ITE,JTS,JTE,KTS,KTE
69     integer :: seeds(its:ite),n
71     if(present(seed)) then
72        iseed=seed
73     else
74        iseed=0
75     endif
77     n=ite-its+1
79     ! Seed all random number generators.
80     do k=kts,kte
81        do j=jts,jte
82           do i=its,ite
83              seeds(i)=(kde-kds+1)*((jde-jds+1)*i+j)+k
84              ! We can use the same seed here every time
85              ! because bobraninit will use both the 
86              ! "seeds" array and the "seed" integer to
87              ! create the actual seed for each generator.
88           enddo
89           call bobraninit(state1(its,j,k),state2(its,j,k), &
90                           state3(its,j,k),state4(its,j,k), &
91                           seeds,seed,n)
92        enddo
93     enddo
94   end subroutine srand_grid
96   subroutine rand_grid_r4(state1,state2,state3,state4,randdat, &
97                           IDS,IDE,JDS,JDE,KDS,KDE, &
98                           IMS,IME,JMS,JME,KMS,KME, &
99                           ITS,ITE,JTS,JTE,KTS,KTE)
101     ! This routine fills randdat(ITS:ITE,JTS:JTE,KTS:KTE) with an
102     ! array of random 32-bit floating-point numbers uniformly
103     ! distributed from 0 (inclusive) to 1 (exclusive).
104     !
105     ! Make sure you call srand_grid before calling this routine.
107     implicit none
108     integer(kind=4), intent(inout) :: state1(ims:ime,jms:jme,kms:kme)
109     integer(kind=4), intent(inout) :: state2(ims:ime,jms:jme,kms:kme)
110     integer(kind=4), intent(inout) :: state3(ims:ime,jms:jme,kms:kme)
111     integer(kind=4), intent(inout) :: state4(ims:ime,jms:jme,kms:kme)
112     real(kind=4),    intent(inout) :: randdat(ims:ime,jms:jme,kms:kme)
113     integer :: i,j,k,n
114     INTEGER, intent(in) :: IDS,IDE,JDS,JDE,KDS,KDE, &
115                            IMS,IME,JMS,JME,KMS,KME, &
116                            ITS,ITE,JTS,JTE,KTS,KTE
118     n=ite-its+1
120     do k=kts,kte
121        do j=jts,jte
122           call bobranval_r4(state1(its,j,k),state2(its,j,k), &
123                             state3(its,j,k),state4(its,j,k), &
124                             randdat(its,j,k),n)
125        enddo
126     enddo
128   end subroutine rand_grid_r4
130   subroutine rand_grid_i4(state1,state2,state3,state4,randdat, &
131                           IDS,IDE,JDS,JDE,KDS,KDE, &
132                           IMS,IME,JMS,JME,KMS,KME, &
133                           ITS,ITE,JTS,JTE,KTS,KTE)
135     ! This routine fills randdat(ITS:ITE,JTS:JTE,KTS:KTE) with an
136     ! array of random 32-bit signed integers.  The integers will
137     ! be uniformly distributed across the entire range of
138     ! representation of their datatype: -2**31..2**31-1.
139     !
140     ! Make sure you call srand_grid before calling this routine.
141     !
142     ! If you want integers that fall in a specified range, you 
143     ! can produce them like this:
144     !
145     ! do (for each gridpoint)
146     !    ! random numbers uniformly distributed from 0..9:
147     !    randdat(i,j,k)=mod(abs(randdat(i,j,k),10))
148     ! enddo
150     implicit none
151     integer(kind=4), intent(inout) :: state1(ims:ime,jms:jme,kms:kme)
152     integer(kind=4), intent(inout) :: state2(ims:ime,jms:jme,kms:kme)
153     integer(kind=4), intent(inout) :: state3(ims:ime,jms:jme,kms:kme)
154     integer(kind=4), intent(inout) :: state4(ims:ime,jms:jme,kms:kme)
155     integer(kind=4), intent(inout) :: randdat(ims:ime,jms:jme,kms:kme)
156     integer :: i,j,k,n
157     INTEGER, intent(in) :: IDS,IDE,JDS,JDE,KDS,KDE, &
158                            IMS,IME,JMS,JME,KMS,KME, &
159                            ITS,ITE,JTS,JTE,KTS,KTE
161     n=ite-its+1
163     do k=kts,kte
164        do j=jts,jte
165           call bobranval_i4(state1(its,j,k),state2(its,j,k), &
166                             state3(its,j,k),state4(its,j,k), &
167                             randdat(its,j,k),n)
168        enddo
169     enddo
171   end subroutine rand_grid_i4
173   subroutine rand_grid_r8(state1,state2,state3,state4,randdat, &
174                           IDS,IDE,JDS,JDE,KDS,KDE, &
175                           IMS,IME,JMS,JME,KMS,KME, &
176                           ITS,ITE,JTS,JTE,KTS,KTE)
178     ! This routine fills randdat(ITS:ITE,JTS:JTE,KTS:KTE) with an
179     ! array of random 64-bit floating-point numbers uniformly
180     ! distributed from 0 (inclusive) to 1 (exclusive).
181     !
182     ! Make sure you call srand_grid before calling this routine.
184     implicit none
185     integer(kind=4), intent(inout) :: state1(ims:ime,jms:jme,kms:kme)
186     integer(kind=4), intent(inout) :: state2(ims:ime,jms:jme,kms:kme)
187     integer(kind=4), intent(inout) :: state3(ims:ime,jms:jme,kms:kme)
188     integer(kind=4), intent(inout) :: state4(ims:ime,jms:jme,kms:kme)
189     real(kind=8),    intent(inout) :: randdat(ims:ime,jms:jme,kms:kme)
190     integer :: i,j,k,n
191     INTEGER, intent(in) :: IDS,IDE,JDS,JDE,KDS,KDE, &
192                            IMS,IME,JMS,JME,KMS,KME, &
193                            ITS,ITE,JTS,JTE,KTS,KTE
195     n=ite-its+1
197     do k=kts,kte
198        do j=jts,jte
199           call bobranval_r8(state1(its,j,k),state2(its,j,k), &
200                             state3(its,j,k),state4(its,j,k), &
201                             randdat(its,j,k),n)
202        enddo
203     enddo
205   end subroutine rand_grid_r8
207   subroutine rand_grid_i8(state1,state2,state3,state4,randdat, &
208                           IDS,IDE,JDS,JDE,KDS,KDE, &
209                           IMS,IME,JMS,JME,KMS,KME, &
210                           ITS,ITE,JTS,JTE,KTS,KTE)
212     ! This routine fills randdat(ITS:ITE,JTS:JTE,KTS:KTE) with an
213     ! array of random 64-bit signed integers.  The integers will
214     ! be uniformly distributed across the entire range of
215     ! representation of their datatype: -2**63..2**63-1.
216     !
217     ! Make sure you call srand_grid before calling this routine.
218     !
219     ! If you want integers that fall in a specified range, you 
220     ! can produce them like this:
221     !
222     ! do (for each gridpoint)
223     !    ! random numbers uniformly distributed from 0..9:
224     !    randdat(i,j,k)=mod(abs(randdat(i,j,k),10))
225     ! enddo
227     implicit none
228     integer(kind=4), intent(inout) :: state1(ims:ime,jms:jme,kms:kme)
229     integer(kind=4), intent(inout) :: state2(ims:ime,jms:jme,kms:kme)
230     integer(kind=4), intent(inout) :: state3(ims:ime,jms:jme,kms:kme)
231     integer(kind=4), intent(inout) :: state4(ims:ime,jms:jme,kms:kme)
232     integer(kind=8), intent(inout) :: randdat(ims:ime,jms:jme,kms:kme)
233     integer :: i,j,k,n
234     INTEGER, intent(in) :: IDS,IDE,JDS,JDE,KDS,KDE, &
235                            IMS,IME,JMS,JME,KMS,KME, &
236                            ITS,ITE,JTS,JTE,KTS,KTE
238     n=ite-its+1
240     do k=kts,kte
241        do j=jts,jte
242           call bobranval_i8(state1(its,j,k),state2(its,j,k), &
243                             state3(its,j,k),state4(its,j,k), &
244                             randdat(its,j,k),n)
245        enddo
246     enddo
248   end subroutine rand_grid_i8
250 end module module_random