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
44 : !> This module contains the classes and procedures for setting up the `randomSeed` attribute of ParaMonte samplers.
45 : !> For more information, see the description of this attribute in the body of the module.
46 : !> \author Amir Shahmoradi
47 :
48 : module SpecBase_RandomSeed_mod
49 :
50 : use RandomSeed_mod, only: RandomSeed_t => RandomSeed_type
51 : use Constants_mod, only: IK
52 : implicit none
53 :
54 : #if defined CAF_ENABLED
55 : ! This must be allocatable, even though it will have only one element.
56 : ! Otherwise, GNU Fortran 10 compiler results in runtime segmentation fault in coarray mode,
57 : ! when the routine is called multiple times.
58 : type(RandomSeed_t), allocatable :: comv_RandomSeed(:)[:]
59 : #else
60 : type(RandomSeed_t), allocatable :: comv_RandomSeed(:)
61 : #endif
62 :
63 : character(*), parameter :: MODULE_NAME = "@SpecBase_RandomSeed_mod"
64 :
65 : integer(IK) :: randomSeed ! namelist input
66 :
67 : type :: RandomSeed_type
68 : logical :: isImageDistinct
69 : logical :: isRepeatable
70 : integer(IK) :: userSeed
71 : integer(IK) :: nullSeed
72 : integer(IK) :: sizeSeed
73 : integer(IK) :: imageID
74 : integer(IK) :: imageCount
75 : integer(IK) :: ProcessID
76 : integer(IK) , allocatable :: Seed(:,:)
77 : character(:), allocatable :: desc
78 : contains
79 : procedure, pass :: set => setRandomSeed, nullifyNameListVar ! , checkForSanity
80 : end type RandomSeed_type
81 :
82 : interface RandomSeed_type
83 : module procedure :: constructRandomSeed
84 : end interface RandomSeed_type
85 : private :: constructRandomSeed, setRandomSeed, nullifyNameListVar ! , checkForSanity
86 :
87 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
88 :
89 : contains
90 :
91 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
92 :
93 349 : function constructRandomSeed(methodName,imageID,imageCount) result(RandomSeedObj)
94 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
95 : !DEC$ ATTRIBUTES DLLEXPORT :: constructRandomSeed
96 : #endif
97 : use Constants_mod, only: IK, NULL_IK
98 : implicit none
99 : character(*), intent(in) :: methodName
100 : integer(IK), intent(in) :: imageID, imageCount
101 : type(RandomSeed_type) :: RandomSeedObj
102 349 : RandomSeedObj%userSeed = NULL_IK
103 349 : RandomSeedObj%nullSeed = NULL_IK
104 349 : RandomSeedObj%ProcessID = NULL_IK
105 349 : RandomSeedObj%isRepeatable = .false.
106 349 : RandomSeedObj%isImageDistinct = .true.
107 349 : RandomSeedObj%imageID = imageID
108 349 : RandomSeedObj%imageCount = imageCount
109 349 : call random_seed(size=RandomSeedObj%sizeSeed)
110 349 : allocate(RandomSeedObj%Seed(RandomSeedObj%sizeSeed,RandomSeedObj%imageCount))
111 : RandomSeedObj%desc = &
112 : "randomSeed is a scalar 32bit integer that serves as the seed of the random number generator. When it is provided, &
113 : &the seed of the random number generator will be set in a specific deterministic manner to enable future replications &
114 : &of the simulation with the same configuration and input specifications. The default value for randomSeed is an integer &
115 : &vector of processor-dependent size and value that will vary from one simulation to another. &
116 : &However, enough care has been taken to assign unique random seed values to the random number generator on &
117 349 : &each of the parallel threads (or images, processors, cores, ...) at all circumstances."
118 349 : end function constructRandomSeed
119 :
120 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
121 :
122 349 : subroutine nullifyNameListVar(RandomSeedObj)
123 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
124 : !DEC$ ATTRIBUTES DLLEXPORT :: nullifyNameListVar
125 : #endif
126 : implicit none
127 : class(RandomSeed_type), intent(in) :: RandomSeedObj
128 349 : randomSeed = RandomSeedObj%nullSeed
129 349 : end subroutine nullifyNameListVar
130 :
131 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
132 :
133 798 : subroutine setRandomSeed(RandomSeedObj,randomSeed,Err)
134 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
135 : !DEC$ ATTRIBUTES DLLEXPORT :: setRandomSeed
136 : #endif
137 :
138 349 : use Constants_mod, only: IK
139 : use Err_mod, only: Err_type
140 :
141 : #if defined CAF_ENABLED
142 : implicit none
143 : integer(IK) :: imageID
144 : #elif defined MPI_ENABLED
145 : use mpi
146 : implicit none
147 : integer :: ierrMPI
148 : integer(IK), allocatable :: Seed(:,:)
149 : #endif
150 :
151 : class(RandomSeed_type), intent(inout) :: RandomSeedObj
152 : integer(IK), intent(in) :: randomSeed
153 : type(Err_type), intent(out) :: Err
154 :
155 : character(*), parameter :: PROCEDURE_NAME = MODULE_NAME // "@setRandomSeed()"
156 :
157 399 : RandomSeedObj%userSeed = randomSeed
158 :
159 : ! broadcast all random seed values of all images to all images
160 :
161 : #if defined CAF_ENABLED
162 : allocate(comv_RandomSeed(1)[*])
163 : #else
164 798 : allocate(comv_RandomSeed(1))
165 : #endif
166 :
167 399 : if ( RandomSeedObj%userSeed == RandomSeedObj%nullSeed ) then
168 : comv_RandomSeed(1) = RandomSeed_t ( imageID = RandomSeedObj%imageID & ! LCOV_EXCL_LINE
169 : , isRepeatable = RandomSeedObj%isRepeatable & ! LCOV_EXCL_LINE
170 : , isImageDistinct = RandomSeedObj%isImageDistinct & ! LCOV_EXCL_LINE
171 341 : )
172 : else
173 : comv_RandomSeed(1) = RandomSeed_t ( imageID = RandomSeedObj%imageID & ! LCOV_EXCL_LINE
174 : , isRepeatable = RandomSeedObj%isRepeatable & ! LCOV_EXCL_LINE
175 : , isImageDistinct = RandomSeedObj%isImageDistinct & ! LCOV_EXCL_LINE
176 : , inputSeed = RandomSeedObj%userSeed & ! LCOV_EXCL_LINE
177 58 : )
178 : end if
179 :
180 : #if defined GNU_COMPILER_ENABLED && CAF_ENABLED
181 : ! opencoarrays crashes without this, by somehow setting comv_RandomSeed(1)%Err%occurred = TRUE
182 : ! likely a result of memory corruption
183 : !if (comv_RandomSeed(1)%Err%occurred) write(*,*) ""
184 : #endif
185 :
186 399 : if (comv_RandomSeed(1)%Err%occurred) then
187 : ! LCOV_EXCL_START
188 : Err%occurred = .true.
189 : Err%msg = Err%msg // PROCEDURE_NAME // comv_RandomSeed(1)%Err%msg
190 : return
191 : ! LCOV_EXCL_STOP
192 : end if
193 :
194 399 : call comv_RandomSeed(1)%get()
195 3591 : RandomSeedObj%Seed(:,RandomSeedObj%imageID) = comv_RandomSeed(1)%Value(:)
196 : #if defined CAF_ENABLED
197 : sync all ! allow all images to set the seed first, then fetch the values
198 : do imageID = 1, RandomSeedObj%imageCount
199 : if (imageID/=RandomSeedObj%imageID) RandomSeedObj%Seed(:,imageID) = comv_RandomSeed(1)[imageID]%Value(:)
200 : end do
201 : #elif defined MPI_ENABLED
202 : allocate(Seed(RandomSeedObj%sizeSeed,RandomSeedObj%imageCount))
203 : call mpi_barrier(mpi_comm_world,ierrMPI) ! allow all images to set the seed first, then fetch the values
204 : call mpi_allgather ( RandomSeedObj%Seed(:,RandomSeedObj%imageID) & ! LCOV_EXCL_LINE : send buffer
205 : , RandomSeedObj%sizeSeed & ! LCOV_EXCL_LINE : send count
206 : , mpi_integer & ! LCOV_EXCL_LINE : send datatype
207 : , Seed(:,:) & ! LCOV_EXCL_LINE : receive buffer
208 : , RandomSeedObj%sizeSeed & ! LCOV_EXCL_LINE : receive count
209 : , mpi_integer & ! LCOV_EXCL_LINE : receive datatype
210 : , mpi_comm_world & ! LCOV_EXCL_LINE : comm
211 : , ierrMPI & ! LCOV_EXCL_LINE : ierr
212 : )
213 : RandomSeedObj%Seed(:,:) = Seed
214 : deallocate(Seed)
215 : #endif
216 1197 : deallocate(comv_RandomSeed)
217 :
218 399 : end subroutine setRandomSeed
219 :
220 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
221 :
222 : end module SpecBase_RandomSeed_mod ! LCOV_EXCL_LINE
|