Line data Source code
1 : !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2 : !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
3 : !!!!
4 : !!!! MIT License
5 : !!!!
6 : !!!! ParaMonte: plain powerful parallel Monte Carlo library.
7 : !!!!
8 : !!!! Copyright (C) 2012-present, The Computational Data Science Lab
9 : !!!!
10 : !!!! This file is part of the ParaMonte library.
11 : !!!!
12 : !!!! Permission is hereby granted, free of charge, to any person obtaining a
13 : !!!! copy of this software and associated documentation files (the "Software"),
14 : !!!! to deal in the Software without restriction, including without limitation
15 : !!!! the rights to use, copy, modify, merge, publish, distribute, sublicense,
16 : !!!! and/or sell copies of the Software, and to permit persons to whom the
17 : !!!! Software is furnished to do so, subject to the following conditions:
18 : !!!!
19 : !!!! The above copyright notice and this permission notice shall be
20 : !!!! included in all copies or substantial portions of the Software.
21 : !!!!
22 : !!!! THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
23 : !!!! EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
24 : !!!! MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.
25 : !!!! IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM,
26 : !!!! DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR
27 : !!!! OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE
28 : !!!! OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
29 : !!!!
30 : !!!! ACKNOWLEDGMENT
31 : !!!!
32 : !!!! ParaMonte is an honor-ware and its currency is acknowledgment and citations.
33 : !!!! As per the ParaMonte library license agreement terms, if you use any parts of
34 : !!!! this library for any purposes, kindly acknowledge the use of ParaMonte in your
35 : !!!! work (education/research/industry/development/...) by citing the ParaMonte
36 : !!!! library as described on this page:
37 : !!!!
38 : !!!! https://github.com/cdslaborg/paramonte/blob/main/ACKNOWLEDGMENT.md
39 : !!!!
40 : !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
41 : !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
42 :
43 : !> \brief This module contains tests of the module [RandomSeed_mod](@ref randomseed_mod).
44 : !> \author Amir Shahmoradi
45 :
46 : module Test_RandomSeed_mod
47 :
48 : use RandomSeed_mod
49 : use Test_mod, only: Test_type
50 : implicit none
51 :
52 : private
53 : public :: test_RandomSeed
54 :
55 : type(Test_type) :: Test
56 :
57 : #if defined CAF_ENABLED
58 : integer, allocatable, save :: Seed(:)[:]
59 : #else
60 : integer, allocatable, save :: Seed(:)
61 : #endif
62 :
63 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
64 :
65 : contains
66 :
67 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
68 :
69 1 : subroutine test_RandomSeed()
70 :
71 : implicit none
72 :
73 1 : Test = Test_type(moduleName=MODULE_NAME)
74 1 : call Test%run(test_constructRandomSeed, "test_constructRandomSeed")
75 1 : call Test%finalize()
76 :
77 1 : end subroutine test_RandomSeed
78 :
79 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
80 :
81 1 : function test_constructRandomSeed() result(assertion)
82 :
83 : implicit none
84 : logical :: assertion
85 1 : type(RandomSeed_type) :: RandomSeed
86 : integer :: seedSize
87 :
88 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
89 : ! Testing RandomSeed_type with no input arguments to constructor default non-repeatable simulation, image-distinct.
90 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
91 :
92 : ! without any arguments it must give non-repeatable image-distinct random seeds.
93 :
94 1 : RandomSeed = RandomSeed_type(imageID=Test%Image%id)
95 1 : assertion = .not. RandomSeed%Err%occurred
96 1 : if (.not. assertion) return
97 :
98 1 : call random_seed(size=seedSize)
99 1 : assertion = RandomSeed%size == seedSize
100 :
101 : ! LCOV_EXCL_START
102 : if (Test%isDebugMode .and. .not. assertion) then
103 :
104 : write(Test%outputUnit,"(*(g0,:,' '))")
105 : write(Test%outputUnit,"(*(g0,:,' '))") "RandomSeed%isRepeatable :", RandomSeed%isRepeatable
106 : write(Test%outputUnit,"(*(g0,:,' '))") "RandomSeed%isImageDistinct :", RandomSeed%isImageDistinct
107 : write(Test%outputUnit,"(*(g0,:,' '))") "RandomSeed%info :", RandomSeed%info
108 : write(Test%outputUnit,"(*(g0,:,' '))") "RandomSeed%size :", RandomSeed%size
109 : write(Test%outputUnit,"(*(g0,:,' '))")
110 :
111 : if (Test%Image%id==1) then
112 : write(Test%outputUnit,"(*(g0,' '))") "this_image(), GETPID(), Seed:", Test%Image%id, ",", RandomSeed%imageID, ",", RandomSeed%Value
113 : #if defined CAF_ENABLED
114 : else
115 : sync images (Test%Image%id-1)
116 : write(Test%outputUnit,"(*(g0,' '))") "this_image(), GETPID(), Seed:", Test%Image%id, ",", RandomSeed%imageID, ",", RandomSeed%Value
117 : #endif
118 : end if
119 : #if defined CAF_ENABLED
120 : if (Test%Image%id<Test%Image%count) sync images (Test%Image%id+1)
121 : #endif
122 :
123 : end if
124 : ! LCOV_EXCL_STOP
125 :
126 : #if defined CAF_ENABLED
127 : allocate( Seed(seedSize)[*] )
128 : #else
129 1 : allocate( Seed(seedSize) )
130 : #endif
131 :
132 1 : call random_seed(get=Seed)
133 9 : assertion = all(RandomSeed%Value == Seed)
134 :
135 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
136 : ! Testing RandomSeed_type with default isRepeatable, isImageDistinct=.false.
137 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
138 :
139 1 : RandomSeed = RandomSeed_type(imageID=Test%Image%id, isImageDistinct=.false.)
140 1 : assertion = .not. RandomSeed%Err%occurred
141 1 : if (.not. assertion) return
142 :
143 1 : call random_seed(get=Seed)
144 9 : assertion = all(RandomSeed%Value == Seed)
145 :
146 : ! LCOV_EXCL_START
147 : if (Test%isDebugMode .and. .not. assertion) then
148 :
149 : write(Test%outputUnit,"(*(g0,:,' '))")
150 : write(Test%outputUnit,"(*(g0,:,' '))") "RandomSeed%isRepeatable :", RandomSeed%isRepeatable
151 : write(Test%outputUnit,"(*(g0,:,' '))") "RandomSeed%isImageDistinct :", RandomSeed%isImageDistinct
152 : write(Test%outputUnit,"(*(g0,:,' '))") "RandomSeed%info :", RandomSeed%info
153 : write(Test%outputUnit,"(*(g0,:,' '))") "RandomSeed%size :", RandomSeed%size
154 : write(Test%outputUnit,"(*(g0,:,' '))")
155 :
156 : if (Test%Image%id==1) then
157 : write(Test%outputUnit,"(*(g0,' '))") "this_image(), GETPID(), Seed:", Test%Image%id, ",", RandomSeed%imageID, ",", RandomSeed%Value
158 : #if defined CAF_ENABLED
159 : else
160 : sync images (Test%Image%id-1)
161 : write(Test%outputUnit,"(*(g0,' '))") "this_image(), GETPID(), Seed:", Test%Image%id, ",", RandomSeed%imageID, ",", RandomSeed%Value
162 : #endif
163 : end if
164 : #if defined CAF_ENABLED
165 : if (Test%Image%id<Test%Image%count) sync images (Test%Image%id+1)
166 : #endif
167 :
168 : end if
169 : ! LCOV_EXCL_STOP
170 :
171 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
172 : ! Testing RandomSeed_type for equivalence of Seed vector on all images
173 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
174 :
175 1 : assertion = .true.
176 :
177 : #if defined CAF_ENABLED
178 : sync all
179 : if (Test%Image%id==1) then
180 : sync images(*)
181 : else
182 : if ( any(Seed /= Seed(:)[1]) ) assertion = .true.
183 : sync images(1)
184 : end if
185 : #endif
186 :
187 : #if defined CAF_ENABLED
188 : sync all
189 : #endif
190 :
191 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
192 : ! Testing RandomSeed_type with isRepeatable=.true., isImageDistinct=.false.
193 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
194 :
195 1 : RandomSeed = RandomSeed_type(imageID=Test%Image%id, isRepeatable=.true., isImageDistinct=.false.)
196 1 : assertion = .not. RandomSeed%Err%occurred
197 1 : if (.not. assertion) return
198 :
199 1 : call random_seed(get=Seed)
200 9 : assertion = all(RandomSeed%Value == Seed)
201 :
202 : ! LCOV_EXCL_START
203 : if (Test%isDebugMode .and. .not. assertion) then
204 :
205 : write(Test%outputUnit,"(*(g0,:,' '))")
206 : write(Test%outputUnit,"(*(g0,:,' '))") "RandomSeed%isRepeatable :", RandomSeed%isRepeatable
207 : write(Test%outputUnit,"(*(g0,:,' '))") "RandomSeed%isImageDistinct :", RandomSeed%isImageDistinct
208 : write(Test%outputUnit,"(*(g0,:,' '))") "RandomSeed%info :", RandomSeed%info
209 : write(Test%outputUnit,"(*(g0,:,' '))") "RandomSeed%size :", RandomSeed%size
210 : write(Test%outputUnit,"(*(g0,:,' '))")
211 :
212 : if (Test%Image%id==1) then
213 : write(Test%outputUnit,"(*(g0,' '))") "this_image(), GETPID(), Seed:", Test%Image%id, ",", RandomSeed%imageID, ",", RandomSeed%Value
214 : #if defined CAF_ENABLED
215 : else
216 : sync images (Test%Image%id-1)
217 : write(Test%outputUnit,"(*(g0,' '))") "this_image(), GETPID(), Seed:", Test%Image%id, ",", RandomSeed%imageID, ",", RandomSeed%Value
218 : #endif
219 : end if
220 : #if defined CAF_ENABLED
221 : if (Test%Image%id<Test%Image%count) sync images (Test%Image%id+1)
222 : #endif
223 :
224 : end if
225 : ! LCOV_EXCL_STOP
226 :
227 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
228 : ! Testing RandomSeed_type for equivalence of Seed vector on all images
229 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
230 :
231 1 : assertion = .true.
232 : #if defined CAF_ENABLED
233 : sync all
234 : if (Test%Image%id==1) then
235 : sync images(*)
236 : else
237 : if ( any(Seed /= Seed(:)[1]) ) assertion = .false.
238 : sync images(1)
239 : end if
240 : #endif
241 :
242 1 : RandomSeed = RandomSeed_type(imageID=Test%Image%id, isRepeatable=.true., isImageDistinct=.false.)
243 1 : assertion = .not. RandomSeed%Err%occurred
244 1 : if (.not. assertion) return
245 :
246 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
247 : ! Testing RandomSeed_type for equivalence of the old and the new Seed vector on each image
248 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
249 :
250 : block
251 : integer, allocatable, save :: SeedNew(:)
252 1 : allocate( SeedNew(seedSize) )
253 1 : call random_seed(get=SeedNew)
254 9 : assertion = all(SeedNew==Seed)
255 : ! LCOV_EXCL_START
256 : if (Test%isDebugMode .and. .not. assertion) then
257 : if (Test%Image%id==1) then
258 : write(Test%outputUnit,"(*(g0,' '))") "this_image(), SeedOld:", Test%Image%id,",", Seed
259 : write(Test%outputUnit,"(*(g0,' '))") "this_image(), SeedNew:", Test%Image%id,",", SeedNew
260 : #if defined CAF_ENABLED
261 : else
262 : sync images (Test%Image%id-1)
263 : write(Test%outputUnit,"(*(g0,' '))") "this_image(), SeedOld:", Test%Image%id,",", Seed
264 : write(Test%outputUnit,"(*(g0,' '))") "this_image(), SeedNew:", Test%Image%id,",", SeedNew
265 : #endif
266 : end if
267 : #if defined CAF_ENABLED
268 : if (Test%Image%id<Test%Image%count) sync images (Test%Image%id+1)
269 : #endif
270 : end if
271 : ! LCOV_EXCL_STOP
272 1 : deallocate(SeedNew)
273 : end block
274 :
275 : #if defined CAF_ENABLED
276 : sync all
277 : #endif
278 :
279 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
280 : ! Testing RandomSeed_type with isRepeatable=.true., isImageDistinct=.true.
281 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
282 :
283 1 : RandomSeed = RandomSeed_type(imageID=Test%Image%id, isRepeatable=.true., isImageDistinct=.true.)
284 1 : assertion = .not. RandomSeed%Err%occurred
285 1 : if (.not. assertion) return
286 :
287 1 : call random_seed(get=Seed)
288 9 : assertion = all(RandomSeed%Value == Seed)
289 :
290 : ! LCOV_EXCL_START
291 : if (Test%isDebugMode .and. .not. assertion) then
292 :
293 : write(Test%outputUnit,"(*(g0,:,' '))")
294 : write(Test%outputUnit,"(*(g0,:,' '))") "RandomSeed%isRepeatable :", RandomSeed%isRepeatable
295 : write(Test%outputUnit,"(*(g0,:,' '))") "RandomSeed%isImageDistinct :", RandomSeed%isImageDistinct
296 : write(Test%outputUnit,"(*(g0,:,' '))") "RandomSeed%info :", RandomSeed%info
297 : write(Test%outputUnit,"(*(g0,:,' '))") "RandomSeed%size :", RandomSeed%size
298 : write(Test%outputUnit,"(*(g0,:,' '))")
299 :
300 : if (Test%Image%id==1) then
301 : write(Test%outputUnit,"(*(g0,' '))") "this_image(), GETPID(), Seed:", Test%Image%id, ",", RandomSeed%imageID, ",", RandomSeed%Value
302 : #if defined CAF_ENABLED
303 : else
304 : sync images (Test%Image%id-1)
305 : write(Test%outputUnit,"(*(g0,' '))") "this_image(), GETPID(), Seed:", Test%Image%id, ",", RandomSeed%imageID, ",", RandomSeed%Value
306 : #endif
307 : end if
308 : #if defined CAF_ENABLED
309 : if (Test%Image%id<Test%Image%count) sync images (Test%Image%id+1)
310 : #endif
311 :
312 : end if
313 : ! LCOV_EXCL_STOP
314 :
315 : #if defined CAF_ENABLED
316 : sync all
317 : #endif
318 :
319 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
320 : ! Testing RandomSeed_type for equivalence of the old and the new Seed vector on each image
321 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
322 :
323 1 : RandomSeed = RandomSeed_type(imageID=Test%Image%id, isRepeatable=.true., isImageDistinct=.true.)
324 1 : assertion = .not. RandomSeed%Err%occurred
325 1 : if (.not. assertion) return
326 :
327 : block
328 : integer, allocatable, save :: SeedNew(:)
329 1 : allocate( SeedNew(seedSize) )
330 1 : call random_seed(get=SeedNew)
331 9 : assertion = all(SeedNew==Seed)
332 : ! LCOV_EXCL_START
333 : if (Test%isDebugMode .and. .not. assertion) then
334 : if (Test%Image%id==1) then
335 : write(Test%outputUnit,"(*(g0,' '))") "this_image(), SeedOld(diff. on each image):", Test%Image%id,",", Seed
336 : write(Test%outputUnit,"(*(g0,' '))") "this_image(), SeedNew(diff. on each image):", Test%Image%id,",", SeedNew
337 : #if defined CAF_ENABLED
338 : else
339 : sync images (Test%Image%id-1)
340 : write(Test%outputUnit,"(*(g0,' '))") "this_image(), SeedOld(diff. on each image):", Test%Image%id,",", Seed
341 : write(Test%outputUnit,"(*(g0,' '))") "this_image(), SeedNew(diff. on each image):", Test%Image%id,",", SeedNew
342 : #endif
343 : end if
344 : #if defined CAF_ENABLED
345 : if (Test%Image%id<Test%Image%count) sync images (Test%Image%id+1)
346 : #endif
347 : end if
348 : ! LCOV_EXCL_STOP
349 1 : deallocate(SeedNew)
350 : end block
351 :
352 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
353 : ! Testing RandomSeed_type for non-equivalence of Seed vector on all images
354 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
355 :
356 1 : assertion = .true.
357 : #if defined CAF_ENABLED
358 : sync all
359 : if (Test%Image%id==1) then
360 : sync images(*)
361 : else
362 : if ( all(Seed == Seed(:)[1]) ) assertion = .false.
363 : sync images(1)
364 : end if
365 : #endif
366 :
367 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
368 : ! Testing RandomSeed_type(inputSeed = 1313, isImageDistinct=.false.)
369 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
370 :
371 1 : RandomSeed = RandomSeed_type(imageID=Test%Image%id, inputSeed = 1313, isImageDistinct=.false.)
372 1 : assertion = .not. RandomSeed%Err%occurred
373 1 : if (.not. assertion) return
374 :
375 : ! LCOV_EXCL_START
376 : if (Test%isDebugMode .and. .not. assertion) then
377 : #if defined CAF_ENABLED
378 : if (Test%Image%id==1) then
379 : write(Test%outputUnit,"(*(g0,' '))") "this_image(), Seed(same on each image):", Test%Image%id,",", RandomSeed%Value
380 : else
381 : sync images (Test%Image%id-1)
382 : write(Test%outputUnit,"(*(g0,' '))") "this_image(), Seed(same on each image):", Test%Image%id,",", RandomSeed%Value
383 : end if
384 : if (Test%Image%id<Test%Image%count) sync images (Test%Image%id+1)
385 : #endif
386 : end if
387 : ! LCOV_EXCL_STOP
388 :
389 1 : call random_seed(get=Seed)
390 1 : assertion = .true.
391 :
392 : #if defined CAF_ENABLED
393 : sync all
394 : if (Test%Image%id==1) then
395 : sync images(*)
396 : else
397 : if ( any(Seed /= Seed(:)[1]) ) assertion = .false.
398 : sync images(1)
399 : end if
400 : #endif
401 :
402 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
403 : ! Testing RandomSeed_type(inputSeed = 1313, isImageDistinct=.true.)
404 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
405 :
406 1 : RandomSeed = RandomSeed_type(imageID=Test%Image%id, inputSeed = 1313, isImageDistinct=.true.)
407 1 : assertion = .not. RandomSeed%Err%occurred
408 1 : if (.not. assertion) return
409 :
410 1 : call random_seed(get=Seed)
411 1 : assertion = .true.
412 : #if defined CAF_ENABLED
413 : sync all
414 : if (Test%Image%id==1) then
415 : sync images(*)
416 : else
417 : if ( any(Seed == Seed(:)[1]) ) assertion = .false.
418 : sync images(1)
419 : end if
420 : #endif
421 :
422 : ! LCOV_EXCL_START
423 : if (Test%isDebugMode .and. .not. assertion) then
424 : if (Test%Image%id==1) then
425 : write(Test%outputUnit,"(*(g0,' '))") "this_image(), Seed(same on each image):", Test%Image%id,",", RandomSeed%Value
426 : #if defined CAF_ENABLED
427 : else
428 : sync images (Test%Image%id-1)
429 : write(Test%outputUnit,"(*(g0,' '))") "this_image(), Seed(same on each image):", Test%Image%id,",", RandomSeed%Value
430 : #endif
431 : end if
432 : #if defined CAF_ENABLED
433 : if (Test%Image%id<Test%Image%count) sync images (Test%Image%id+1)
434 : #endif
435 : end if
436 : ! LCOV_EXCL_STOP
437 :
438 1 : deallocate( Seed )
439 :
440 2 : end function test_constructRandomSeed
441 :
442 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
443 :
444 : end module Test_RandomSeed_mod ! LCOV_EXCL_LINE
|