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 [Parallelism_mod](@ref parallelism_mod).
44 : !> \author Amir Shahmoradi
45 :
46 : module Test_Parallelism_mod
47 :
48 : use Test_mod, only: Test_type
49 : use Parallelism_mod
50 : implicit none
51 :
52 : private
53 : public :: test_Parallelism
54 :
55 : type(Test_type) :: Test
56 :
57 : real(RK) , parameter :: comSecTime = 5.E-007_RK
58 : real(RK) , parameter :: parSecTime = .7E-03_RK
59 : real(RK) , parameter :: successProb = 0.234_RK
60 : integer(IK), parameter :: lenProcessID = 100_IK
61 : integer(IK), parameter :: processCount = 8_IK
62 : integer(IK), parameter :: ProcessID(lenProcessID) = [ 1_IK, 3_IK, 7_IK, 6_IK, 6_IK, 1_IK, 2_IK, 8_IK, 8_IK, 2_IK &
63 : , 8_IK, 3_IK, 7_IK, 6_IK, 3_IK, 5_IK, 8_IK, 4_IK, 8_IK, 4_IK &
64 : , 1_IK, 5_IK, 3_IK, 3_IK, 7_IK, 6_IK, 2_IK, 2_IK, 4_IK, 3_IK &
65 : , 2_IK, 2_IK, 4_IK, 4_IK, 7_IK, 3_IK, 8_IK, 4_IK, 6_IK, 4_IK &
66 : , 3_IK, 2_IK, 8_IK, 3_IK, 8_IK, 1_IK, 1_IK, 1_IK, 4_IK, 2_IK &
67 : , 8_IK, 4_IK, 6_IK, 5_IK, 3_IK, 1_IK, 8_IK, 4_IK, 1_IK, 3_IK &
68 : , 4_IK, 3_IK, 4_IK, 8_IK, 3_IK, 6_IK, 2_IK, 7_IK, 8_IK, 4_IK &
69 : , 7_IK, 5_IK, 4_IK, 5_IK, 1_IK, 2_IK, 1_IK, 3_IK, 3_IK, 6_IK &
70 : , 5_IK, 6_IK, 4_IK, 6_IK, 1_IK, 5_IK, 3_IK, 8_IK, 8_IK, 7_IK &
71 : , 7_IK, 6_IK, 8_IK, 1_IK, 2_IK, 3_IK, 1_IK, 3_IK, 8_IK, 4_IK ]
72 : real(RK) , parameter :: ForkJoinSpeedupScaling(*)=[ 1.0000000000000000_RK, 1.9709401945470562_RK, 2.9130986783067012_RK, 3.8267945495787576_RK &
73 : , 4.7123840519965787_RK, 5.5702568576898672_RK, 6.4008325027127082_RK, 7.2045569830497680_RK &
74 : , 7.9818995172384897_RK, 8.7333494795853746_RK, 9.4594135061080085_RK, 10.160612773695840_RK &
75 : , 10.837480451544774_RK, 11.490559322673228_RK, 12.120399572259624_RK, 12.727556738641406_RK &
76 : , 13.312589822070557_RK, 13.876059545717652_RK, 14.418526762942477_RK, 14.940551004491214_RK &
77 : , 15.442689159026127_RK, 15.925494280231174_RK, 16.389514513655225_RK, 16.835292136442131_RK &
78 : , 17.263362703145123_RK, 17.674254290921780_RK, 18.068486837547017_RK, 18.446571565858278_RK &
79 : , 18.809010488451573_RK, 19.156295986674149_RK, 19.488910458202938_RK, 19.807326027754005_RK &
80 : , 20.112004315731770_RK, 20.403396259894631_RK, 20.681941985383180_RK, 20.948070718725017_RK &
81 : , 21.202200741694575_RK, 21.444739381165583_RK, 21.676083031346092_RK, 21.896617205030289_RK &
82 : , 22.106716610736861_RK, 22.306745252829629_RK, 22.497056551931891_RK, 22.677993483151678_RK &
83 : , 22.849888729829892_RK, 23.013064850708005_RK, 23.167834458585791_RK, 23.314500408703378_RK &
84 : , 23.453355995235302_RK, 23.584685154428104_RK, 23.708762673047069_RK, 23.825854400923014_RK &
85 : , 23.936217466505919_RK, 24.040100494440729_RK, 24.137743824279756_RK, 24.229379729539652_RK &
86 : , 24.315232636394896_RK, 24.395519341379647_RK, 24.470449227540744_RK, 24.540224478552073_RK &
87 : , 24.605040290360275_RK, 24.665085079988089_RK, 24.720540691171845_RK, 24.771582596555930_RK &
88 : , 24.818380096209165_RK, 24.861096512266098_RK, 24.899889379530705_RK, 24.934910631911251_RK &
89 : , 24.966306784583264_RK, 24.994219111802845_RK, 25.018783820315196_RK, 25.040132218323745_RK &
90 : , 25.058390880003248_RK, 25.073681805556479_RK, 25.086122576828277_RK, 25.095826508503546_RK &
91 : , 25.102902794926649_RK, 25.107456652589516_RK, 25.109589458344086_RK, 25.109398883401962_RK &
92 : , 25.106979023190462_RK, 25.102420523139443_RK, 25.095810700477681_RK, 25.087233662121250_RK &
93 : , 25.076770418739297_RK, 25.064498995084946_RK, 25.050494536680663_RK, 25.034829412948952_RK &
94 : , 25.017573316879893_RK, 24.998793361327269_RK, 24.978554172025603_RK, 24.956917977419540_RK &
95 : , 24.933944695397066_RK, 24.909692017016823_RK, 24.884215487319214_RK, 24.857568583309476_RK &
96 : , 24.829802789199849_RK, 24.800967668996421_RK, 24.771110936514656_RK, 24.740278522906117_RK &
97 : , 24.708514641776901_RK, 24.675861851976773_RK, 24.642361118136034_RK, 24.608051869025356_RK &
98 : , 24.572972053811721_RK, 24.537158196282036_RK, 24.500645447103722_RK, 24.463467634189893_RK &
99 : , 24.425657311234712_RK, 24.387245804482649_RK, 24.348263257793459_RK, 24.308738676062795_RK &
100 : , 24.268699967056719_RK, 24.228173981716250_RK, 24.187186552986518_RK, 24.145762533223461_RK &
101 : , 24.103925830228839_RK, 24.061699441963224_RK, 24.019105489984572_RK, 23.976165251658554_RK &
102 : , 23.932899191185239_RK, 23.889326989485234_RK, 23.845467572986806_RK, 23.801339141354195_RK &
103 : , 23.756959194195876_RK, 23.712344556790100_RK, 23.667511404863891_RK, 23.622475288460180_RK ]
104 :
105 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
106 :
107 : contains
108 :
109 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
110 :
111 1 : subroutine test_Parallelism()
112 : implicit none
113 1 : Test = Test_type(moduleName=MODULE_NAME)
114 1 : call Test%run(test_constructForkJoin_1, "test_constructForkJoin_1")
115 1 : call Test%run(test_constructForkJoin_2, "test_constructForkJoin_2")
116 1 : call Test%run(test_constructForkJoin_3, "test_constructForkJoin_3")
117 1 : call Test%run(test_constructForkJoin_4, "test_constructForkJoin_4")
118 1 : call Test%run(test_constructForkJoin_5, "test_constructForkJoin_5")
119 1 : call Test%run(test_constructForkJoin_6, "test_constructForkJoin_6")
120 1 : call Test%run(test_constructForkJoin_7, "test_constructForkJoin_7")
121 1 : call Test%finalize()
122 1 : end subroutine test_Parallelism
123 :
124 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
125 :
126 : !> \brief
127 : !> Test the ForkJoin constructor with valid input.
128 1 : function test_constructForkJoin_1() result(assertion)
129 1 : use Constants_mod, only: IK, RK
130 : implicit none
131 : logical :: assertion
132 : real(RK), parameter :: tolerance = 1.e-5_RK
133 1 : type(ForkJoin_type) :: ForkJoin
134 :
135 : ForkJoin = ForkJoin_type( processCount = processCount &
136 : , lenProcessID = lenProcessID &
137 : , ProcessID = ProcessID &
138 : , successProb = successProb &
139 : , seqSecTime = epsilon(1._RK) &
140 : , parSecTime = parSecTime &
141 : , comSecTime = comSecTime &
142 1 : )
143 1 : assertion = .not. ForkJoin%Err%occurred
144 : if (.not. assertion) return ! LCOV_EXCL_LINE
145 :
146 1 : assertion = assertion .and. ForkJoin%UniqueProcess%count == 8_IK
147 9 : assertion = assertion .and. all(ForkJoin%UniqueProcess%Identity == [1_IK, 2_IK, 3_IK, 4_IK, 5_IK, 6_IK, 7_IK, 8_IK])
148 9 : assertion = assertion .and. all(ForkJoin%UniqueProcess%Frequency == [13_IK, 11_IK, 18_IK, 16_IK, 7_IK, 11_IK, 8_IK, 16_IK])
149 :
150 1 : if (Test%isDebugMode .and. .not. assertion) then
151 : ! LCOV_EXCL_START
152 : write(*,"(10(g0,:,', '))")
153 : write(*,"(10(g0,:,', '))") "ForkJoin%UniqueProcess%count ", ForkJoin%UniqueProcess%count
154 : write(*,"(10(g0,:,', '))") "ForkJoin_UniqueProcess_count ", 8_IK
155 : write(*,"(10(g0,:,', '))") "ForkJoin%UniqueProcess%Identity ", ForkJoin%UniqueProcess%Identity
156 : write(*,"(10(g0,:,', '))") "ForkJoin_UniqueProcess_Identity ", [1_IK, 2_IK, 3_IK, 4_IK, 5_IK, 6_IK, 7_IK, 8_IK]
157 : write(*,"(10(g0,:,', '))") "ForkJoin%UniqueProcess%Frequency", ForkJoin%UniqueProcess%Frequency
158 : write(*,"(10(g0,:,', '))") "ForkJoin_UniqueProcess_Frequency", [13_IK, 11_IK, 18_IK, 16_IK, 7_IK, 11_IK, 8_IK, 16_IK]
159 : write(*,"(10(g0,:,', '))")
160 : end if
161 : ! LCOV_EXCL_STOP
162 :
163 1 : assertion = assertion .and. ForkJoin%Contribution%count == 8_IK
164 9 : assertion = assertion .and. all(ForkJoin%Contribution%Identity == [1_IK, 2_IK, 3_IK, 4_IK, 5_IK, 6_IK, 7_IK, 8_IK])
165 9 : assertion = assertion .and. all(ForkJoin%Contribution%Frequency == [13_IK, 11_IK, 18_IK, 16_IK, 7_IK, 11_IK, 8_IK, 16_IK])
166 : assertion = assertion .and. all( abs(ForkJoin%Contribution%LogFrequency-[ 2.5649493574615367_RK & ! LCOV_EXCL_LINE
167 : , 2.3978952727983707_RK & ! LCOV_EXCL_LINE
168 : , 2.8903717578961645_RK & ! LCOV_EXCL_LINE
169 : , 2.7725887222397811_RK & ! LCOV_EXCL_LINE
170 : , 1.9459101490553132_RK & ! LCOV_EXCL_LINE
171 : , 2.3978952727983707_RK & ! LCOV_EXCL_LINE
172 : , 2.0794415416798357_RK & ! LCOV_EXCL_LINE
173 9 : , 2.7725887222397811_RK ] ) < 1.e-10_RK )
174 :
175 1 : if (Test%isDebugMode .and. .not. assertion) then
176 : ! LCOV_EXCL_START
177 : write(*,"(10(g0,:,', '))")
178 : write(*,"(10(g0,:,', '))") "ForkJoin%Contribution%count"
179 : write(*,"(10(g0,:,', '))") ForkJoin%Contribution%count
180 : write(*,"(10(g0,:,', '))") "ForkJoin%Contribution%Identity"
181 : write(*,"(10(g0,:,', '))") ForkJoin%Contribution%Identity
182 : write(*,"(10(g0,:,', '))") "ForkJoin%Contribution%Frequency"
183 : write(*,"(10(g0,:,', '))") ForkJoin%Contribution%Frequency
184 : write(*,"(10(g0,:,', '))") "ForkJoin%Contribution%LogFrequency"
185 : write(*,"(10(g0,:,', '))") ForkJoin%Contribution%LogFrequency
186 : write(*,"(10(g0,:,', '))")
187 : end if
188 : ! LCOV_EXCL_STOP
189 :
190 1 : assertion = assertion .and. abs(ForkJoin%SuccessProb%current - successProb) < tolerance
191 1 : assertion = assertion .and. abs(ForkJoin%SuccessProb%effective - ForkJoin%SuccessProb%PowellMinimum%xmin(1)) < tolerance
192 3 : assertion = assertion .and. all( abs(ForkJoin%SuccessProb%PowellMinimum%xmin - [0.28663337425270718E-1_RK, 4.5593657754033101_RK]) < tolerance )
193 : assertion = assertion .and. all( abs(ForkJoin%Contribution%LogFrequency-[ 2.5649493574615367_RK & ! LCOV_EXCL_LINE
194 : , 2.3978952727983707_RK & ! LCOV_EXCL_LINE
195 : , 2.8903717578961645_RK & ! LCOV_EXCL_LINE
196 : , 2.7725887222397811_RK & ! LCOV_EXCL_LINE
197 : , 1.9459101490553132_RK & ! LCOV_EXCL_LINE
198 : , 2.3978952727983707_RK & ! LCOV_EXCL_LINE
199 : , 2.0794415416798357_RK & ! LCOV_EXCL_LINE
200 9 : , 2.7725887222397811_RK ] ) < tolerance )
201 :
202 1 : if (Test%isDebugMode .and. .not. assertion) then
203 : ! LCOV_EXCL_START
204 : write(*,"(10(g0,:,', '))")
205 : write(*,"(10(g0,:,', '))") "ForkJoin%SuccessProb%current ", ForkJoin%SuccessProb%current
206 : write(*,"(10(g0,:,', '))") "ForkJoin_SuccessProb_current ", successProb
207 : write(*,"(10(g0,:,', '))") "ForkJoin%SuccessProb%effective ", ForkJoin%SuccessProb%effective
208 : write(*,"(10(g0,:,', '))") "ForkJoin_SuccessProb_effective ", ForkJoin%SuccessProb%PowellMinimum%xmin(1)
209 : write(*,"(10(g0,:,', '))") "ForkJoin%SuccessProb%PowellMinimum%xmin ", ForkJoin%SuccessProb%PowellMinimum%xmin
210 : write(*,"(10(g0,:,', '))") "ForkJoin_SuccessProb_PowellMinimum_xmin ", [0.28663337425270718E-1_RK, 4.5593657754033101_RK]
211 : write(*,"(10(g0,:,', '))")
212 : end if
213 : ! LCOV_EXCL_STOP
214 :
215 1 : assertion = assertion .and. ForkJoin%Speedup%count == size(ForkJoinSpeedupScaling)
216 1 : assertion = assertion .and. ForkJoin%Speedup%Maximum%nproc == 79_IK
217 1 : assertion = assertion .and. abs(ForkJoin%Speedup%Maximum%value - 25.109589458344086_RK) < tolerance
218 1 : assertion = assertion .and. abs(ForkJoin%Speedup%current - 7.2045569830497680_RK) < tolerance
219 129 : assertion = assertion .and. all(abs(ForkJoin%Speedup%Scaling - ForkJoinSpeedupScaling) < tolerance)
220 :
221 1 : if (Test%isDebugMode .and. .not. assertion) then
222 : ! LCOV_EXCL_START
223 : write(*,"(10(g0,:,', '))")
224 : write(*,"(10(g0,:,', '))") "ForkJoin%Speedup%count ", ForkJoin%Speedup%count
225 : write(*,"(10(g0,:,', '))") "ForkJoin_Speedup_count ", size(ForkJoinSpeedupScaling)
226 : write(*,"(10(g0,:,', '))") "ForkJoin%Speedup%current ", ForkJoin%Speedup%current
227 : write(*,"(10(g0,:,', '))") "ForkJoin_Speedup_current ", 7.2045569830497680_RK
228 : write(*,"(10(g0,:,', '))") "ForkJoin%Speedup%maximum%value ", ForkJoin%Speedup%maximum%value
229 : write(*,"(10(g0,:,', '))") "ForkJoin_Speedup_maximum_value ", 25.109589458344086_RK
230 : write(*,"(10(g0,:,', '))") "ForkJoin%Speedup%maximum%nproc ", ForkJoin%Speedup%maximum%nproc
231 : write(*,"(10(g0,:,', '))") "ForkJoin_Speedup_maximum_nproc ", 79_IK
232 : write(*,"(10(g0,:,', '))") "ForkJoin%Speedup%Scaling ", ForkJoin%Speedup%Scaling
233 : write(*,"(10(g0,:,', '))") "ForkJoin%Speedup%Scaling ", ForkJoinSpeedupScaling
234 : write(*,"(10(g0,:,', '))") "Difference ", abs(ForkJoin%Speedup%Scaling - ForkJoinSpeedupScaling)
235 : write(*,"(10(g0,:,', '))")
236 : end if
237 : ! LCOV_EXCL_STOP
238 :
239 1 : end function test_constructForkJoin_1
240 :
241 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
242 :
243 : !> \brief
244 : !> Test the ForkJoin constructor with a valid input `processCount == 1`.
245 1 : function test_constructForkJoin_2() result(assertion)
246 1 : use Constants_mod, only: IK, RK
247 : implicit none
248 : logical :: assertion
249 1 : type(ForkJoin_type) :: ForkJoin
250 : real(RK), parameter :: tolerance = 1.e-5_RK
251 :
252 : integer(IK) , parameter :: processCount = 1_IK
253 : real(RK) , parameter :: ForkJoin_Speedup_Maximum_value = 1._RK
254 : integer(IK) , parameter :: ForkJoin_Speedup_Maximum_nproc = 1_IK
255 : real(RK) , parameter :: ForkJoin_Speedup_current = 1._RK
256 : integer(IK) , parameter :: ForkJoin_Speedup_count = 1_IK
257 : real(RK) , parameter :: ForkJoin_Speedup_Scaling(*) = [1._RK]
258 : integer(IK) , parameter :: ForkJoin_Contribution_count = processCount
259 : integer(IK) , parameter :: ForkJoin_Contribution_Identity(*) = [1_IK]
260 : integer(IK) , parameter :: ForkJoin_Contribution_Frequency(*) = [lenProcessID]
261 : real(RK) , parameter :: ForkJoin_Contribution_LogFrequency(*) = log(real(ForkJoin_Contribution_Frequency,kind=RK))
262 : integer(IK) , parameter :: ForkJoin_UniqueProcess_count = 1_IK
263 : integer(IK) , parameter :: ForkJoin_UniqueProcess_Identity(*) = [1_IK]
264 : integer(IK) , parameter :: ForkJoin_UniqueProcess_Frequency(*) = [lenProcessID]
265 : real(RK) , parameter :: ForkJoin_SuccessProb_current = successProb
266 : real(RK) , parameter :: ForkJoin_SuccessProb_effective = successProb
267 :
268 : ForkJoin = ForkJoin_type( processCount = processCount &
269 : , lenProcessID = lenProcessID &
270 : , ProcessID = ProcessID &
271 : , successProb = successProb &
272 : , seqSecTime = epsilon(1._RK) &
273 : , parSecTime = parSecTime &
274 : , comSecTime = comSecTime &
275 1 : )
276 1 : assertion = .not. ForkJoin%Err%occurred
277 1 : assertion = assertion .and. ForkJoin%Speedup%Maximum%value == ForkJoin_Speedup_Maximum_value
278 1 : assertion = assertion .and. ForkJoin%Speedup%Maximum%nproc == ForkJoin_Speedup_Maximum_nproc
279 1 : assertion = assertion .and. ForkJoin%Speedup%current == ForkJoin_Speedup_current
280 1 : assertion = assertion .and. ForkJoin%Speedup%count == ForkJoin_Speedup_count
281 2 : assertion = assertion .and. all(ForkJoin%Speedup%Scaling == ForkJoin_Speedup_Scaling)
282 1 : assertion = assertion .and. ForkJoin%Contribution%count == ForkJoin_Contribution_count
283 2 : assertion = assertion .and. all(ForkJoin%Contribution%Identity == ForkJoin_Contribution_Identity)
284 2 : assertion = assertion .and. all(ForkJoin%Contribution%Frequency == ForkJoin_Contribution_Frequency)
285 2 : assertion = assertion .and. all(ForkJoin%Contribution%LogFrequency == ForkJoin_Contribution_LogFrequency)
286 1 : assertion = assertion .and. ForkJoin%UniqueProcess%count == ForkJoin_UniqueProcess_count
287 2 : assertion = assertion .and. all(ForkJoin%UniqueProcess%Identity == ForkJoin_UniqueProcess_Identity)
288 2 : assertion = assertion .and. all(ForkJoin%UniqueProcess%Frequency == ForkJoin_UniqueProcess_Frequency)
289 1 : assertion = assertion .and. abs(ForkJoin%SuccessProb%current - ForkJoin_SuccessProb_current) < tolerance
290 1 : assertion = assertion .and. abs(ForkJoin%SuccessProb%effective - ForkJoin_SuccessProb_effective) < tolerance
291 :
292 1 : if (Test%isDebugMode .and. .not. assertion) then
293 : ! LCOV_EXCL_START
294 : write(*,"(10(g0,:,', '))") "ForkJoin%Speedup%Maximum%value ", ForkJoin%Speedup%Maximum%value
295 : write(*,"(10(g0,:,', '))") "ForkJoin_Speedup_Maximum_value ", ForkJoin_Speedup_Maximum_value
296 : write(*,"(10(g0,:,', '))") "ForkJoin%Speedup%Maximum%nproc ", ForkJoin%Speedup%Maximum%nproc
297 : write(*,"(10(g0,:,', '))") "ForkJoin_Speedup_Maximum_nproc ", ForkJoin_Speedup_Maximum_nproc
298 : write(*,"(10(g0,:,', '))") "ForkJoin%Speedup%current ", ForkJoin%Speedup%current
299 : write(*,"(10(g0,:,', '))") "ForkJoin_Speedup_current ", ForkJoin_Speedup_current
300 : write(*,"(10(g0,:,', '))") "ForkJoin%Speedup%count ", ForkJoin%Speedup%count
301 : write(*,"(10(g0,:,', '))") "ForkJoin_Speedup_count ", ForkJoin_Speedup_count
302 : write(*,"(10(g0,:,', '))") "ForkJoin%Speedup%Scaling ", ForkJoin%Speedup%Scaling
303 : write(*,"(10(g0,:,', '))") "ForkJoin_Speedup_Scaling ", ForkJoin_Speedup_Scaling
304 : write(*,"(10(g0,:,', '))") "ForkJoin%Contribution%count ", ForkJoin%Contribution%count
305 : write(*,"(10(g0,:,', '))") "ForkJoin_Contribution_count ", ForkJoin_Contribution_count
306 : write(*,"(10(g0,:,', '))") "ForkJoin%Contribution%Identity ", ForkJoin%Contribution%Identity
307 : write(*,"(10(g0,:,', '))") "ForkJoin_Contribution_Identity ", ForkJoin_Contribution_Identity
308 : write(*,"(10(g0,:,', '))") "ForkJoin%Contribution%Frequency ", ForkJoin%Contribution%Frequency
309 : write(*,"(10(g0,:,', '))") "ForkJoin_Contribution_Frequency ", ForkJoin_Contribution_Frequency
310 : write(*,"(10(g0,:,', '))") "ForkJoin%Contribution%LogFrequency", ForkJoin%Contribution%LogFrequency
311 : write(*,"(10(g0,:,', '))") "ForkJoin_Contribution_LogFrequency", ForkJoin_Contribution_LogFrequency
312 : write(*,"(10(g0,:,', '))") "ForkJoin%UniqueProcess%count ", ForkJoin%UniqueProcess%count
313 : write(*,"(10(g0,:,', '))") "ForkJoin_UniqueProcess_count ", ForkJoin_UniqueProcess_count
314 : write(*,"(10(g0,:,', '))") "ForkJoin%UniqueProcess%Identity ", ForkJoin%UniqueProcess%Identity
315 : write(*,"(10(g0,:,', '))") "ForkJoin_UniqueProcess_Identity ", ForkJoin_UniqueProcess_Identity
316 : write(*,"(10(g0,:,', '))") "ForkJoin%UniqueProcess%Frequency ", ForkJoin%UniqueProcess%Frequency
317 : write(*,"(10(g0,:,', '))") "ForkJoin_UniqueProcess_Frequency ", ForkJoin_UniqueProcess_Frequency
318 : write(*,"(10(g0,:,', '))") "ForkJoin%SuccessProb%current ", ForkJoin%SuccessProb%current
319 : write(*,"(10(g0,:,', '))") "ForkJoin_SuccessProb_current ", ForkJoin_SuccessProb_current
320 : write(*,"(10(g0,:,', '))") "ForkJoin%SuccessProb%effective ", ForkJoin%SuccessProb%effective
321 : write(*,"(10(g0,:,', '))") "ForkJoin_SuccessProb_effective ", ForkJoin_SuccessProb_effective
322 : end if
323 : ! LCOV_EXCL_STOP
324 :
325 1 : end function test_constructForkJoin_2
326 :
327 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
328 :
329 : !> \brief
330 : !> Test the ForkJoin constructor with an invalid input `processCount < 1`.
331 1 : function test_constructForkJoin_3() result(assertion)
332 1 : use Constants_mod, only: IK, RK
333 : implicit none
334 : logical :: assertion
335 1 : type(ForkJoin_type) :: ForkJoin
336 :
337 : ForkJoin = ForkJoin_type( processCount = 0_IK &
338 : , lenProcessID = lenProcessID &
339 : , ProcessID = ProcessID &
340 : , successProb = successProb &
341 : , seqSecTime = epsilon(1._RK) &
342 : , parSecTime = parSecTime &
343 : , comSecTime = comSecTime &
344 1 : )
345 1 : assertion = ForkJoin%Err%occurred
346 :
347 1 : end function test_constructForkJoin_3
348 :
349 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
350 :
351 : !> \brief
352 : !> Test the ForkJoin constructor with an invalid input `successProb = 0`.
353 1 : function test_constructForkJoin_4() result(assertion)
354 1 : use Constants_mod, only: IK, RK
355 : implicit none
356 : logical :: assertion
357 1 : type(ForkJoin_type) :: ForkJoin
358 :
359 : ForkJoin = ForkJoin_type( processCount = processCount &
360 : , lenProcessID = lenProcessID &
361 : , ProcessID = ProcessID &
362 : , successProb = -0.1_RK &
363 : , seqSecTime = epsilon(1._RK) &
364 : , parSecTime = parSecTime &
365 : , comSecTime = comSecTime &
366 1 : )
367 1 : assertion = ForkJoin%Err%occurred
368 :
369 1 : end function test_constructForkJoin_4
370 :
371 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
372 :
373 : !> \brief
374 : !> Test the ForkJoin constructor with an invalid input `successProb = 1`.
375 1 : function test_constructForkJoin_5() result(assertion)
376 1 : use Constants_mod, only: IK, RK
377 : implicit none
378 : logical :: assertion
379 1 : type(ForkJoin_type) :: ForkJoin
380 :
381 : ForkJoin = ForkJoin_type( processCount = processCount &
382 : , lenProcessID = lenProcessID &
383 : , ProcessID = ProcessID &
384 : , successProb = 2._RK &
385 : , seqSecTime = epsilon(1._RK) &
386 : , parSecTime = parSecTime &
387 : , comSecTime = comSecTime &
388 1 : )
389 1 : assertion = ForkJoin%Err%occurred
390 :
391 1 : end function test_constructForkJoin_5
392 :
393 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
394 :
395 : !> \brief
396 : !> Test the ForkJoin constructor with a valid but extreme input for `successProb`.
397 1 : function test_constructForkJoin_6() result(assertion)
398 1 : use Constants_mod, only: IK, RK
399 : implicit none
400 : logical :: assertion
401 1 : type(ForkJoin_type) :: ForkJoin
402 :
403 : ForkJoin = ForkJoin_type( processCount = processCount &
404 : , lenProcessID = lenProcessID &
405 : , ProcessID = ProcessID &
406 : , successProb = 1.00000000001_RK &
407 : , seqSecTime = epsilon(1._RK) &
408 : , parSecTime = parSecTime &
409 : , comSecTime = comSecTime &
410 1 : )
411 1 : assertion = .not. ForkJoin%Err%occurred
412 :
413 1 : end function test_constructForkJoin_6
414 :
415 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
416 :
417 : !> \brief
418 : !> Test the ForkJoin constructor with a valid but extreme input for `successProb`.
419 1 : function test_constructForkJoin_7() result(assertion)
420 1 : use Constants_mod, only: IK, RK
421 : implicit none
422 : logical :: assertion
423 1 : type(ForkJoin_type) :: ForkJoin
424 :
425 : ForkJoin = ForkJoin_type( processCount = processCount &
426 : , lenProcessID = lenProcessID &
427 : , ProcessID = ProcessID &
428 : , successProb = -0.00000000001_RK &
429 : , seqSecTime = epsilon(1._RK) &
430 : , parSecTime = parSecTime &
431 : , comSecTime = comSecTime &
432 1 : )
433 1 : assertion = .not. ForkJoin%Err%occurred
434 :
435 1 : end function test_constructForkJoin_7
436 :
437 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
438 :
439 : end module Test_Parallelism_mod
|