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 [BandSpectrum_mod](@ref bandspectrum_mod).
44 : !> \author Amir Shahmoradi
45 :
46 : module Test_BandSpectrum_mod
47 :
48 : use BandSpectrum_mod
49 : use Test_mod, only: Test_type
50 : !use Constants_mod, only: RK, IK
51 : implicit none
52 :
53 : private
54 : public :: test_BandSpectrum
55 :
56 : type(Test_type) :: Test
57 :
58 : type :: BandSpec_type
59 : real(RK) :: epk, alpha, beta, ebrk, coef
60 : real(RK) :: Limit(2) ! energy window for fluence computation in keV units
61 : real(RK) :: photonFluence ! integral of the Band spectrum in the given energy window
62 : real(RK) :: energyFluence ! integral of the Band spectrum in the given energy window, in units of keV
63 : real(RK) :: tolerance ! acceptable tolerance (accuracy) in the numerical computation of fluence
64 : end type BandSpec_type
65 :
66 : ! involves integration of both upper and lower tails
67 :
68 : type(BandSpec_type), parameter :: BAND_SPEC1 = BandSpec_type( epk = 700._RK &
69 : , alpha = -0.5_RK &
70 : , beta = -2.5_RK &
71 : , ebrk = 9.333333333333334e2_RK &
72 : , coef = 1.178920689527826e5_RK &
73 : , Limit = [1._RK,10000._RK] &
74 : , photonFluence = 37.226409565894123_RK &
75 : , energyFluence = 1.195755906912896e4_RK &
76 : , tolerance = 1.e-7_RK &
77 : )
78 :
79 : ! involves only the lower tail integration
80 :
81 : type(BandSpec_type), parameter :: BAND_SPEC2 = BandSpec_type( epk = 700._RK &
82 : , alpha = -0.5_RK &
83 : , beta = -2.5_RK &
84 : , ebrk = 9.333333333333334e2_RK &
85 : , coef = 1.178920689527826e5_RK &
86 : , Limit = [1._RK,500._RK] &
87 : , photonFluence = 30.806431300618090_RK &
88 : , energyFluence = 4.079656304178462e3_RK &
89 : , tolerance = 1.e-7_RK &
90 : )
91 :
92 : ! involves only the upper tail integration
93 :
94 : type(BandSpec_type), parameter :: BAND_SPEC3 = BandSpec_type( epk = 700._RK &
95 : , alpha = -0.5_RK &
96 : , beta = -2.5_RK &
97 : , ebrk = 9.333333333333334e2_RK &
98 : , coef = 1.178920689527826e5_RK &
99 : , Limit = [1000._RK,10000._RK] &
100 : , photonFluence = 2.406788327100909_RK &
101 : , energyFluence = 5.098307740152641e3_RK &
102 : , tolerance = 1.e-7_RK &
103 : )
104 :
105 : ! involves integration of both upper and lower tails
106 :
107 : type(BandSpec_type), parameter :: BAND_SPEC4 = BandSpec_type( epk = 700._RK &
108 : , alpha = -1.9_RK &
109 : , beta = -3.5_RK &
110 : , ebrk = 1.119999999999999e4_RK &
111 : , coef = 6.079637221508616e5_RK &
112 : , Limit = [1._RK,10000._RK] &
113 : , photonFluence = 1.108858577351433_RK &
114 : , energyFluence = 12.769650780448401_RK &
115 : , tolerance = 1.e-6_RK &
116 : )
117 :
118 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
119 :
120 : contains
121 :
122 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
123 :
124 3 : subroutine test_BandSpectrum()
125 : implicit none
126 3 : Test = Test_type(moduleName=MODULE_NAME)
127 3 : call Test%run(test_getEbreak, "test_getEbreak")
128 3 : call Test%run(test_getBandParam_1, "test_getBandParam_1")
129 3 : call Test%run(test_getPhotonFlux_1, "test_getPhotonFlux_1")
130 3 : call Test%run(test_getPhotonFlux_2, "test_getPhotonFlux_2")
131 3 : call Test%run(test_getPhotonFlux_3, "test_getPhotonFlux_3")
132 3 : call Test%run(test_getPhotonFlux_4, "test_getPhotonFlux_4")
133 3 : call Test%run(test_getPhotonFluence_3, "test_getPhotonFluence_3")
134 3 : call Test%run(test_getPhotonFluence_5, "test_getPhotonFluence_5")
135 3 : call Test%run(test_getPhotonFluence_6, "test_getPhotonFluence_6")
136 3 : call Test%run(test_getPhotonFluence_7, "test_getPhotonFluence_7")
137 3 : call Test%run(test_getPhotonFluence_8, "test_getPhotonFluence_8")
138 3 : call Test%run(test_getEnergyFluence_3, "test_getEnergyFluence_3")
139 3 : call Test%run(test_getEnergyFluence_6, "test_getEnergyFluence_6")
140 3 : call Test%run(test_getEnergyFluence_7, "test_getEnergyFluence_7")
141 3 : call Test%run(test_getEnergyFluence_8, "test_getEnergyFluence_8")
142 3 : call Test%run(test_getPhotonFluxLower_1, "test_getPhotonFluxLower_1")
143 3 : call Test%run(test_getPhotonFluenceFromEnergyFluence_6, "test_getPhotonFluenceFromEnergyFluence_6")
144 3 : call Test%run(test_getPhotonFluenceFromEnergyFluence_7, "test_getPhotonFluenceFromEnergyFluence_7")
145 3 : call Test%run(test_getPhotonFluenceFromEnergyFluence_8, "test_getPhotonFluenceFromEnergyFluence_8")
146 3 : call Test%run(test_getPhotonFluence_1, "test_getPhotonFluence_1") ! The internal function passing as actual argument causes segfault with Gfortran (any version) on Windows subsystem for Linux.
147 3 : call Test%run(test_getPhotonFluence_2, "test_getPhotonFluence_2") ! The internal function passing as actual argument causes segfault with Gfortran (any version) on Windows subsystem for Linux.
148 3 : call Test%run(test_getPhotonFluence_4, "test_getPhotonFluence_4") ! The internal function passing as actual argument causes segfault with Gfortran (any version) on Windows subsystem for Linux.
149 3 : call Test%run(test_getEnergyFluence_1, "test_getEnergyFluence_1") ! The internal function passing as actual argument causes segfault with Gfortran (any version) on Windows subsystem for Linux.
150 3 : call Test%run(test_getEnergyFluence_2, "test_getEnergyFluence_2") ! The internal function passing as actual argument causes segfault with Gfortran (any version) on Windows subsystem for Linux.
151 3 : call Test%run(test_getEnergyFluence_4, "test_getEnergyFluence_4") ! The internal function passing as actual argument causes segfault with Gfortran (any version) on Windows subsystem for Linux.
152 3 : call Test%run(test_getPhotonFluenceFromEnergyFluence_1, "test_getPhotonFluenceFromEnergyFluence_1") ! The internal function passing as actual argument causes segfault with Gfortran (any version) on Windows subsystem for Linux.
153 3 : call Test%run(test_getPhotonFluenceFromEnergyFluence_2, "test_getPhotonFluenceFromEnergyFluence_2") ! The internal function passing as actual argument causes segfault with Gfortran (any version) on Windows subsystem for Linux.
154 3 : call Test%run(test_getPhotonFluenceFromEnergyFluence_3, "test_getPhotonFluenceFromEnergyFluence_3") ! The internal function passing as actual argument causes segfault with Gfortran (any version) on Windows subsystem for Linux.
155 3 : call Test%run(test_getPhotonFluenceFromEnergyFluence_4, "test_getPhotonFluenceFromEnergyFluence_4") ! The internal function passing as actual argument causes segfault with Gfortran (any version) on Windows subsystem for Linux.
156 3 : call Test%run(test_getPhotonFluenceFromEnergyFluence_5, "test_getPhotonFluenceFromEnergyFluence_5") ! The internal function passing as actual argument causes segfault with Gfortran (any version) on Windows subsystem for Linux.
157 3 : call Test%finalize()
158 3 : end subroutine test_BandSpectrum
159 :
160 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
161 :
162 3 : function test_getEbreak() result(assertion)
163 3 : use Constants_mod, only: RK, IK
164 : implicit none
165 : logical :: assertion
166 3 : real(RK) :: ebrk, difference
167 3 : ebrk = getEbreak(BAND_SPEC1%epk,BAND_SPEC1%alpha,BAND_SPEC1%beta)
168 3 : difference = 2._RK * abs(ebrk - BAND_SPEC1%ebrk) / (ebrk + BAND_SPEC1%ebrk)
169 3 : assertion = difference < 1.e-7_RK
170 : ! LCOV_EXCL_START
171 : if (Test%isDebugMode .and. .not. assertion) then
172 : write(Test%outputUnit,"(*(g0,:,', '))")
173 : write(Test%outputUnit,"(*(g0,:,', '))") "Ebreak, Reference Ebreak, difference"
174 : write(Test%outputUnit,"(*(g0,:,', '))") ebrk, BAND_SPEC1%ebrk, difference
175 : write(Test%outputUnit,"(*(g0,:,', '))")
176 : end if
177 : ! LCOV_EXCL_STOP
178 3 : end function test_getEbreak
179 :
180 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
181 :
182 3 : function test_getBandParam_1() result(assertion)
183 :
184 3 : use Constants_mod, only: RK, IK
185 : implicit none
186 :
187 : real(RK), parameter :: alphaPlusTwo_ref = 0.5_RK
188 : real(RK), parameter :: tolerance = 1.e-10_RK
189 : real(RK), parameter :: ebrk_ref = 6.e2_RK
190 : real(RK), parameter :: coef_ref = 220.72766470286541_RK
191 : real(RK), parameter :: alpha = -1.5_RK
192 : real(RK), parameter :: beta = -2.5_RK
193 : real(RK), parameter :: epk = 3.e2_RK
194 :
195 : logical :: assertion
196 3 : real(RK) :: difference
197 3 : real(RK) :: alphaPlusTwo
198 3 : real(RK) :: ebrk
199 3 : real(RK) :: coef
200 :
201 3 : call getBandParam(epk,alpha,beta,ebrk,coef,alphaPlusTwo)
202 :
203 3 : difference = abs( (ebrk - ebrk_ref) / ebrk_ref )
204 3 : assertion = difference < tolerance
205 :
206 3 : if (Test%isDebugMode .and. .not. assertion) then
207 : ! LCOV_EXCL_START
208 : write(Test%outputUnit,"(*(g0,:,', '))")
209 : write(Test%outputUnit,"(*(g0,:,', '))") "ebrk_ref ", ebrk_ref
210 : write(Test%outputUnit,"(*(g0,:,', '))") "ebrk ", ebrk
211 : write(Test%outputUnit,"(*(g0,:,', '))") "difference ", difference
212 : write(Test%outputUnit,"(*(g0,:,', '))")
213 : end if
214 : ! LCOV_EXCL_STOP
215 :
216 3 : difference = abs( (coef - coef_ref) / coef_ref )
217 3 : assertion = difference < tolerance
218 :
219 3 : if (Test%isDebugMode .and. .not. assertion) then
220 : ! LCOV_EXCL_START
221 : write(Test%outputUnit,"(*(g0,:,', '))")
222 : write(Test%outputUnit,"(*(g0,:,', '))") "coef_ref ", coef_ref
223 : write(Test%outputUnit,"(*(g0,:,', '))") "coef ", coef
224 : write(Test%outputUnit,"(*(g0,:,', '))") "difference ", difference
225 : write(Test%outputUnit,"(*(g0,:,', '))")
226 : end if
227 : ! LCOV_EXCL_STOP
228 :
229 3 : difference = abs( (alphaPlusTwo - alphaPlusTwo_ref) / alphaPlusTwo_ref )
230 3 : assertion = difference < tolerance
231 :
232 3 : if (Test%isDebugMode .and. .not. assertion) then
233 : ! LCOV_EXCL_START
234 : write(Test%outputUnit,"(*(g0,:,', '))")
235 : write(Test%outputUnit,"(*(g0,:,', '))") "alphaPlusTwo_ref ", alphaPlusTwo_ref
236 : write(Test%outputUnit,"(*(g0,:,', '))") "alphaPlusTwo ", alphaPlusTwo
237 : write(Test%outputUnit,"(*(g0,:,', '))") "difference ", difference
238 : write(Test%outputUnit,"(*(g0,:,', '))")
239 : end if
240 : ! LCOV_EXCL_STOP
241 :
242 3 : end function test_getBandParam_1
243 :
244 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
245 :
246 3 : function test_getPhotonFluxLower_1() result(assertion)
247 :
248 3 : use Constants_mod, only: RK, IK
249 : implicit none
250 :
251 : real(RK), parameter :: photonFluxLower_ref = 0.59727709940405714E-5_RK
252 : real(RK), parameter :: alphaPlusTwo = 0.5_RK
253 : real(RK), parameter :: tolerance = 1.e-10_RK
254 : real(RK), parameter :: energy = 1.e3_RK
255 : real(RK), parameter :: alpha = -1.5_RK
256 : real(RK), parameter :: beta = -2.5_RK
257 : real(RK), parameter :: coef = 220.72766470286541_RK
258 : real(RK), parameter :: ebrk = 6.e2_RK
259 : real(RK), parameter :: epk = 3.e2_RK
260 : real(RK), parameter :: alphaPlusTwoOverEpk = alphaPlusTwo / epk
261 :
262 : logical :: assertion
263 3 : real(RK) :: difference
264 3 : real(RK) :: photonFluxLower
265 :
266 3 : photonFluxLower = getPhotonFluxLower(energy,alpha,alphaPlusTwoOverEpk)
267 3 : assertion = photonFluxLower > 0._RK
268 :
269 3 : difference = abs( (photonFluxLower - photonFluxLower_ref) / photonFluxLower_ref )
270 3 : assertion = assertion .and. difference < tolerance
271 :
272 3 : if (Test%isDebugMode .and. .not. assertion) then
273 : ! LCOV_EXCL_START
274 : write(Test%outputUnit,"(*(g0,:,', '))")
275 : write(Test%outputUnit,"(*(g0,:,', '))") "photonFluxLower_ref", photonFluxLower_ref
276 : write(Test%outputUnit,"(*(g0,:,', '))") "photonFluxLower ", photonFluxLower
277 : write(Test%outputUnit,"(*(g0,:,', '))") "difference ", difference
278 : write(Test%outputUnit,"(*(g0,:,', '))")
279 : end if
280 : ! LCOV_EXCL_STOP
281 :
282 3 : end function test_getPhotonFluxLower_1
283 :
284 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
285 :
286 3 : function test_getPhotonFlux_1() result(assertion)
287 :
288 3 : use Constants_mod, only: RK, IK
289 : implicit none
290 :
291 : real(RK), parameter :: photonFlux_ref = 0.69800216307100779E-5_RK
292 : real(RK), parameter :: alphaPlusTwo = 0.5_RK
293 : real(RK), parameter :: tolerance = 1.e-10_RK
294 : real(RK), parameter :: energy = 1.e3_RK
295 : real(RK), parameter :: alpha = -1.5_RK
296 : real(RK), parameter :: beta = -2.5_RK
297 : real(RK), parameter :: coef = 220.72766470286541_RK
298 : real(RK), parameter :: ebrk = 6.e2_RK
299 : real(RK), parameter :: epk = 3.e2_RK
300 :
301 : logical :: assertion
302 3 : real(RK) :: difference
303 3 : real(RK) :: photonFlux
304 :
305 3 : photonFlux = getPhotonFlux(energy,epk,alpha,beta,ebrk,coef,alphaPlusTwo)
306 3 : assertion = photonFlux > 0._RK
307 :
308 3 : difference = abs( (photonFlux - photonFlux_ref) / photonFlux_ref )
309 3 : assertion = assertion .and. difference < tolerance
310 :
311 3 : if (Test%isDebugMode .and. .not. assertion) then
312 : ! LCOV_EXCL_START
313 : write(Test%outputUnit,"(*(g0,:,', '))")
314 : write(Test%outputUnit,"(*(g0,:,', '))") "photonFlux_ref ", photonFlux_ref
315 : write(Test%outputUnit,"(*(g0,:,', '))") "photonFlux ", photonFlux
316 : write(Test%outputUnit,"(*(g0,:,', '))") "difference ", difference
317 : write(Test%outputUnit,"(*(g0,:,', '))")
318 : end if
319 : ! LCOV_EXCL_STOP
320 :
321 3 : end function test_getPhotonFlux_1
322 :
323 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
324 :
325 3 : function test_getPhotonFlux_2() result(assertion)
326 :
327 3 : use Constants_mod, only: RK, IK
328 : implicit none
329 :
330 : real(RK), parameter :: photonFlux_ref = 0.31100098078334186E-1_RK
331 : real(RK), parameter :: alphaPlusTwo = 0.5_RK
332 : real(RK), parameter :: tolerance = 1.e-10_RK
333 : real(RK), parameter :: energy = 1.e1_RK
334 : real(RK), parameter :: alpha = -1.5_RK
335 : real(RK), parameter :: beta = -2.5_RK
336 : real(RK), parameter :: coef = 220.72766470286541_RK
337 : real(RK), parameter :: ebrk = 6.e2_RK
338 : real(RK), parameter :: epk = 3.e2_RK
339 :
340 : logical :: assertion
341 3 : real(RK) :: difference
342 3 : real(RK) :: photonFlux
343 :
344 3 : photonFlux = getPhotonFlux(energy,epk,alpha,beta,ebrk,coef,alphaPlusTwo)
345 3 : assertion = photonFlux > 0._RK
346 :
347 3 : difference = abs( (photonFlux - photonFlux_ref) / photonFlux_ref )
348 3 : assertion = assertion .and. difference < tolerance
349 :
350 3 : if (Test%isDebugMode .and. .not. assertion) then
351 : ! LCOV_EXCL_START
352 : write(Test%outputUnit,"(*(g0,:,', '))")
353 : write(Test%outputUnit,"(*(g0,:,', '))") "photonFlux_ref ", photonFlux_ref
354 : write(Test%outputUnit,"(*(g0,:,', '))") "photonFlux ", photonFlux
355 : write(Test%outputUnit,"(*(g0,:,', '))") "difference ", difference
356 : write(Test%outputUnit,"(*(g0,:,', '))")
357 : end if
358 : ! LCOV_EXCL_STOP
359 :
360 3 : end function test_getPhotonFlux_2
361 :
362 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
363 :
364 : ! alpha < -2
365 3 : function test_getPhotonFlux_3() result(assertion)
366 :
367 3 : use Constants_mod, only: RK, IK
368 : implicit none
369 :
370 : real(RK), parameter :: alphaPlusTwo = 0.5_RK
371 : real(RK), parameter :: energy = 1.e1_RK
372 : real(RK), parameter :: alpha = -3.5_RK
373 : real(RK), parameter :: beta = -2.5_RK
374 : real(RK), parameter :: coef = 220.72766470286541_RK
375 : real(RK), parameter :: ebrk = 6.e2_RK
376 : real(RK), parameter :: epk = 3.e2_RK
377 :
378 : logical :: assertion
379 3 : real(RK) :: photonFlux
380 :
381 3 : photonFlux = getPhotonFlux(energy,epk,alpha,beta,ebrk,coef,alphaPlusTwo)
382 3 : assertion = photonFlux < 0._RK
383 :
384 3 : if (Test%isDebugMode .and. .not. assertion) then
385 : ! LCOV_EXCL_START
386 : write(Test%outputUnit,"(*(g0,:,', '))")
387 : write(Test%outputUnit,"(*(g0,:,', '))") "photonFlux ", photonFlux
388 : write(Test%outputUnit,"(*(g0,:,', '))")
389 : end if
390 : ! LCOV_EXCL_STOP
391 :
392 3 : end function test_getPhotonFlux_3
393 :
394 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
395 :
396 : ! alpha < beta
397 3 : function test_getPhotonFlux_4() result(assertion)
398 :
399 3 : use Constants_mod, only: RK, IK
400 : implicit none
401 :
402 : real(RK), parameter :: alphaPlusTwo = 0.5_RK
403 : real(RK), parameter :: energy = 1.e1_RK
404 : real(RK), parameter :: alpha = -1.5_RK
405 : real(RK), parameter :: beta = -0.5_RK
406 : real(RK), parameter :: coef = 220.72766470286541_RK
407 : real(RK), parameter :: ebrk = 6.e2_RK
408 : real(RK), parameter :: epk = 3.e2_RK
409 :
410 : logical :: assertion
411 3 : real(RK) :: photonFlux
412 :
413 3 : photonFlux = getPhotonFlux(energy,epk,alpha,beta,ebrk,coef,alphaPlusTwo)
414 3 : assertion = photonFlux < 0._RK
415 :
416 3 : if (Test%isDebugMode .and. .not. assertion) then
417 : ! LCOV_EXCL_START
418 : write(Test%outputUnit,"(*(g0,:,', '))")
419 : write(Test%outputUnit,"(*(g0,:,', '))") "photonFlux ", photonFlux
420 : write(Test%outputUnit,"(*(g0,:,', '))")
421 : end if
422 : ! LCOV_EXCL_STOP
423 :
424 3 : end function test_getPhotonFlux_4
425 :
426 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
427 :
428 : !> \brief
429 : !> Test the integration of both upper and lower tails.
430 3 : function test_getPhotonFluence_3() result(assertion)
431 3 : use Constants_mod, only: RK, IK
432 : use Err_mod, only: Err_type
433 : implicit none
434 : logical :: assertion
435 3 : real(RK) :: photonFluence, difference
436 3 : type(Err_type) :: Err
437 : call getPhotonFluence ( lowerLim = BAND_SPEC3%Limit(1) &
438 : , upperLim = BAND_SPEC3%Limit(2) &
439 : , epk = BAND_SPEC3%epk &
440 : , alpha = BAND_SPEC3%alpha &
441 : , beta = BAND_SPEC3%beta &
442 : , tolerance = BAND_SPEC3%tolerance &
443 : , photonFluence = photonFluence &
444 : , Err = Err &
445 3 : )
446 3 : difference = 2._RK * abs( photonFluence - BAND_SPEC3%photonFluence ) / ( photonFluence + BAND_SPEC3%photonFluence )
447 3 : assertion = difference < BAND_SPEC3%tolerance
448 3 : if (Test%isDebugMode .and. .not. assertion) then
449 : ! LCOV_EXCL_START
450 : write(Test%outputUnit,"(*(g0,:,', '))")
451 : write(Test%outputUnit,"(*(g0,:,', '))") "photon fluence, Reference photon fluence, difference"
452 : write(Test%outputUnit,"(*(g0,:,', '))") photonFluence, BAND_SPEC3%photonFluence, difference
453 : write(Test%outputUnit,"(*(g0,:,', '))")
454 : end if
455 : ! LCOV_EXCL_STOP
456 3 : end function test_getPhotonFluence_3
457 :
458 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
459 :
460 : !> \brief
461 : !> Test the integration of when lower limit is larger than upper limit.
462 3 : function test_getPhotonFluence_5() result(assertion)
463 3 : use Constants_mod, only: RK, IK
464 : use Err_mod, only: Err_type
465 : implicit none
466 : logical :: assertion
467 : real(RK) :: tolerance = 1.e-10_RK
468 3 : real(RK) :: photonFluence, difference
469 3 : type(Err_type) :: Err
470 : call getPhotonFluence ( lowerLim = BAND_SPEC3%Limit(2) &
471 : , upperLim = BAND_SPEC3%Limit(1) &
472 : , epk = BAND_SPEC3%epk &
473 : , alpha = BAND_SPEC3%alpha &
474 : , beta = BAND_SPEC3%beta &
475 : , tolerance = BAND_SPEC3%tolerance &
476 : , photonFluence = photonFluence &
477 : , Err = Err &
478 3 : )
479 3 : difference = abs( photonFluence - 0._RK )
480 3 : assertion = difference < tolerance
481 3 : if (Test%isDebugMode .and. .not. assertion) then
482 : ! LCOV_EXCL_START
483 : write(Test%outputUnit,"(*(g0,:,', '))")
484 : write(Test%outputUnit,"(*(g0,:,', '))") "photon fluence, Reference photon fluence, difference"
485 : write(Test%outputUnit,"(*(g0,:,', '))") photonFluence, BAND_SPEC3%photonFluence, difference
486 : write(Test%outputUnit,"(*(g0,:,', '))")
487 : end if
488 : ! LCOV_EXCL_STOP
489 3 : end function test_getPhotonFluence_5
490 :
491 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
492 :
493 : !> \brief
494 : !> Test the integration of when lower limit is larger than upper limit.
495 3 : function test_getPhotonFluence_6() result(assertion)
496 3 : use Constants_mod, only: RK, IK
497 : use Err_mod, only: Err_type
498 : implicit none
499 : logical :: assertion
500 3 : real(RK) :: photonFluence
501 3 : type(Err_type) :: Err
502 : call getPhotonFluence ( lowerLim = BAND_SPEC3%Limit(2) &
503 : , upperLim = BAND_SPEC3%Limit(1) &
504 : , epk = BAND_SPEC3%epk &
505 : , alpha = BAND_SPEC3%alpha &
506 : , beta = BAND_SPEC3%beta &
507 : , tolerance = BAND_SPEC3%tolerance &
508 : , photonFluence = photonFluence &
509 : , Err = Err &
510 3 : )
511 3 : assertion = abs(photonFluence - 0._RK) < 1.e-12_RK
512 3 : if (Test%isDebugMode .and. .not. assertion) then
513 : ! LCOV_EXCL_START
514 : write(Test%outputUnit,"(*(g0,:,', '))")
515 : write(Test%outputUnit,"(*(g0,:,', '))") "photon fluence", photonFluence
516 : write(Test%outputUnit,"(*(g0,:,', '))")
517 : end if
518 : ! LCOV_EXCL_STOP
519 3 : end function test_getPhotonFluence_6
520 :
521 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
522 :
523 : !> \brief
524 : !> Test with conflicting alpha photon index.
525 3 : function test_getPhotonFluence_7() result(assertion)
526 3 : use Constants_mod, only: RK, IK
527 : use Err_mod, only: Err_type
528 : implicit none
529 : logical :: assertion
530 3 : real(RK) :: photonFluence
531 3 : type(Err_type) :: Err
532 : call getPhotonFluence ( lowerLim = BAND_SPEC3%Limit(1) &
533 : , upperLim = BAND_SPEC3%Limit(2) &
534 : , epk = BAND_SPEC3%epk &
535 : , alpha = -1.e1_RK &
536 : , beta = BAND_SPEC3%beta &
537 : , tolerance = BAND_SPEC3%tolerance &
538 : , photonFluence = photonFluence &
539 : , Err = Err &
540 3 : )
541 3 : assertion = Err%occurred .and. photonFluence < 0._RK
542 3 : if (Test%isDebugMode .and. .not. assertion) then
543 : ! LCOV_EXCL_START
544 : write(Test%outputUnit,"(*(g0,:,', '))")
545 : write(Test%outputUnit,"(*(g0,:,', '))") "photon fluence", photonFluence
546 : write(Test%outputUnit,"(*(g0,:,', '))")
547 : end if
548 : ! LCOV_EXCL_STOP
549 3 : end function test_getPhotonFluence_7
550 :
551 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
552 :
553 : !> \brief
554 : !> Test with conflicting alpha < beta photon indices.
555 3 : function test_getPhotonFluence_8() result(assertion)
556 3 : use Constants_mod, only: RK, IK
557 : use Err_mod, only: Err_type
558 : implicit none
559 : logical :: assertion
560 3 : real(RK) :: photonFluence, difference
561 3 : type(Err_type) :: Err
562 : call getPhotonFluence ( lowerLim = BAND_SPEC3%Limit(1) &
563 : , upperLim = BAND_SPEC3%Limit(2) &
564 : , epk = BAND_SPEC3%epk &
565 : , alpha = BAND_SPEC3%beta &
566 : , beta = BAND_SPEC3%alpha &
567 : , tolerance = BAND_SPEC3%tolerance &
568 : , photonFluence = photonFluence &
569 : , Err = Err &
570 3 : )
571 3 : assertion = Err%occurred .and. photonFluence < 0._RK
572 3 : if (Test%isDebugMode .and. .not. assertion) then
573 : ! LCOV_EXCL_START
574 : write(Test%outputUnit,"(*(g0,:,', '))")
575 : write(Test%outputUnit,"(*(g0,:,', '))") "photon fluence, Reference photon fluence, difference"
576 : write(Test%outputUnit,"(*(g0,:,', '))") photonFluence, BAND_SPEC3%photonFluence, difference
577 : write(Test%outputUnit,"(*(g0,:,', '))")
578 : end if
579 : ! LCOV_EXCL_STOP
580 3 : end function test_getPhotonFluence_8
581 :
582 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
583 :
584 : !> \brief
585 : !> Test the integration of both upper and lower tails.
586 3 : function test_getEnergyFluence_3() result(assertion)
587 3 : use Constants_mod, only: RK, IK
588 : use Err_mod, only: Err_type
589 : implicit none
590 : logical :: assertion
591 3 : real(RK) :: energyFluence, difference
592 3 : type(Err_type) :: Err
593 : call getEnergyFluence ( lowerLim = BAND_SPEC3%Limit(1) &
594 : , upperLim = BAND_SPEC3%Limit(2) &
595 : , epk = BAND_SPEC3%epk &
596 : , alpha = BAND_SPEC3%alpha &
597 : , beta = BAND_SPEC3%beta &
598 : , tolerance = BAND_SPEC3%tolerance &
599 : , energyFluence = energyFluence &
600 : , Err = Err &
601 3 : )
602 3 : difference = 2._RK * abs( energyFluence - BAND_SPEC3%energyFluence ) / ( energyFluence + BAND_SPEC3%energyFluence )
603 3 : assertion = difference < BAND_SPEC3%tolerance
604 3 : if (Test%isDebugMode .and. .not. assertion) then
605 : ! LCOV_EXCL_START
606 : write(Test%outputUnit,"(*(g0,:,', '))")
607 : write(Test%outputUnit,"(*(g0,:,', '))") "photon fluence, Reference photon fluence, difference"
608 : write(Test%outputUnit,"(*(g0,:,', '))") energyFluence, BAND_SPEC3%energyFluence, difference
609 : write(Test%outputUnit,"(*(g0,:,', '))")
610 : end if
611 : ! LCOV_EXCL_STOP
612 3 : end function test_getEnergyFluence_3
613 :
614 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
615 :
616 : !> \brief
617 : !> Test the integration of when lower limit is larger than upper limit.
618 3 : function test_getEnergyFluence_6() result(assertion)
619 3 : use Constants_mod, only: RK, IK
620 : use Err_mod, only: Err_type
621 : implicit none
622 : logical :: assertion
623 3 : real(RK) :: EnergyFluence
624 3 : type(Err_type) :: Err
625 : call getEnergyFluence ( lowerLim = BAND_SPEC3%Limit(2) &
626 : , upperLim = BAND_SPEC3%Limit(1) &
627 : , epk = BAND_SPEC3%epk &
628 : , alpha = BAND_SPEC3%alpha &
629 : , beta = BAND_SPEC3%beta &
630 : , tolerance = BAND_SPEC3%tolerance &
631 : , EnergyFluence = EnergyFluence &
632 : , Err = Err &
633 3 : )
634 3 : assertion = abs(EnergyFluence - 0._RK) < 1.e-12_RK
635 3 : if (Test%isDebugMode .and. .not. assertion) then
636 : ! LCOV_EXCL_START
637 : write(Test%outputUnit,"(*(g0,:,', '))")
638 : write(Test%outputUnit,"(*(g0,:,', '))") "EnergyFluence", EnergyFluence
639 : write(Test%outputUnit,"(*(g0,:,', '))")
640 : end if
641 : ! LCOV_EXCL_STOP
642 3 : end function test_getEnergyFluence_6
643 :
644 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
645 :
646 : !> \brief
647 : !> Test with conflicting alpha photon index.
648 3 : function test_getEnergyFluence_7() result(assertion)
649 3 : use Constants_mod, only: RK, IK
650 : use Err_mod, only: Err_type
651 : implicit none
652 : logical :: assertion
653 3 : real(RK) :: EnergyFluence
654 3 : type(Err_type) :: Err
655 : call getEnergyFluence ( lowerLim = BAND_SPEC3%Limit(1) &
656 : , upperLim = BAND_SPEC3%Limit(2) &
657 : , epk = BAND_SPEC3%epk &
658 : , alpha = -1.e1_RK &
659 : , beta = BAND_SPEC3%beta &
660 : , tolerance = BAND_SPEC3%tolerance &
661 : , EnergyFluence = EnergyFluence &
662 : , Err = Err &
663 3 : )
664 3 : assertion = Err%occurred .and. EnergyFluence < 0._RK
665 3 : if (Test%isDebugMode .and. .not. assertion) then
666 : ! LCOV_EXCL_START
667 : write(Test%outputUnit,"(*(g0,:,', '))")
668 : write(Test%outputUnit,"(*(g0,:,', '))") "EnergyFluence", EnergyFluence
669 : write(Test%outputUnit,"(*(g0,:,', '))")
670 : end if
671 : ! LCOV_EXCL_STOP
672 3 : end function test_getEnergyFluence_7
673 :
674 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
675 :
676 : !> \brief
677 : !> Test with conflicting alpha < beta photon indices.
678 3 : function test_getEnergyFluence_8() result(assertion)
679 3 : use Constants_mod, only: RK, IK
680 : use Err_mod, only: Err_type
681 : implicit none
682 : logical :: assertion
683 3 : real(RK) :: EnergyFluence
684 3 : type(Err_type) :: Err
685 : call getEnergyFluence ( lowerLim = BAND_SPEC3%Limit(1) &
686 : , upperLim = BAND_SPEC3%Limit(2) &
687 : , epk = BAND_SPEC3%epk &
688 : , alpha = BAND_SPEC3%beta &
689 : , beta = BAND_SPEC3%alpha &
690 : , tolerance = BAND_SPEC3%tolerance &
691 : , EnergyFluence = EnergyFluence &
692 : , Err = Err &
693 3 : )
694 3 : assertion = Err%occurred .and. EnergyFluence < 0._RK
695 3 : if (Test%isDebugMode .and. .not. assertion) then
696 : ! LCOV_EXCL_START
697 : write(Test%outputUnit,"(*(g0,:,', '))")
698 : write(Test%outputUnit,"(*(g0,:,', '))") "EnergyFluence", EnergyFluence
699 : write(Test%outputUnit,"(*(g0,:,', '))")
700 : end if
701 : ! LCOV_EXCL_STOP
702 3 : end function test_getEnergyFluence_8
703 :
704 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
705 :
706 : !> \brief
707 : !> Test the integration of when lower limit is larger than upper limit.
708 3 : function test_getPhotonFluenceFromEnergyFluence_6() result(assertion)
709 3 : use Constants_mod, only: RK, IK
710 : use Err_mod, only: Err_type
711 : implicit none
712 : logical :: assertion
713 3 : real(RK) :: photonFluence
714 3 : type(Err_type) :: Err
715 : call getPhotonFluenceFromEnergyFluence ( energyFluence = BAND_SPEC2%energyFluence &
716 : , lowerLim = BAND_SPEC2%Limit(2) &
717 : , upperLim = BAND_SPEC2%Limit(1) &
718 : , epk = BAND_SPEC2%epk &
719 : , alpha = BAND_SPEC2%alpha &
720 : , beta = BAND_SPEC2%alpha &
721 : , tolerance = BAND_SPEC2%tolerance &
722 : , photonFluence = photonFluence &
723 : , Err = Err &
724 3 : )
725 3 : assertion = abs(photonFluence - 0._RK) < 1.e-12_RK
726 3 : if (Test%isDebugMode .and. .not. assertion) then
727 : ! LCOV_EXCL_START
728 : write(Test%outputUnit,"(*(g0,:,', '))")
729 : write(Test%outputUnit,"(*(g0,:,', '))") "photonFluence", photonFluence
730 : write(Test%outputUnit,"(*(g0,:,', '))")
731 : end if
732 : ! LCOV_EXCL_STOP
733 3 : end function test_getPhotonFluenceFromEnergyFluence_6
734 :
735 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
736 :
737 : !> \brief
738 : !> Test with conflicting alpha photon index alpha < -2.
739 3 : function test_getPhotonFluenceFromEnergyFluence_7() result(assertion)
740 3 : use Constants_mod, only: RK, IK
741 : use Err_mod, only: Err_type
742 : implicit none
743 : logical :: assertion
744 3 : real(RK) :: photonFluence
745 3 : type(Err_type) :: Err
746 : call getPhotonFluenceFromEnergyFluence ( energyFluence = BAND_SPEC2%energyFluence &
747 : , lowerLim = BAND_SPEC2%Limit(1) &
748 : , upperLim = BAND_SPEC2%Limit(2) &
749 : , epk = BAND_SPEC2%epk &
750 : , alpha = -1.e1_RK &
751 : , beta = BAND_SPEC2%beta &
752 : , tolerance = BAND_SPEC2%tolerance &
753 : , photonFluence = photonFluence &
754 : , Err = Err &
755 3 : )
756 3 : assertion = Err%occurred .and. photonFluence < 0._RK
757 3 : if (Test%isDebugMode .and. .not. assertion) then
758 : ! LCOV_EXCL_START
759 : write(Test%outputUnit,"(*(g0,:,', '))")
760 : write(Test%outputUnit,"(*(g0,:,', '))") "photonFluence", photonFluence
761 : write(Test%outputUnit,"(*(g0,:,', '))")
762 : end if
763 : ! LCOV_EXCL_STOP
764 3 : end function test_getPhotonFluenceFromEnergyFluence_7
765 :
766 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
767 :
768 : !> \brief
769 : !> Test with conflicting alpha < beta photon indices.
770 3 : function test_getPhotonFluenceFromEnergyFluence_8() result(assertion)
771 3 : use Constants_mod, only: RK, IK
772 : use Err_mod, only: Err_type
773 : implicit none
774 : logical :: assertion
775 3 : real(RK) :: photonFluence
776 3 : type(Err_type) :: Err
777 : call getPhotonFluenceFromEnergyFluence ( energyFluence = BAND_SPEC2%energyFluence &
778 : , lowerLim = BAND_SPEC2%Limit(1) &
779 : , upperLim = BAND_SPEC2%Limit(2) &
780 : , epk = BAND_SPEC2%epk &
781 : , alpha = BAND_SPEC2%beta &
782 : , beta = BAND_SPEC2%alpha &
783 : , tolerance = BAND_SPEC2%tolerance &
784 : , photonFluence = photonFluence &
785 : , Err = Err &
786 3 : )
787 3 : assertion = Err%occurred .and. photonFluence < 0._RK
788 3 : if (Test%isDebugMode .and. .not. assertion) then
789 : ! LCOV_EXCL_START
790 : write(Test%outputUnit,"(*(g0,:,', '))")
791 : write(Test%outputUnit,"(*(g0,:,', '))") "photonFluence", photonFluence
792 : write(Test%outputUnit,"(*(g0,:,', '))")
793 : end if
794 : ! LCOV_EXCL_STOP
795 3 : end function test_getPhotonFluenceFromEnergyFluence_8
796 :
797 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
798 :
799 : !#if !defined OS_IS_WSL || !defined CODECOV_ENABLED || defined DLL_ENABLED
800 :
801 : !> \brief
802 : !> Test the integration of both the upper and lower tails.
803 3 : function test_getPhotonFluence_1() result(assertion)
804 3 : use Constants_mod, only: RK, IK
805 : use Err_mod, only: Err_type
806 : implicit none
807 : logical :: assertion
808 3 : real(RK) :: photonFluence, difference
809 3 : type(Err_type) :: Err
810 : call getPhotonFluence ( lowerLim = BAND_SPEC1%Limit(1) &
811 : , upperLim = BAND_SPEC1%Limit(2) &
812 : , epk = BAND_SPEC1%epk &
813 : , alpha = BAND_SPEC1%alpha &
814 : , beta = BAND_SPEC1%beta &
815 : , tolerance = BAND_SPEC1%tolerance &
816 : , photonFluence = photonFluence &
817 : , Err = Err &
818 3 : )
819 3 : difference = 2._RK * abs( photonFluence - BAND_SPEC1%photonFluence ) / ( photonFluence + BAND_SPEC1%photonFluence )
820 3 : assertion = difference < BAND_SPEC1%tolerance
821 3 : if (Test%isDebugMode .and. .not. assertion) then
822 : ! LCOV_EXCL_START
823 : write(Test%outputUnit,"(*(g0,:,', '))")
824 : write(Test%outputUnit,"(*(g0,:,', '))") "photon fluence, Reference photon fluence, difference"
825 : write(Test%outputUnit,"(*(g0,:,', '))") photonFluence, BAND_SPEC1%photonFluence, difference
826 : write(Test%outputUnit,"(*(g0,:,', '))")
827 : end if
828 : ! LCOV_EXCL_STOP
829 3 : end function test_getPhotonFluence_1
830 :
831 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
832 :
833 : !> \brief
834 : !> Test the integration of only the upper tail.
835 3 : function test_getPhotonFluence_2() result(assertion)
836 3 : use Constants_mod, only: RK, IK
837 : use Err_mod, only: Err_type
838 : implicit none
839 : logical :: assertion
840 3 : real(RK) :: photonFluence, difference
841 3 : type(Err_type) :: Err
842 : call getPhotonFluence ( lowerLim = BAND_SPEC2%Limit(1) &
843 : , upperLim = BAND_SPEC2%Limit(2) &
844 : , epk = BAND_SPEC2%epk &
845 : , alpha = BAND_SPEC2%alpha &
846 : , beta = BAND_SPEC2%beta &
847 : , tolerance = BAND_SPEC2%tolerance &
848 : , photonFluence = photonFluence &
849 : , Err = Err &
850 3 : )
851 3 : difference = 2._RK * abs( photonFluence - BAND_SPEC2%photonFluence ) / ( photonFluence + BAND_SPEC2%photonFluence )
852 3 : assertion = difference < BAND_SPEC2%tolerance
853 3 : if (Test%isDebugMode .and. .not. assertion) then
854 : ! LCOV_EXCL_START
855 : write(Test%outputUnit,"(*(g0,:,', '))")
856 : write(Test%outputUnit,"(*(g0,:,', '))") "photon fluence, Reference photon fluence, difference"
857 : write(Test%outputUnit,"(*(g0,:,', '))") photonFluence, BAND_SPEC2%photonFluence, difference
858 : write(Test%outputUnit,"(*(g0,:,', '))")
859 : end if
860 : ! LCOV_EXCL_STOP
861 3 : end function test_getPhotonFluence_2
862 :
863 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
864 :
865 : !> \brief
866 : !> Test the integration of both upper and upper tails with steep slopes.
867 3 : function test_getPhotonFluence_4() result(assertion)
868 3 : use Constants_mod, only: RK, IK
869 : use Err_mod, only: Err_type
870 : implicit none
871 : logical :: assertion
872 3 : real(RK) :: photonFluence, difference
873 3 : type(Err_type) :: Err
874 :
875 : call getPhotonFluence ( lowerLim = BAND_SPEC4%Limit(1) &
876 : , upperLim = BAND_SPEC4%Limit(2) &
877 : , epk = BAND_SPEC4%epk &
878 : , alpha = BAND_SPEC4%alpha &
879 : , beta = BAND_SPEC4%beta &
880 : , tolerance = BAND_SPEC4%tolerance &
881 : , photonFluence = photonFluence &
882 : , Err = Err &
883 3 : )
884 3 : difference = 2._RK * abs( photonFluence - BAND_SPEC4%photonFluence ) / ( photonFluence + BAND_SPEC4%photonFluence )
885 3 : assertion = difference < BAND_SPEC4%tolerance
886 3 : if (Test%isDebugMode .and. .not. assertion) then
887 : ! LCOV_EXCL_START
888 : write(Test%outputUnit,"(*(g0,:,', '))")
889 : write(Test%outputUnit,"(*(g0,:,', '))") "photon fluence, Reference photon fluence, difference"
890 : write(Test%outputUnit,"(*(g0,:,', '))") photonFluence, BAND_SPEC4%photonFluence, difference
891 : write(Test%outputUnit,"(*(g0,:,', '))")
892 : end if
893 : ! LCOV_EXCL_STOP
894 3 : end function test_getPhotonFluence_4
895 :
896 : !> \brief
897 : !> Test the integration of both upper and upper tails.
898 3 : function test_getEnergyFluence_1() result(assertion)
899 3 : use Constants_mod, only: RK, IK
900 : use Err_mod, only: Err_type
901 : implicit none
902 : logical :: assertion
903 3 : real(RK) :: energyFluence, difference
904 3 : type(Err_type) :: Err
905 : call getEnergyFluence ( lowerLim = BAND_SPEC1%Limit(1) &
906 : , upperLim = BAND_SPEC1%Limit(2) &
907 : , epk = BAND_SPEC1%epk &
908 : , alpha = BAND_SPEC1%alpha &
909 : , beta = BAND_SPEC1%beta &
910 : , tolerance = BAND_SPEC1%tolerance &
911 : , energyFluence = energyFluence &
912 : , Err = Err &
913 3 : )
914 3 : difference = 2._RK * abs( energyFluence - BAND_SPEC1%energyFluence ) / ( energyFluence + BAND_SPEC1%energyFluence )
915 3 : assertion = difference < BAND_SPEC1%tolerance
916 3 : if (Test%isDebugMode .and. .not. assertion) then
917 : ! LCOV_EXCL_START
918 : write(Test%outputUnit,"(*(g0,:,', '))")
919 : write(Test%outputUnit,"(*(g0,:,', '))") "photon fluence, Reference photon fluence, difference"
920 : write(Test%outputUnit,"(*(g0,:,', '))") energyFluence, BAND_SPEC1%energyFluence, difference
921 : write(Test%outputUnit,"(*(g0,:,', '))")
922 : end if
923 : ! LCOV_EXCL_STOP
924 3 : end function test_getEnergyFluence_1
925 :
926 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
927 :
928 : !> \brief
929 : !> Test the integration of only the upper tail.
930 3 : function test_getEnergyFluence_2() result(assertion)
931 3 : use Constants_mod, only: RK, IK
932 : use Err_mod, only: Err_type
933 : implicit none
934 : logical :: assertion
935 3 : real(RK) :: energyFluence, difference
936 3 : type(Err_type) :: Err
937 : call getEnergyFluence ( lowerLim = BAND_SPEC2%Limit(1) &
938 : , upperLim = BAND_SPEC2%Limit(2) &
939 : , epk = BAND_SPEC2%epk &
940 : , alpha = BAND_SPEC2%alpha &
941 : , beta = BAND_SPEC2%beta &
942 : , tolerance = BAND_SPEC2%tolerance &
943 : , energyFluence = energyFluence &
944 : , Err = Err &
945 3 : )
946 3 : difference = 2._RK * abs( energyFluence - BAND_SPEC2%energyFluence ) / ( energyFluence + BAND_SPEC2%energyFluence )
947 3 : assertion = difference < BAND_SPEC2%tolerance
948 3 : if (Test%isDebugMode .and. .not. assertion) then
949 : ! LCOV_EXCL_START
950 : write(Test%outputUnit,"(*(g0,:,', '))")
951 : write(Test%outputUnit,"(*(g0,:,', '))") "photon fluence, Reference photon fluence, difference"
952 : write(Test%outputUnit,"(*(g0,:,', '))") energyFluence, BAND_SPEC2%energyFluence, difference
953 : write(Test%outputUnit,"(*(g0,:,', '))")
954 : end if
955 : ! LCOV_EXCL_STOP
956 3 : end function test_getEnergyFluence_2
957 :
958 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
959 :
960 : !> \brief
961 : !> Test the integration of both upper and upper tails with steep slopes.
962 3 : function test_getEnergyFluence_4() result(assertion)
963 3 : use Constants_mod, only: RK, IK
964 : use Err_mod, only: Err_type
965 : implicit none
966 : logical :: assertion
967 3 : real(RK) :: energyFluence, difference
968 3 : type(Err_type) :: Err
969 : call getEnergyFluence ( lowerLim = BAND_SPEC4%Limit(1) &
970 : , upperLim = BAND_SPEC4%Limit(2) &
971 : , epk = BAND_SPEC4%epk &
972 : , alpha = BAND_SPEC4%alpha &
973 : , beta = BAND_SPEC4%beta &
974 : , tolerance = BAND_SPEC4%tolerance &
975 : , energyFluence = energyFluence &
976 : , Err = Err &
977 3 : )
978 3 : difference = 2._RK * abs( energyFluence - BAND_SPEC4%energyFluence ) / ( energyFluence + BAND_SPEC4%energyFluence )
979 3 : assertion = difference < BAND_SPEC4%tolerance
980 3 : if (Test%isDebugMode .and. .not. assertion) then
981 : ! LCOV_EXCL_START
982 : write(Test%outputUnit,"(*(g0,:,', '))")
983 : write(Test%outputUnit,"(*(g0,:,', '))") "photon fluence, Reference photon fluence, difference"
984 : write(Test%outputUnit,"(*(g0,:,', '))") energyFluence, BAND_SPEC4%energyFluence, difference
985 : write(Test%outputUnit,"(*(g0,:,', '))")
986 : end if
987 : ! LCOV_EXCL_STOP
988 3 : end function test_getEnergyFluence_4
989 :
990 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
991 :
992 3 : function test_getPhotonFluenceFromEnergyFluence_1() result(assertion)
993 3 : use Constants_mod, only: RK, IK
994 : use Err_mod, only: Err_type
995 : implicit none
996 : logical :: assertion
997 3 : real(RK) :: photonFluence, difference
998 3 : type(Err_type) :: Err
999 : call getPhotonFluenceFromEnergyFluence ( energyFluence = BAND_SPEC1%energyFluence &
1000 : , lowerLim = BAND_SPEC1%Limit(1) &
1001 : , upperLim = BAND_SPEC1%Limit(2) &
1002 : , epk = BAND_SPEC1%epk &
1003 : , alpha = BAND_SPEC1%alpha &
1004 : , beta = BAND_SPEC1%beta &
1005 : , tolerance = BAND_SPEC1%tolerance &
1006 : , photonFluence = photonFluence &
1007 : , Err = Err &
1008 3 : )
1009 3 : difference = 2._RK * abs( photonFluence - BAND_SPEC1%photonFluence ) / ( photonFluence + BAND_SPEC1%photonFluence )
1010 3 : assertion = difference < BAND_SPEC1%tolerance
1011 3 : if (Test%isDebugMode .and. .not. assertion) then
1012 : ! LCOV_EXCL_START
1013 : write(Test%outputUnit,"(*(g0,:,', '))")
1014 : write(Test%outputUnit,"(*(g0,:,', '))") "photon fluence, Reference photon fluence, difference"
1015 : write(Test%outputUnit,"(*(g0,:,', '))") photonFluence, BAND_SPEC1%photonFluence, difference
1016 : write(Test%outputUnit,"(*(g0,:,', '))")
1017 : end if
1018 : ! LCOV_EXCL_STOP
1019 3 : end function test_getPhotonFluenceFromEnergyFluence_1
1020 :
1021 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1022 :
1023 3 : function test_getPhotonFluenceFromEnergyFluence_2() result(assertion)
1024 3 : use Constants_mod, only: RK, IK
1025 : use Err_mod, only: Err_type
1026 : implicit none
1027 : logical :: assertion
1028 3 : real(RK) :: photonFluence, difference
1029 3 : type(Err_type) :: Err
1030 : call getPhotonFluenceFromEnergyFluence ( energyFluence = BAND_SPEC2%energyFluence &
1031 : , lowerLim = BAND_SPEC2%Limit(1) &
1032 : , upperLim = BAND_SPEC2%Limit(2) &
1033 : , epk = BAND_SPEC2%epk &
1034 : , alpha = BAND_SPEC2%alpha &
1035 : , beta = BAND_SPEC2%beta &
1036 : , tolerance = BAND_SPEC2%tolerance &
1037 : , photonFluence = photonFluence &
1038 : , Err = Err &
1039 3 : )
1040 3 : difference = 2._RK * abs( photonFluence - BAND_SPEC2%photonFluence ) / ( photonFluence + BAND_SPEC2%photonFluence )
1041 3 : assertion = difference < BAND_SPEC2%tolerance
1042 3 : if (Test%isDebugMode .and. .not. assertion) then
1043 : ! LCOV_EXCL_START
1044 : write(Test%outputUnit,"(*(g0,:,', '))")
1045 : write(Test%outputUnit,"(*(g0,:,', '))") "photon fluence, Reference photon fluence, difference"
1046 : write(Test%outputUnit,"(*(g0,:,', '))") photonFluence, BAND_SPEC2%photonFluence, difference
1047 : write(Test%outputUnit,"(*(g0,:,', '))")
1048 : end if
1049 : ! LCOV_EXCL_STOP
1050 3 : end function test_getPhotonFluenceFromEnergyFluence_2
1051 :
1052 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1053 :
1054 3 : function test_getPhotonFluenceFromEnergyFluence_3() result(assertion)
1055 3 : use Constants_mod, only: RK, IK
1056 : use Err_mod, only: Err_type
1057 : implicit none
1058 : logical :: assertion
1059 3 : real(RK) :: photonFluence, difference
1060 3 : type(Err_type) :: Err
1061 : call getPhotonFluenceFromEnergyFluence ( energyFluence = BAND_SPEC3%energyFluence &
1062 : , lowerLim = BAND_SPEC3%Limit(1) &
1063 : , upperLim = BAND_SPEC3%Limit(2) &
1064 : , epk = BAND_SPEC3%epk &
1065 : , alpha = BAND_SPEC3%alpha &
1066 : , beta = BAND_SPEC3%beta &
1067 : , tolerance = BAND_SPEC3%tolerance &
1068 : , photonFluence = photonFluence &
1069 : , Err = Err &
1070 3 : )
1071 3 : difference = 2._RK * abs( photonFluence - BAND_SPEC3%photonFluence ) / ( photonFluence + BAND_SPEC3%photonFluence )
1072 3 : assertion = difference < BAND_SPEC3%tolerance
1073 3 : if (Test%isDebugMode .and. .not. assertion) then
1074 : ! LCOV_EXCL_START
1075 : write(Test%outputUnit,"(*(g0,:,', '))")
1076 : write(Test%outputUnit,"(*(g0,:,', '))") "photon fluence, Reference photon fluence, difference"
1077 : write(Test%outputUnit,"(*(g0,:,', '))") photonFluence, BAND_SPEC3%photonFluence, difference
1078 : write(Test%outputUnit,"(*(g0,:,', '))")
1079 : end if
1080 : ! LCOV_EXCL_STOP
1081 3 : end function test_getPhotonFluenceFromEnergyFluence_3
1082 :
1083 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1084 :
1085 3 : function test_getPhotonFluenceFromEnergyFluence_4() result(assertion)
1086 3 : use Constants_mod, only: RK, IK
1087 : use Err_mod, only: Err_type
1088 : implicit none
1089 : logical :: assertion
1090 3 : real(RK) :: photonFluence, difference
1091 3 : type(Err_type) :: Err
1092 : call getPhotonFluenceFromEnergyFluence ( energyFluence = BAND_SPEC4%energyFluence &
1093 : , lowerLim = BAND_SPEC4%Limit(1) &
1094 : , upperLim = BAND_SPEC4%Limit(2) &
1095 : , epk = BAND_SPEC4%epk &
1096 : , alpha = BAND_SPEC4%alpha &
1097 : , beta = BAND_SPEC4%beta &
1098 : , tolerance = BAND_SPEC4%tolerance &
1099 : , photonFluence = photonFluence &
1100 : , Err = Err &
1101 3 : )
1102 3 : difference = 2 * abs( photonFluence - BAND_SPEC4%photonFluence ) / ( photonFluence + BAND_SPEC4%photonFluence )
1103 3 : assertion = difference < BAND_SPEC4%tolerance
1104 3 : if (Test%isDebugMode .and. .not. assertion) then
1105 : ! LCOV_EXCL_START
1106 : write(Test%outputUnit,"(*(g0,:,', '))")
1107 : write(Test%outputUnit,"(*(g0,:,', '))") "photon fluence, Reference photon fluence, difference"
1108 : write(Test%outputUnit,"(*(g0,:,', '))") photonFluence, BAND_SPEC4%photonFluence, difference
1109 : write(Test%outputUnit,"(*(g0,:,', '))")
1110 : end if
1111 : ! LCOV_EXCL_STOP
1112 3 : end function test_getPhotonFluenceFromEnergyFluence_4
1113 :
1114 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1115 :
1116 3 : function test_getPhotonFluenceFromEnergyFluence_5() result(assertion)
1117 3 : use Constants_mod, only: RK, IK
1118 : use Err_mod, only: Err_type
1119 : implicit none
1120 : logical :: assertion
1121 3 : real(RK) :: photonFluence, difference
1122 3 : type(Err_type) :: Err
1123 : call getPhotonFluenceFromEnergyFluence ( energyFluence = BAND_SPEC1%energyFluence &
1124 : , lowerLim = BAND_SPEC1%Limit(1) &
1125 : , upperLim = BAND_SPEC1%Limit(2) &
1126 : , epk = BAND_SPEC1%epk &
1127 : , alpha = BAND_SPEC1%alpha &
1128 : , beta = BAND_SPEC1%beta &
1129 : , tolerance = BAND_SPEC1%tolerance &
1130 : , lowerLimNew = BAND_SPEC2%Limit(1) &
1131 : , upperLimNew = BAND_SPEC2%Limit(2) &
1132 : , photonFluence = photonFluence &
1133 : , Err = Err &
1134 3 : )
1135 3 : difference = 2._RK * abs( photonFluence - BAND_SPEC2%photonFluence ) / ( photonFluence + BAND_SPEC2%photonFluence )
1136 3 : assertion = difference < BAND_SPEC4%tolerance
1137 3 : if (Test%isDebugMode .and. .not. assertion) then
1138 : ! LCOV_EXCL_START
1139 : write(Test%outputUnit,"(*(g0,:,', '))")
1140 : write(Test%outputUnit,"(*(g0,:,', '))") "photon fluence, Reference photon fluence, difference"
1141 : write(Test%outputUnit,"(*(g0,:,', '))") photonFluence, BAND_SPEC2%photonFluence, difference
1142 : write(Test%outputUnit,"(*(g0,:,', '))")
1143 : end if
1144 : ! LCOV_EXCL_STOP
1145 3 : end function test_getPhotonFluenceFromEnergyFluence_5
1146 :
1147 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1148 :
1149 : !#endif
1150 :
1151 : end module Test_BandSpectrum_mod ! LCOV_EXCL_LINE
|