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 [CrossCorr_mod](@ref crosscorr_mod).
44 : !> \author Amir Shahmoradi
45 :
46 : module Test_CrossCorr_mod
47 :
48 : use Test_mod, only: Test_type
49 : use Constants_mod, only: IK, RK
50 : use CrossCorr_mod
51 : implicit none
52 :
53 : private
54 : public :: Test_CrossCorr
55 :
56 : type(Test_type) :: Test
57 :
58 : ! input Test data
59 :
60 : type :: WeightedData_type
61 : integer(IK) :: nd = 1_IK
62 : integer(IK) :: np = 9985_IK
63 : integer(IK) , allocatable :: Weight(:)
64 : real(RK) , allocatable :: Data(:,:)
65 : real(RK) , allocatable :: NormedData(:,:)
66 : real(RK) , allocatable :: ref_AutoCorr(:,:)
67 : real(RK) , allocatable :: InverseSumNormedDataSq(:)
68 : real(RK) , allocatable :: InverseSumNormedDataSq_ref(:)
69 : contains
70 : procedure , pass :: read => readData
71 : end type WeightedData_type
72 : type(WeightedData_type) :: WeightedData !< An object of class WeightedData_type containing the input Compact-Weighted Data (WCD).
73 :
74 : ! Computed Autocorrelation
75 :
76 : type :: AutoCorr_type
77 : real(RK) , allocatable :: NormedDataFFT1(:,:), NormedDataFFT2(:,:)
78 : real(RK) , allocatable :: AutoCorrWeightedFFT(:,:)
79 : real(RK) , allocatable :: AutoCorrDirect_ref(:,:)
80 : real(RK) , allocatable :: AutoCorrFFT_ref(:,:)
81 : real(RK) , allocatable :: AutoCorrDirect(:,:)
82 : real(RK) , allocatable :: AutoCorrFFT(:,:)
83 : integer(IK) , allocatable :: Lag_ref(:)
84 : integer(IK) , allocatable :: Lag(:)
85 : integer(IK) :: nlag
86 : integer(IK) :: paddedLen
87 : end type AutoCorr_type
88 : type(AutoCorr_type) :: AutoCorr
89 :
90 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
91 :
92 : contains
93 :
94 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
95 :
96 1 : subroutine Test_CrossCorr()
97 :
98 : use Constants_mod, only: IK, RK
99 : implicit none
100 :
101 1 : Test = Test_type(moduleName=MODULE_NAME)
102 1 : call Test%run(Test_padZero_1, "Test_padZero_1")
103 1 : call Test%run(Test_padZero_2, "Test_padZero_2")
104 1 : call Test%run(Test_getCumSumIAC_1, "Test_getCumSumIAC_1")
105 1 : call Test%run(Test_getCumSumIAC_2, "Test_getCumSumIAC_2")
106 1 : call Test%run(Test_getCumSumIAC_3, "Test_getCumSumIAC_3")
107 1 : call Test%run(Test_getCrossCorrFFT, "Test_getCrossCorrFFT")
108 1 : call Test%run(Test_getMaxCumSumIAC_1, "Test_getMaxCumSumIAC_1")
109 1 : call Test%run(Test_getMaxCumSumIAC_2, "Test_getMaxCumSumIAC_2")
110 1 : call Test%run(Test_getPaddedLen_IK_1, "Test_getPaddedLen_IK_1")
111 1 : call Test%run(Test_getPaddedLen_IK_2, "Test_getPaddedLen_IK_2")
112 1 : call Test%run(Test_getPaddedLen_RK_1, "Test_getPaddedLen_RK_1")
113 1 : call Test%run(Test_getPaddedLen_RK_2, "Test_getPaddedLen_RK_2")
114 1 : call Test%run(Test_getNextExponent_1, "Test_getNextExponent_1")
115 1 : call Test%run(Test_getNextExponent_2, "Test_getNextExponent_2")
116 1 : call Test%run(Test_getNextExponent_3, "Test_getNextExponent_3")
117 1 : call Test%run(Test_getBatchMeansIAC_1, "Test_getBatchMeansIAC_1")
118 1 : call Test%run(Test_getBatchMeansIAC_2, "Test_getBatchMeansIAC_2")
119 1 : call Test%run(Test_getBatchMeansIAC_3, "Test_getBatchMeansIAC_3")
120 1 : call Test%run(Test_getAutoCorrDirect_1, "Test_getAutoCorrDirect_1")
121 1 : call Test%run(Test_getAutoCorrDirect_2, "Test_getAutoCorrDirect_2")
122 1 : call Test%run(Test_getPreviousExponent_1, "Test_getPreviousExponent_1")
123 1 : call Test%run(Test_getPreviousExponent_2, "Test_getPreviousExponent_2")
124 1 : call Test%run(Test_getInverseSumNormedDataSq_1, "Test_getInverseSumNormedDataSq_1")
125 1 : call Test%run(Test_getCrossCorrWeightedFFT_1, "Test_getCrossCorrWeightedFFT_1")
126 1 : call Test%run(Test_getCrossCorrWeightedFFT_2, "Test_getCrossCorrWeightedFFT_2")
127 1 : call Test%run(Test_getCrossCorrWeightedFFT_3, "Test_getCrossCorrWeightedFFT_3")
128 1 : call Test%finalize()
129 :
130 1 : end subroutine Test_CrossCorr
131 :
132 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
133 :
134 1 : function Test_padZero_1() result(assertion)
135 1 : use Constants_mod, only: IK, RK
136 : implicit none
137 : logical :: assertion
138 : real(RK) , parameter :: tolerance = 1.e-14_RK
139 : real(RK) , parameter :: CurrentArray(*) = [1._RK, 1._RK, 1._RK, 1._RK]
140 : real(RK) , parameter :: PaddedArray_ref(*) = [1._RK, 1._RK, 1._RK, 1._RK, 0._RK, 0._RK, 0._RK, 0._RK, 0._RK, 0._RK]
141 : integer(IK) , parameter :: lenCurrentArray = size(CurrentArray)
142 : integer(IK) , parameter :: paddedLen = size(PaddedArray_ref)
143 : real(RK) :: PaddedArray(size(PaddedArray_ref)) ! Gfortran 7.1 fails to automatically allocate an allocatable version of these arrays
144 : real(RK) :: Difference(size(PaddedArray_ref)) ! Gfortran 7.1 fails to automatically allocate an allocatable version of these arrays
145 11 : PaddedArray = padZero(currentLen = lenCurrentArray, Array = CurrentArray, paddedLen = paddedLen)
146 11 : Difference = abs(PaddedArray - PaddedArray_ref)
147 11 : assertion = all(Difference < tolerance)
148 1 : if (Test%isDebugMode .and. .not. assertion) then
149 : ! LCOV_EXCL_START
150 : write(Test%outputUnit,"(*(g0.15,:,' '))")
151 : write(Test%outputUnit,"(*(g0.15,:,' '))") "CurrentArray =", CurrentArray
152 : write(Test%outputUnit,"(*(g0.15,:,' '))") "PaddedArray_ref =", PaddedArray_ref
153 : write(Test%outputUnit,"(*(g0.15,:,' '))") "PaddedArray =", PaddedArray
154 : write(Test%outputUnit,"(*(g0.15,:,' '))") "Difference =", Difference
155 : write(Test%outputUnit,"(*(g0.15,:,' '))")
156 : end if
157 : ! LCOV_EXCL_STOP
158 1 : end function Test_padZero_1
159 :
160 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
161 :
162 1 : function Test_padZero_2() result(assertion)
163 1 : use Constants_mod, only: IK, RK
164 : implicit none
165 : logical :: assertion
166 : real(RK) , parameter :: tolerance = 1.e-14_RK
167 : real(RK) , parameter :: CurrentArray(*) = [1._RK, 1._RK, 1._RK, 1._RK]
168 : real(RK) , parameter :: PaddedArray_ref(*) = [1._RK, 1._RK, 1._RK, 1._RK, 0._RK, 0._RK, 0._RK, 0._RK]
169 : integer(IK) , parameter :: lenCurrentArray = size(CurrentArray)
170 : integer(IK) , parameter :: paddedLen = size(PaddedArray_ref)
171 : real(RK) :: PaddedArray(size(PaddedArray_ref)) ! Gfortran 7.1 fails to automatically allocate an allocatable version of these arrays
172 : real(RK) :: Difference(size(PaddedArray_ref)) ! Gfortran 7.1 fails to automatically allocate an allocatable version of these arrays
173 9 : PaddedArray = padZero(currentLen = lenCurrentArray, Array = CurrentArray)
174 9 : Difference = abs(PaddedArray - PaddedArray_ref)
175 9 : assertion = all(Difference < tolerance)
176 1 : if (Test%isDebugMode .and. .not. assertion) then
177 : ! LCOV_EXCL_START
178 : write(Test%outputUnit,"(*(g0.15,:,' '))")
179 : write(Test%outputUnit,"(*(g0.15,:,' '))") "CurrentArray =", CurrentArray
180 : write(Test%outputUnit,"(*(g0.15,:,' '))") "PaddedArray_ref =", PaddedArray_ref
181 : write(Test%outputUnit,"(*(g0.15,:,' '))") "PaddedArray =", PaddedArray
182 : write(Test%outputUnit,"(*(g0.15,:,' '))") "Difference =", Difference
183 : write(Test%outputUnit,"(*(g0.15,:,' '))")
184 : end if
185 : ! LCOV_EXCL_STOP
186 1 : end function Test_padZero_2
187 :
188 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
189 :
190 1 : function Test_getPaddedLen_IK_1() result(assertion)
191 1 : use Constants_mod, only: IK
192 : implicit none
193 : logical :: assertion
194 : integer(IK) , parameter :: actualLen = 4_IK
195 : integer(IK) , parameter :: paddedLen_ref = 27_IK
196 : integer(IK) , parameter :: base = 3_IK
197 : integer(IK) :: paddedLen
198 : integer(IK) :: difference
199 1 : paddedLen = getPaddedLen(actualLen = actualLen, base = base)
200 1 : difference = abs(paddedLen - paddedLen_ref)
201 1 : assertion = difference == 0_IK
202 1 : if (Test%isDebugMode .and. .not. assertion) then
203 : ! LCOV_EXCL_START
204 : write(Test%outputUnit,"(*(g0.15,:,' '))")
205 : write(Test%outputUnit,"(*(g0.15,:,' '))") "actualLen =", actualLen
206 : write(Test%outputUnit,"(*(g0.15,:,' '))") "paddedLen_ref =", paddedLen_ref
207 : write(Test%outputUnit,"(*(g0.15,:,' '))") "paddedLen =", paddedLen
208 : write(Test%outputUnit,"(*(g0.15,:,' '))") "difference =", difference
209 : write(Test%outputUnit,"(*(g0.15,:,' '))")
210 : end if
211 : ! LCOV_EXCL_STOP
212 1 : end function Test_getPaddedLen_IK_1
213 :
214 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
215 :
216 1 : function Test_getPaddedLen_IK_2() result(assertion)
217 1 : use Constants_mod, only: IK
218 : implicit none
219 : logical :: assertion
220 : integer(IK) , parameter :: actualLen = 4_IK
221 : integer(IK) , parameter :: paddedLen_ref = 8_IK
222 : integer(IK) :: paddedLen
223 : integer(IK) :: difference
224 1 : paddedLen = getPaddedLen(actualLen = actualLen)
225 1 : difference = abs(paddedLen - paddedLen_ref)
226 1 : assertion = difference == 0_IK
227 1 : if (Test%isDebugMode .and. .not. assertion) then
228 : ! LCOV_EXCL_START
229 : write(Test%outputUnit,"(*(g0.15,:,' '))")
230 : write(Test%outputUnit,"(*(g0.15,:,' '))") "actualLen =", actualLen
231 : write(Test%outputUnit,"(*(g0.15,:,' '))") "paddedLen_ref =", paddedLen_ref
232 : write(Test%outputUnit,"(*(g0.15,:,' '))") "paddedLen =", paddedLen
233 : write(Test%outputUnit,"(*(g0.15,:,' '))") "difference =", difference
234 : write(Test%outputUnit,"(*(g0.15,:,' '))")
235 : end if
236 : ! LCOV_EXCL_STOP
237 1 : end function Test_getPaddedLen_IK_2
238 :
239 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
240 :
241 1 : function Test_getPaddedLen_RK_1() result(assertion)
242 1 : use Constants_mod, only: IK, RK
243 : implicit none
244 : logical :: assertion
245 : real(RK) , parameter :: actualLen = 4._RK
246 : integer(IK) , parameter :: paddedLen_ref = 43_IK
247 : real(RK) , parameter :: base = 3.5_RK
248 : integer(IK) :: paddedLen
249 : integer(IK) :: difference
250 1 : paddedLen = getPaddedLen(actualLen = actualLen, base = base)
251 1 : difference = abs(paddedLen - paddedLen_ref)
252 1 : assertion = difference == 0_IK
253 1 : if (Test%isDebugMode .and. .not. assertion) then
254 : ! LCOV_EXCL_START
255 : write(Test%outputUnit,"(*(g0.15,:,' '))")
256 : write(Test%outputUnit,"(*(g0.15,:,' '))") "actualLen =", actualLen
257 : write(Test%outputUnit,"(*(g0.15,:,' '))") "paddedLen_ref =", paddedLen_ref
258 : write(Test%outputUnit,"(*(g0.15,:,' '))") "paddedLen =", paddedLen
259 : write(Test%outputUnit,"(*(g0.15,:,' '))") "difference =", difference
260 : write(Test%outputUnit,"(*(g0.15,:,' '))")
261 : end if
262 : ! LCOV_EXCL_STOP
263 1 : end function Test_getPaddedLen_RK_1
264 :
265 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
266 :
267 1 : function Test_getPaddedLen_RK_2() result(assertion)
268 1 : use Constants_mod, only: IK, RK
269 : implicit none
270 : logical :: assertion
271 : real(RK) , parameter :: actualLen = 4._RK
272 : integer(IK) , parameter :: paddedLen_ref = 8_IK
273 : real(RK) , parameter :: base = 2._RK
274 : integer(IK) :: paddedLen
275 : integer(IK) :: difference
276 1 : paddedLen = getPaddedLen(actualLen = actualLen, base = base)
277 1 : difference = abs(paddedLen - paddedLen_ref)
278 1 : assertion = difference == 0_IK
279 1 : if (Test%isDebugMode .and. .not. assertion) then
280 : ! LCOV_EXCL_START
281 : write(Test%outputUnit,"(*(g0.15,:,' '))")
282 : write(Test%outputUnit,"(*(g0.15,:,' '))") "actualLen =", actualLen
283 : write(Test%outputUnit,"(*(g0.15,:,' '))") "paddedLen_ref =", paddedLen_ref
284 : write(Test%outputUnit,"(*(g0.15,:,' '))") "paddedLen =", paddedLen
285 : write(Test%outputUnit,"(*(g0.15,:,' '))") "difference =", difference
286 : write(Test%outputUnit,"(*(g0.15,:,' '))")
287 : end if
288 : ! LCOV_EXCL_STOP
289 1 : end function Test_getPaddedLen_RK_2
290 :
291 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
292 :
293 1 : function Test_getNextExponent_1() result(assertion)
294 1 : use Constants_mod, only: IK, RK
295 : implicit none
296 : logical :: assertion
297 : integer(IK) :: difference
298 : integer(IK) :: nextExponent
299 : integer(IK) , parameter :: nextExponent_ref = 4_IK
300 : real(RK) , parameter :: absoluteValue = 10._RK
301 : real(RK) , parameter :: base = 2._RK
302 1 : nextExponent = getNextExponent(absoluteValue = absoluteValue, base = base)
303 1 : difference = abs(nextExponent - nextExponent_ref)
304 1 : assertion = difference == 0_IK
305 1 : if (Test%isDebugMode .and. .not. assertion) then
306 : ! LCOV_EXCL_START
307 : write(Test%outputUnit,"(*(g0.15,:,' '))")
308 : write(Test%outputUnit,"(*(g0.15,:,' '))") "nextExponent_ref =", nextExponent_ref
309 : write(Test%outputUnit,"(*(g0.15,:,' '))") "Computed nextExponent =", nextExponent
310 : write(Test%outputUnit,"(*(g0.15,:,' '))") "difference =", difference
311 : write(Test%outputUnit,"(*(g0.15,:,' '))")
312 : end if
313 : ! LCOV_EXCL_STOP
314 1 : end function Test_getNextExponent_1
315 :
316 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
317 :
318 1 : function Test_getNextExponent_2() result(assertion)
319 1 : use Constants_mod, only: IK, RK
320 : implicit none
321 : logical :: assertion
322 : integer(IK) :: difference
323 : integer(IK) :: nextExponent
324 : integer(IK) , parameter :: nextExponent_ref = 4_IK
325 : real(RK) , parameter :: absoluteValue = 16._RK
326 : real(RK) , parameter :: base = 2.5_RK
327 1 : nextExponent = getNextExponent(absoluteValue = absoluteValue, base = base)
328 1 : difference = abs(nextExponent - nextExponent_ref)
329 1 : assertion = difference == 0_IK
330 1 : if (Test%isDebugMode .and. .not. assertion) then
331 : ! LCOV_EXCL_START
332 : write(Test%outputUnit,"(*(g0.15,:,' '))")
333 : write(Test%outputUnit,"(*(g0.15,:,' '))") "nextExponent_ref =", nextExponent_ref
334 : write(Test%outputUnit,"(*(g0.15,:,' '))") "Computed nextExponent =", nextExponent
335 : write(Test%outputUnit,"(*(g0.15,:,' '))") "difference =", difference
336 : write(Test%outputUnit,"(*(g0.15,:,' '))")
337 : end if
338 : ! LCOV_EXCL_STOP
339 1 : end function Test_getNextExponent_2
340 :
341 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
342 :
343 1 : function Test_getNextExponent_3() result(assertion)
344 1 : use Constants_mod, only: RK
345 : implicit none
346 : logical :: assertion
347 : integer(IK) :: difference
348 : integer(IK) :: nextExponent
349 : integer(IK) , parameter :: nextExponent_ref = 4_IK
350 : real(RK) , parameter :: absoluteValue = 16._RK
351 1 : nextExponent = getNextExponent(absoluteValue = absoluteValue)
352 1 : difference = abs(nextExponent - nextExponent_ref)
353 1 : assertion = difference == 0_IK
354 1 : if (Test%isDebugMode .and. .not. assertion) then
355 : ! LCOV_EXCL_START
356 : write(Test%outputUnit,"(*(g0.15,:,' '))")
357 : write(Test%outputUnit,"(*(g0.15,:,' '))") "nextExponent_ref =", nextExponent_ref
358 : write(Test%outputUnit,"(*(g0.15,:,' '))") "Computed nextExponent =", nextExponent
359 : write(Test%outputUnit,"(*(g0.15,:,' '))") "difference =", difference
360 : write(Test%outputUnit,"(*(g0.15,:,' '))")
361 : end if
362 : ! LCOV_EXCL_STOP
363 1 : end function Test_getNextExponent_3
364 :
365 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
366 :
367 1 : function Test_getPreviousExponent_1() result(assertion)
368 1 : use Constants_mod, only: IK, RK
369 : implicit none
370 : logical :: assertion
371 : integer(IK) :: difference
372 : integer(IK) :: previousExponent
373 : integer(IK) , parameter :: previousExponent_ref = 13_IK
374 : real(RK) , parameter :: absoluteValue = 9985._RK
375 1 : previousExponent = getPreviousExponent(absoluteValue = absoluteValue)
376 1 : difference = abs(previousExponent - previousExponent_ref)
377 1 : assertion = difference == 0_IK
378 1 : if (Test%isDebugMode .and. .not. assertion) then
379 : ! LCOV_EXCL_START
380 : write(Test%outputUnit,"(*(g0.15,:,' '))")
381 : write(Test%outputUnit,"(*(g0.15,:,' '))") "previousExponent_ref =", previousExponent_ref
382 : write(Test%outputUnit,"(*(g0.15,:,' '))") "previousExponent =", previousExponent
383 : write(Test%outputUnit,"(*(g0.15,:,' '))") "Difference =", difference
384 : write(Test%outputUnit,"(*(g0.15,:,' '))")
385 : end if
386 : ! LCOV_EXCL_STOP
387 1 : end function Test_getPreviousExponent_1
388 :
389 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
390 :
391 1 : function Test_getPreviousExponent_2() result(assertion)
392 1 : use Constants_mod, only: IK, RK
393 : implicit none
394 : logical :: assertion
395 : integer(IK) :: difference
396 : integer(IK) :: previousExponent
397 : integer(IK) , parameter :: previousExponent_ref = 7_IK
398 : real(RK) , parameter :: absoluteValue = 9985._RK
399 : real(RK) , parameter :: base = 3.5_RK
400 1 : previousExponent = getPreviousExponent(absoluteValue = absoluteValue, base = base)
401 1 : difference = abs(previousExponent - previousExponent_ref)
402 1 : assertion = difference == 0_IK
403 1 : if (Test%isDebugMode .and. .not. assertion) then
404 : ! LCOV_EXCL_START
405 : write(Test%outputUnit,"(*(g0.15,:,' '))")
406 : write(Test%outputUnit,"(*(g0.15,:,' '))") "previousExponent_ref =", previousExponent_ref
407 : write(Test%outputUnit,"(*(g0.15,:,' '))") "previousExponent =", previousExponent
408 : write(Test%outputUnit,"(*(g0.15,:,' '))") "Difference =", difference
409 : write(Test%outputUnit,"(*(g0.15,:,' '))")
410 : end if
411 : ! LCOV_EXCL_STOP
412 1 : end function Test_getPreviousExponent_2
413 :
414 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
415 :
416 15 : subroutine readData(WeightedData)
417 :
418 1 : use Statistics_mod, only: getNormData
419 : implicit none
420 : class(WeightedData_type), intent(inout) :: WeightedData
421 : integer(IK) :: ip, fileUnit
422 :
423 : ! read the input data required for other Tests
424 :
425 15 : WeightedData%nd = 1_IK
426 15 : WeightedData%np = 9985_IK
427 15 : if (allocated(WeightedData%Weight)) deallocate(WeightedData%Weight); allocate(WeightedData%Weight(WeightedData%np))
428 15 : if (allocated(WeightedData%Data)) deallocate(WeightedData%Data); allocate(WeightedData%Data(WeightedData%nd,WeightedData%np))
429 :
430 : open( file = Test%inDir//"/Test_CrossCorr_mod@WeightedData.txt" & ! LCOV_EXCL_LINE
431 : , newunit = fileUnit & ! LCOV_EXCL_LINE
432 : , status = "old" & ! LCOV_EXCL_LINE
433 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
434 : , SHARED & ! LCOV_EXCL_LINE
435 : #endif
436 15 : )
437 149790 : do ip = 1, WeightedData%np
438 149790 : read(fileUnit,*) WeightedData%Weight(ip), WeightedData%Data(1:WeightedData%nd,ip)
439 : end do
440 15 : close(fileUnit)
441 :
442 : ! normalize data
443 :
444 299578 : WeightedData%NormedData = getNormData(WeightedData%nd, WeightedData%np, WeightedData%Data)
445 44 : WeightedData%InverseSumNormedDataSq_ref = [ 5.935290321338481E-004_RK ]
446 :
447 15 : end subroutine readData
448 :
449 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
450 :
451 1 : function Test_getInverseSumNormedDataSq_1() result(assertion)
452 :
453 15 : use Constants_mod, only: RK
454 : implicit none
455 : logical :: assertion
456 : real(RK), allocatable :: Difference(:)
457 : real(RK), parameter :: tolerance = 1.e-12_RK
458 1 : call WeightedData%read()
459 :
460 2 : WeightedData%InverseSumNormedDataSq = getInverseSumNormedDataSq(1_IK, WeightedData%np, WeightedData%NormedData)
461 :
462 : ! Gfortran 7.1 fails to automatically reallocate this array. This is not implemented in Gfortran 7.0.0
463 1 : if (allocated(Difference)) deallocate(Difference); allocate(Difference, mold = WeightedData%InverseSumNormedDataSq)
464 :
465 3 : Difference = abs( (WeightedData%InverseSumNormedDataSq - WeightedData%InverseSumNormedDataSq_ref) / WeightedData%InverseSumNormedDataSq_ref)
466 2 : assertion = all( Difference < tolerance )
467 1 : if (Test%isDebugMode .and. .not. assertion) then
468 : ! LCOV_EXCL_START
469 : write(Test%outputUnit,"(*(g0.15,:,' '))")
470 : write(Test%outputUnit,"(*(g0.15,:,' '))") "InverseSumNormedDataSq_ref =", WeightedData%InverseSumNormedDataSq_ref
471 : write(Test%outputUnit,"(*(g0.15,:,' '))") "InverseSumNormedDataSq =", WeightedData%InverseSumNormedDataSq
472 : write(Test%outputUnit,"(*(g0.15,:,' '))") "Difference =", Difference
473 : write(Test%outputUnit,"(*(g0.15,:,' '))")
474 : end if
475 : ! LCOV_EXCL_STOP
476 :
477 1 : end function Test_getInverseSumNormedDataSq_1
478 :
479 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
480 :
481 : ! compute AutoCorr for the given lags using the classical definition.
482 1 : function Test_getAutoCorrDirect_1() result(assertion)
483 :
484 1 : use Constants_mod, only: RK
485 : use String_mod, only: num2str
486 : implicit none
487 : logical :: assertion
488 : integer(IK) , allocatable :: DifferenceLag(:)
489 : real(RK) , allocatable :: DifferenceAutoCorrDirect(:,:)
490 : real(RK) , parameter :: tolerance = 1.e-12_RK
491 : integer(IK) :: ilag, fileUnit
492 :
493 1 : call WeightedData%read()
494 :
495 : ! Generate and verify Lags
496 :
497 16 : AutoCorr%Lag_ref = [ 0_IK, 1_IK, 2_IK, 4_IK, 8_IK, 16_IK, 32_IK, 64_IK, 128_IK, 256_IK, 512_IK, 1024_IK, 2048_IK, 4096_IK, 8192_IK ]
498 : AutoCorr%AutoCorrDirect_ref = reshape( [ 1._RK &
499 : , .8985120580850618_RK &
500 : , .8142306385443645_RK &
501 : , .6793649391868671_RK &
502 : , .5018573940223264_RK &
503 : , .2963258939172878_RK &
504 : , .2018267302958381_RK &
505 : , .1415530903106628_RK &
506 : , .5232924941049354E-01_RK &
507 : , .4982051840374713E-01_RK &
508 : , .5464128642962141E-01_RK &
509 : , -.2355552565791153E-01_RK &
510 : , .2584696857029676E-01_RK &
511 : , -.4164933936801392E-01_RK &
512 : , .4757873176344895E-02_RK &
513 33 : ], shape = [ 1, size(AutoCorr%Lag_ref) ] )
514 1 : AutoCorr%nlag = getPreviousExponent( real(WeightedData%np, kind=RK) ) + 1
515 45 : AutoCorr%Lag = [ 0, ( 2_IK**(ilag-1), ilag = 1, AutoCorr%nlag ) ]
516 :
517 : ! Gfortran 7.1 fails to automatically allocate an allocatable version of these arrays
518 1 : if (allocated(DifferenceLag)) deallocate(DifferenceLag); allocate(DifferenceLag, mold = AutoCorr%Lag)
519 :
520 17 : DifferenceLag = abs( AutoCorr%Lag - AutoCorr%Lag_ref )
521 16 : assertion = all( DifferenceLag == 0_IK )
522 :
523 1 : if (Test%isDebugMode .and. .not. assertion) then
524 : ! LCOV_EXCL_START
525 : write(Test%outputUnit,"(*(g0.15,:,' '))")
526 : write(Test%outputUnit,"(*(g0.15,:,' '))") "AutoCorr%Lag_ref =", AutoCorr%Lag_ref
527 : write(Test%outputUnit,"(*(g0.15,:,' '))") "AutoCorr%Lag =", AutoCorr%Lag
528 : write(Test%outputUnit,"(*(g0.15,:,' '))") "nlag =", AutoCorr%nlag
529 : write(Test%outputUnit,"(*(g0.15,:,' '))")
530 : end if
531 : ! LCOV_EXCL_STOP
532 :
533 : ! Generate and verify AutoCorrs
534 :
535 1 : if (allocated(AutoCorr%AutoCorrDirect)) deallocate(AutoCorr%AutoCorrDirect); allocate( AutoCorr%AutoCorrDirect(WeightedData%nd,AutoCorr%nlag + 1_IK) )
536 : call getAutoCorrDirect ( nd = WeightedData%nd & ! LCOV_EXCL_LINE
537 : , np = WeightedData%np & ! LCOV_EXCL_LINE
538 : , NormedData = WeightedData%NormedData(1:WeightedData%nd,1:WeightedData%np) & ! LCOV_EXCL_LINE
539 : , nlag = AutoCorr%nlag + 1_IK & ! LCOV_EXCL_LINE
540 : , Lag = AutoCorr%Lag & ! LCOV_EXCL_LINE
541 : , AutoCorr = AutoCorr%AutoCorrDirect & ! LCOV_EXCL_LINE
542 : , InverseSumNormedDataSq = WeightedData%InverseSumNormedDataSq & ! LCOV_EXCL_LINE
543 1 : )
544 :
545 : ! Gfortran 7.1 fails to automatically allocate an reallocatable version of these arrays
546 1 : if (allocated(DifferenceAutoCorrDirect)) deallocate(DifferenceAutoCorrDirect); allocate(DifferenceAutoCorrDirect, mold = AutoCorr%AutoCorrDirect)
547 :
548 32 : DifferenceAutoCorrDirect = abs( AutoCorr%AutoCorrDirect - AutoCorr%AutoCorrDirect_ref )
549 :
550 31 : assertion = assertion .and. all( DifferenceAutoCorrDirect < tolerance )
551 :
552 1 : if (Test%isDebugMode .and. .not. assertion) then
553 : ! LCOV_EXCL_START
554 :
555 : ! write data to output for further investigation
556 :
557 : open( file = Test%outDir//"/Test_CrossCorr_mod@WeightedData@AutoCorr@getAutoCorrDirect."//num2str(Test%Image%id)//".txt" & ! LCOV_EXCL_LINE
558 : , status = "replace" & ! LCOV_EXCL_LINE
559 : , newunit = fileUnit & ! LCOV_EXCL_LINE
560 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
561 : , SHARED & ! LCOV_EXCL_LINE
562 : #endif
563 : )
564 : do ilag = 1, AutoCorr%nlag + 1_IK
565 : write(fileUnit,"(*(g0.15,:,' '))") AutoCorr%Lag(ilag), AutoCorr%AutoCorrDirect(1:WeightedData%nd,ilag)
566 : end do
567 : close(fileUnit)
568 :
569 : write(Test%outputUnit,"(*(g0.15,:,' '))")
570 : write(Test%outputUnit,"(*(g0.15,:,' '))") "AutoCorr%AutoCorrDirect_ref =", AutoCorr%AutoCorrDirect_ref
571 : write(Test%outputUnit,"(*(g0.15,:,' '))") "AutoCorr%AutoCorrDirect =", AutoCorr%AutoCorrDirect
572 : write(Test%outputUnit,"(*(g0.15,:,' '))") "DifferenceAutoCorrDirect =", DifferenceAutoCorrDirect
573 : write(Test%outputUnit,"(*(g0.15,:,' '))")
574 :
575 : end if
576 : ! LCOV_EXCL_STOP
577 :
578 1 : end function Test_getAutoCorrDirect_1
579 :
580 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
581 :
582 : ! compute AutoCorr for the given lags using the classical definition, but without passing `InverseSumNormedDataSq`.
583 1 : function Test_getAutoCorrDirect_2() result(assertion)
584 :
585 1 : use Constants_mod, only: RK
586 : use String_mod, only: num2str
587 : implicit none
588 : logical :: assertion
589 : integer(IK) , allocatable :: DifferenceLag(:)
590 : real(RK) , allocatable :: DifferenceAutoCorrDirect(:,:)
591 : real(RK) , parameter :: tolerance = 1.e-12_RK
592 : integer(IK) :: ilag, fileUnit
593 :
594 1 : call WeightedData%read()
595 :
596 : ! Generate and verify Lags
597 :
598 17 : AutoCorr%Lag_ref = [ 0_IK, 1_IK, 2_IK, 4_IK, 8_IK, 16_IK, 32_IK, 64_IK, 128_IK, 256_IK, 512_IK, 1024_IK, 2048_IK, 4096_IK, 8192_IK ]
599 : AutoCorr%AutoCorrDirect_ref = reshape( [ 1._RK &
600 : , .8985120580850618_RK &
601 : , .8142306385443645_RK &
602 : , .6793649391868671_RK &
603 : , .5018573940223264_RK &
604 : , .2963258939172878_RK &
605 : , .2018267302958381_RK &
606 : , .1415530903106628_RK &
607 : , .5232924941049354E-01_RK &
608 : , .4982051840374713E-01_RK &
609 : , .5464128642962141E-01_RK &
610 : , -.2355552565791153E-01_RK &
611 : , .2584696857029676E-01_RK &
612 : , -.4164933936801392E-01_RK &
613 : , .4757873176344895E-02_RK &
614 34 : ], shape = [ 1, size(AutoCorr%Lag_ref) ] )
615 1 : AutoCorr%nlag = getPreviousExponent( real(WeightedData%np, kind=RK) ) + 1
616 46 : AutoCorr%Lag = [ 0, ( 2_IK**(ilag-1), ilag = 1, AutoCorr%nlag ) ]
617 :
618 : ! Gfortran 7.1 fails to automatically reallocate this array. This is not implemented in Gfortran 7.0.0
619 1 : if (allocated(DifferenceLag)) deallocate(DifferenceLag); allocate(DifferenceLag, mold = AutoCorr%Lag)
620 :
621 17 : DifferenceLag = abs( AutoCorr%Lag - AutoCorr%Lag_ref )
622 16 : assertion = all( DifferenceLag == 0_IK )
623 :
624 1 : if (Test%isDebugMode .and. .not. assertion) then
625 : ! LCOV_EXCL_START
626 : write(Test%outputUnit,"(*(g0.15,:,' '))")
627 : write(Test%outputUnit,"(*(g0.15,:,' '))") "AutoCorr%Lag_ref =", AutoCorr%Lag_ref
628 : write(Test%outputUnit,"(*(g0.15,:,' '))") "AutoCorr%Lag =", AutoCorr%Lag
629 : write(Test%outputUnit,"(*(g0.15,:,' '))") "nlag =", AutoCorr%nlag
630 : write(Test%outputUnit,"(*(g0.15,:,' '))")
631 : end if
632 : ! LCOV_EXCL_STOP
633 :
634 : ! Generate and verify AutoCorrs
635 :
636 1 : if (allocated(AutoCorr%AutoCorrDirect)) deallocate(AutoCorr%AutoCorrDirect); allocate( AutoCorr%AutoCorrDirect(WeightedData%nd,AutoCorr%nlag+1_IK) )
637 : call getAutoCorrDirect ( nd = WeightedData%nd & ! LCOV_EXCL_LINE
638 : , np = WeightedData%np & ! LCOV_EXCL_LINE
639 : , NormedData = WeightedData%NormedData(1:WeightedData%nd,1:WeightedData%np) & ! LCOV_EXCL_LINE
640 : , nlag = AutoCorr%nlag + 1_IK & ! LCOV_EXCL_LINE
641 : , Lag = AutoCorr%Lag & ! LCOV_EXCL_LINE
642 : , AutoCorr = AutoCorr%AutoCorrDirect & ! LCOV_EXCL_LINE
643 1 : )
644 :
645 : ! Gfortran 7.1 fails to automatically reallocate this array. This is not implemented in Gfortran 7.0.0
646 1 : if (allocated(DifferenceAutoCorrDirect)) deallocate(DifferenceAutoCorrDirect); allocate(DifferenceAutoCorrDirect, mold = AutoCorr%AutoCorrDirect)
647 :
648 32 : DifferenceAutoCorrDirect = abs( AutoCorr%AutoCorrDirect - AutoCorr%AutoCorrDirect_ref )
649 :
650 31 : assertion = assertion .and. all( DifferenceAutoCorrDirect <= tolerance )
651 :
652 1 : if (Test%isDebugMode .and. .not. assertion) then
653 : ! LCOV_EXCL_START
654 :
655 : ! write data to output for further investigation
656 :
657 : open( file = Test%outDir//"/WeightedDataAutoCorrDirect.Without.InverseSumNormedDataSq."//num2str(Test%Image%id)//".txt" & ! LCOV_EXCL_LINE
658 : , newunit = fileUnit & ! LCOV_EXCL_LINE
659 : , status = "replace" & ! LCOV_EXCL_LINE
660 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
661 : , SHARED & ! LCOV_EXCL_LINE
662 : #endif
663 : )
664 : do ilag = 1, AutoCorr%nlag + 1_IK
665 : write(fileUnit,"(*(g0.15,:,' '))") AutoCorr%Lag(ilag), AutoCorr%AutoCorrDirect(1:WeightedData%nd,ilag)
666 : end do
667 : close(fileUnit)
668 :
669 : write(Test%outputUnit,"(*(g0.15,:,' '))")
670 : write(Test%outputUnit,"(*(g0.15,:,' '))") "AutoCorr%AutoCorrDirect_ref =", AutoCorr%AutoCorrDirect_ref
671 : write(Test%outputUnit,"(*(g0.15,:,' '))") "AutoCorr%AutoCorrDirect =", AutoCorr%AutoCorrDirect
672 : write(Test%outputUnit,"(*(g0.15,:,' '))") "DifferenceAutoCorrDirect =", DifferenceAutoCorrDirect
673 : write(Test%outputUnit,"(*(g0.15,:,' '))")
674 :
675 : end if
676 : ! LCOV_EXCL_STOP
677 :
678 1 : end function Test_getAutoCorrDirect_2
679 :
680 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
681 :
682 : ! Test AutoCorr computation for Compact Data using FFT.
683 1 : function Test_getCrossCorrFFT() result(assertion)
684 1 : use Constants_mod, only: IK, RK
685 : use String_mod, only: num2str
686 : implicit none
687 : logical :: assertion, assertionCurrent
688 : real(RK) , allocatable :: Difference(:,:)
689 : real(RK) , allocatable :: DummyArray(:)
690 : real(RK) , parameter :: tolerance = 1.e-12_RK
691 : integer(IK) :: id, ip, fileUnit, ilag
692 :
693 1 : assertion = .true.
694 :
695 1 : call WeightedData%read()
696 :
697 1 : AutoCorr%paddedLen = getPaddedLen(WeightedData%np)
698 : allocate( AutoCorr%AutoCorrFFT_ref(AutoCorr%paddedLen,WeightedData%nd) & ! LCOV_EXCL_LINE
699 : , AutoCorr%NormedDataFFT1(AutoCorr%paddedLen,WeightedData%nd) & ! LCOV_EXCL_LINE
700 : , AutoCorr%NormedDataFFT2(AutoCorr%paddedLen,WeightedData%nd) & ! LCOV_EXCL_LINE
701 : , AutoCorr%AutoCorrFFT(AutoCorr%paddedLen,WeightedData%nd) & ! LCOV_EXCL_LINE
702 1 : )
703 2 : do id = 1, WeightedData%nd
704 9986 : DummyArray = WeightedData%NormedData(id,1:WeightedData%np)
705 32770 : AutoCorr%NormedDataFFT1(1:AutoCorr%paddedLen,id) = padZero(WeightedData%np, DummyArray, AutoCorr%paddedLen)
706 : end do
707 32771 : AutoCorr%NormedDataFFT2 = AutoCorr%NormedDataFFT1
708 :
709 2 : do id = 1, WeightedData%nd
710 :
711 : AutoCorr%AutoCorrFFT(1:AutoCorr%paddedLen,id) = getCrossCorrFFT ( AutoCorr%paddedLen & ! LCOV_EXCL_LINE
712 : , AutoCorr%NormedDataFFT1(1:AutoCorr%paddedLen,id) & ! LCOV_EXCL_LINE
713 : , AutoCorr%NormedDataFFT1(1:AutoCorr%paddedLen,id) & ! LCOV_EXCL_LINE
714 32769 : )
715 32769 : AutoCorr%AutoCorrFFT(1:AutoCorr%paddedLen,id) = AutoCorr%AutoCorrFFT(1:AutoCorr%paddedLen,id) / AutoCorr%AutoCorrFFT(1,id)
716 :
717 : ! ensure NormedDataFFT1 does not change upon entering and exiting getCrossCorrFFT()
718 :
719 32770 : do ip = 1, AutoCorr%paddedLen
720 32768 : assertionCurrent = AutoCorr%NormedDataFFT2(ip,id) == AutoCorr%NormedDataFFT1(ip,id)
721 32768 : assertion = assertion .and. assertionCurrent
722 32769 : if (Test%isDebugMode .and. .not. assertionCurrent) then
723 : ! LCOV_EXCL_START
724 : write(Test%outputUnit,"(*(g0.15,:,' '))") "Nonsense. These two must be equal: ", AutoCorr%NormedDataFFT1(ip,id), AutoCorr%NormedDataFFT2(ip,id)
725 : end if
726 : ! LCOV_EXCL_STOP
727 : end do
728 :
729 : end do
730 :
731 : ! read reference AutoCorrFFT_ref from the input data
732 :
733 : open( file = Test%inDir//"/Test_CrossCorr_mod@WeightedData@AutoCorrFFT@Compact.txt" & ! LCOV_EXCL_LINE
734 : , newunit = fileUnit & ! LCOV_EXCL_LINE
735 : , status = "old" & ! LCOV_EXCL_LINE
736 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
737 : , SHARED & ! LCOV_EXCL_LINE
738 : #endif
739 1 : )
740 32769 : do ip = 1, AutoCorr%paddedLen
741 32769 : read(fileUnit,*) ilag, AutoCorr%AutoCorrFFT_ref(ip,1)
742 : end do
743 1 : close(fileUnit)
744 :
745 : ! Gfortran 7.1 fails to automatically allocate an allocatable version of these arrays
746 1 : if (allocated(Difference)) deallocate(Difference); allocate(Difference, mold = AutoCorr%AutoCorrFFT)
747 :
748 32771 : Difference = abs( AutoCorr%AutoCorrFFT - AutoCorr%AutoCorrFFT_ref )
749 32770 : assertion = assertion .and. all( Difference <= tolerance )
750 :
751 1 : if (Test%isDebugMode .and. .not. assertion) then
752 : ! LCOV_EXCL_START
753 :
754 : ! write data to output for further investigation
755 :
756 : open( file = Test%outDir//"/Test_CrossCorr_mod@WeightedData@AutoCorrFFT@Compact@getCrossCorrFFT."//num2str(Test%Image%id)//".out" & ! LCOV_EXCL_LINE
757 : , newunit = fileUnit & ! LCOV_EXCL_LINE
758 : , status = "replace" & ! LCOV_EXCL_LINE
759 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
760 : , SHARED & ! LCOV_EXCL_LINE
761 : #endif
762 : )
763 : do ip = 1, AutoCorr%paddedLen
764 : write(fileUnit,"(*(g0.15,:,' '))") ip-1, AutoCorr%AutoCorrFFT(ip,1)
765 : end do
766 : close(fileUnit)
767 :
768 : end if
769 : ! LCOV_EXCL_STOP
770 :
771 1 : end function Test_getCrossCorrFFT
772 :
773 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
774 :
775 : ! Test the AutoCorr computation using FFT with missing Weighted Data, that is, for the compact data.
776 1 : function Test_getCrossCorrWeightedFFT_1() result(assertion)
777 :
778 1 : use Statistics_mod, only: getNormData
779 : use Constants_mod, only: IK, RK
780 : use String_mod, only: num2str
781 : implicit none
782 : logical :: assertion
783 : real(RK) , allocatable :: Difference(:,:)
784 : real(RK) , allocatable :: DummyArray(:)
785 : real(RK) , parameter :: tolerance = 1.e-12_RK
786 : integer(IK) :: id, ip, fileUnit
787 : integer(IK) , allocatable :: DiffMaxLoc(:)
788 :
789 1 : assertion = .true.
790 :
791 1 : call WeightedData%read()
792 :
793 : ! open( file = Test%outDir//"/NormedData.compact."//num2str(Test%Image%id)//".txt" & ! LCOV_EXCL_LINE
794 : ! , newunit = fileUnit & ! LCOV_EXCL_LINE
795 : ! , status = "replace" & ! LCOV_EXCL_LINE
796 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
797 : ! , SHARED & ! LCOV_EXCL_LINE
798 : #endif
799 : ! )
800 : ! write(fileUnit,"(*(g0.15,:,/))") WeightedData%NormedData
801 : ! close(fileUnit)
802 :
803 1 : if (allocated(AutoCorr%AutoCorrWeightedFFT)) deallocate(AutoCorr%AutoCorrWeightedFFT)
804 1 : allocate( AutoCorr%AutoCorrWeightedFFT(AutoCorr%paddedLen, WeightedData%nd) )
805 :
806 2 : do id = 1, WeightedData%nd
807 9986 : DummyArray = WeightedData%NormedData(id,1:WeightedData%np)
808 : AutoCorr%AutoCorrWeightedFFT(1:AutoCorr%paddedLen,id) = getCrossCorrWeightedFFT ( lenCompactData1 = WeightedData%np & ! LCOV_EXCL_LINE
809 : , lenCompactData2 = WeightedData%np & ! LCOV_EXCL_LINE
810 : , paddedLen = AutoCorr%paddedLen & ! LCOV_EXCL_LINE
811 : , CompactData1 = DummyArray & ! LCOV_EXCL_LINE
812 : , CompactData2 = DummyArray & ! LCOV_EXCL_LINE
813 32769 : )
814 32770 : AutoCorr%AutoCorrWeightedFFT(1:AutoCorr%paddedLen,id) = AutoCorr%AutoCorrWeightedFFT(1:AutoCorr%paddedLen,id) / AutoCorr%AutoCorrWeightedFFT(1,id)
815 : end do
816 :
817 : ! Gfortran 7.1 fails to automatically allocate an allocatable version of these arrays
818 1 : if (allocated(Difference)) deallocate(Difference); allocate(Difference, mold = AutoCorr%AutoCorrWeightedFFT)
819 :
820 32771 : Difference = abs( AutoCorr%AutoCorrWeightedFFT - AutoCorr%AutoCorrFFT_ref )
821 32770 : assertion = assertion .and. all( Difference <= tolerance )
822 :
823 1 : if (Test%isDebugMode .and. .not. assertion) then
824 : ! LCOV_EXCL_START
825 :
826 : ! write data to output for further investigation
827 :
828 : open( file = Test%outDir//"/Test_CrossCorr_mod@WeightedData@AutoCorrFFT@Compact@getCrossCorrWeightedFFT."//num2str(Test%Image%id)//".out" & ! LCOV_EXCL_LINE
829 : , newunit = fileUnit & ! LCOV_EXCL_LINE
830 : , status = "replace" & ! LCOV_EXCL_LINE
831 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
832 : , SHARED & ! LCOV_EXCL_LINE
833 : #endif
834 : )
835 : do ip = 1, AutoCorr%paddedLen
836 : write(fileUnit,"(*(g0.15,:,' '))") ip-1, AutoCorr%AutoCorrWeightedFFT(ip,1)
837 : end do
838 : close(fileUnit)
839 :
840 : !allocate(DiffMaxLoc(WeightedData%nd))
841 : DiffMaxLoc = maxloc(Difference(1:AutoCorr%paddedLen,1:WeightedData%nd))
842 :
843 : write(Test%outputUnit,"(*(g0.15,:,' '))")
844 : write(Test%outputUnit,"(*(g0.15,:,' '))") "Stats at max difference:"
845 : write(Test%outputUnit,"(*(g0.15,:,' '))") "AutoCorr%AutoCorrFFT_ref =", AutoCorr%AutoCorrFFT_ref(DiffMaxLoc(1),1)
846 : write(Test%outputUnit,"(*(g0.15,:,' '))") "AutoCorr%AutoCorrWeightedFFT =", AutoCorr%AutoCorrWeightedFFT(DiffMaxLoc(1),1)
847 : write(Test%outputUnit,"(*(g0.15,:,' '))") "maxDifference =", Difference(DiffMaxLoc(1),1)
848 : write(Test%outputUnit,"(*(g0.15,:,' '))") "location =", DiffMaxLoc(1)
849 : write(Test%outputUnit,"(*(g0.15,:,' '))")
850 :
851 : end if
852 : ! LCOV_EXCL_STOP
853 :
854 1 : end function Test_getCrossCorrWeightedFFT_1
855 :
856 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
857 :
858 : ! Test AutoCorr computation for the verbose data, stored Compact Weighted format, using FFT.
859 1 : function Test_getCrossCorrWeightedFFT_2() result(assertion)
860 :
861 1 : use Statistics_mod, only: getNormData
862 : use Constants_mod, only: IK, RK
863 : use String_mod, only: num2str
864 : implicit none
865 : logical :: assertion, assertionCurrent
866 : real(RK) , allocatable :: Difference(:,:)
867 : real(RK) , parameter :: tolerance = 1.e-12_RK
868 : integer(IK) :: id, ip, fileUnit, ilag
869 :
870 1 : assertion = .true.
871 :
872 1 : call WeightedData%read()
873 :
874 : ! normalize data according to weights
875 :
876 9987 : WeightedData%NormedData = getNormData(WeightedData%nd, WeightedData%np, WeightedData%Data, WeightedData%Weight, tenabled = .true.)
877 9987 : AutoCorr%NormedDataFFT1 = WeightedData%NormedData
878 :
879 9986 : AutoCorr%paddedLen = getPaddedLen( sum(WeightedData%Weight) )
880 1 : if (allocated(AutoCorr%AutoCorrWeightedFFT)) deallocate(AutoCorr%AutoCorrWeightedFFT)
881 1 : allocate( AutoCorr%AutoCorrWeightedFFT(AutoCorr%paddedLen, WeightedData%nd) )
882 1 : if (allocated(AutoCorr%AutoCorrFFT_ref)) deallocate(AutoCorr%AutoCorrFFT_ref)
883 1 : allocate( AutoCorr%AutoCorrFFT_ref(AutoCorr%paddedLen, WeightedData%nd) )
884 2 : do id = 1, WeightedData%nd
885 :
886 : AutoCorr%AutoCorrWeightedFFT(1:AutoCorr%paddedLen,id) = getCrossCorrWeightedFFT ( lenCompactData1 = WeightedData%np & ! LCOV_EXCL_LINE
887 : , lenCompactData2 = WeightedData%np & ! LCOV_EXCL_LINE
888 : , paddedLen = AutoCorr%paddedLen & ! LCOV_EXCL_LINE
889 : , CompactData1 = WeightedData%NormedData(1:WeightedData%np,id) & ! LCOV_EXCL_LINE
890 : , CompactData2 = WeightedData%NormedData(1:WeightedData%np,id) & ! LCOV_EXCL_LINE
891 : , Weight1 = WeightedData%Weight(1:WeightedData%np) & ! LCOV_EXCL_LINE
892 : , Weight2 = WeightedData%Weight(1:WeightedData%np) & ! LCOV_EXCL_LINE
893 131073 : )
894 131073 : AutoCorr%AutoCorrWeightedFFT(1:AutoCorr%paddedLen,id) = AutoCorr%AutoCorrWeightedFFT(1:AutoCorr%paddedLen,id) / AutoCorr%AutoCorrWeightedFFT(1,id)
895 :
896 : ! ensure NormedData does not change upon entering and exiting getCrossCorrFFT()
897 :
898 9987 : do ip = 1, WeightedData%np
899 9985 : assertionCurrent = AutoCorr%NormedDataFFT1(ip,id) == WeightedData%NormedData(ip,id)
900 9985 : assertion = assertion .and. assertionCurrent
901 9986 : if (Test%isDebugMode .and. .not. assertionCurrent) then
902 : ! LCOV_EXCL_START
903 : write(Test%outputUnit,"(*(g0.15,:,' '))") "Nonsense. These two must be equal ", ip, id, WeightedData%NormedData(ip,id), AutoCorr%NormedDataFFT1(ip,id)
904 : end if
905 : ! LCOV_EXCL_STOP
906 : end do
907 :
908 : end do
909 :
910 : ! read reference AutoCorrFFT_ref from the input data
911 :
912 : open( file = Test%inDir//"/Test_CrossCorr_mod@WeightedData@AutoCorrFFT@Verbose.txt" & ! LCOV_EXCL_LINE
913 : , newunit = fileUnit & ! LCOV_EXCL_LINE
914 : , status = "old" & ! LCOV_EXCL_LINE
915 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
916 : , SHARED & ! LCOV_EXCL_LINE
917 : #endif
918 1 : )
919 131073 : do ip = 1, AutoCorr%paddedLen
920 131073 : read(fileUnit,*) ilag, AutoCorr%AutoCorrFFT_ref(ip,1)
921 : end do
922 1 : close(fileUnit)
923 :
924 : ! Gfortran 7.1 fails to automatically reallocate this array. This is not implemented in Gfortran 7.0.0
925 1 : if (allocated(Difference)) deallocate(Difference); allocate(Difference, mold = AutoCorr%AutoCorrWeightedFFT)
926 :
927 131075 : Difference = abs( AutoCorr%AutoCorrWeightedFFT - AutoCorr%AutoCorrFFT_ref )
928 131074 : assertion = assertion .and. all( Difference <= tolerance )
929 :
930 : ! LCOV_EXCL_START
931 : if (Test%isDebugMode .and. .not. assertion) then
932 :
933 : ! write data to output for further investigation
934 :
935 : open( file = Test%outDir//"/Test_CrossCorr_mod@WeightedData@AutoCorrFFT@Verbose@getCrossCorrWeightedFFT."//num2str(Test%Image%id)//".out" & ! LCOV_EXCL_LINE
936 : , newunit = fileUnit & ! LCOV_EXCL_LINE
937 : , status = "replace" & ! LCOV_EXCL_LINE
938 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
939 : , SHARED & ! LCOV_EXCL_LINE
940 : #endif
941 : )
942 : do ip = 1, AutoCorr%paddedLen
943 : write(fileUnit,"(*(g0.15,:,' '))") ip-1, AutoCorr%AutoCorrWeightedFFT(ip,1)
944 : end do
945 : close(fileUnit)
946 :
947 : end if
948 : ! LCOV_EXCL_STOP
949 :
950 1 : end function Test_getCrossCorrWeightedFFT_2
951 :
952 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
953 :
954 : ! Test the AutoCorr computation using FFT for an input identity data vector with a weight vector of ones.
955 1 : function Test_getCrossCorrWeightedFFT_3() result(assertion)
956 :
957 1 : use Statistics_mod, only: getNormData
958 : use Constants_mod, only: IK, RK
959 : use String_mod, only: num2str
960 : implicit none
961 : logical :: assertion, assertionCurrent
962 : real(RK) , allocatable :: Difference(:,:)
963 : real(RK) , parameter :: tolerance = 1.e-12_RK
964 : integer(IK) :: id, ip, fileUnit, ilag
965 :
966 1 : assertion = .true.
967 :
968 1 : call WeightedData%read()
969 :
970 : ! normalize data
971 :
972 1 : WeightedData%nd = 1
973 1 : WeightedData%np = 100
974 1 : if (allocated(WeightedData%Data)) deallocate(WeightedData%Data)
975 1 : if (allocated(WeightedData%Weight)) deallocate(WeightedData%Weight)
976 1 : if (allocated(WeightedData%NormedData)) deallocate(WeightedData%NormedData)
977 1 : if (allocated(AutoCorr%NormedDataFFT1)) deallocate(AutoCorr%NormedDataFFT1)
978 1 : allocate( WeightedData%Data(WeightedData%nd,WeightedData%np), WeightedData%Weight(WeightedData%np) )
979 1 : allocate( WeightedData%NormedData(WeightedData%nd,WeightedData%np), AutoCorr%NormedDataFFT1(WeightedData%np,WeightedData%nd) )
980 201 : WeightedData%Data = 1._RK
981 1 : WeightedData%Data(1,WeightedData%np) = .999999_RK
982 101 : WeightedData%Weight = 1_IK
983 102 : WeightedData%NormedData = getNormData(WeightedData%nd, WeightedData%np, WeightedData%Data, WeightedData%Weight, tenabled = .true.)
984 103 : AutoCorr%NormedDataFFT1 = WeightedData%NormedData
985 :
986 101 : AutoCorr%paddedLen = getPaddedLen(sum(WeightedData%Weight))
987 1 : if (allocated(AutoCorr%AutoCorrWeightedFFT)) deallocate(AutoCorr%AutoCorrWeightedFFT)
988 1 : allocate(AutoCorr%AutoCorrWeightedFFT(AutoCorr%paddedLen,WeightedData%nd))
989 2 : do id = 1, WeightedData%nd
990 :
991 : AutoCorr%AutoCorrWeightedFFT(1:AutoCorr%paddedLen,id) = getCrossCorrWeightedFFT ( lenCompactData1 = WeightedData%np & ! LCOV_EXCL_LINE
992 : , lenCompactData2 = WeightedData%np & ! LCOV_EXCL_LINE
993 : , paddedLen = AutoCorr%paddedLen & ! LCOV_EXCL_LINE
994 : , CompactData1 = WeightedData%NormedData(1:WeightedData%np,id) & ! LCOV_EXCL_LINE
995 : , CompactData2 = WeightedData%NormedData(1:WeightedData%np,id) & ! LCOV_EXCL_LINE
996 : , Weight1 = WeightedData%Weight(1:WeightedData%np) & ! LCOV_EXCL_LINE
997 : , Weight2 = WeightedData%Weight(1:WeightedData%np) & ! LCOV_EXCL_LINE
998 257 : )
999 257 : AutoCorr%AutoCorrWeightedFFT(1:AutoCorr%paddedLen,id) = AutoCorr%AutoCorrWeightedFFT(1:AutoCorr%paddedLen,id) / AutoCorr%AutoCorrWeightedFFT(1,id)
1000 :
1001 : ! ensure NormedData does not change upon entering and exiting getCrossCorrFFT()
1002 :
1003 102 : do ip = 1, WeightedData%np
1004 100 : assertionCurrent = AutoCorr%NormedDataFFT1(ip,id) == WeightedData%NormedData(ip,id)
1005 100 : assertion = assertion .and. assertionCurrent
1006 101 : if (Test%isDebugMode .and. .not. assertionCurrent) then
1007 : ! LCOV_EXCL_START
1008 : write(Test%outputUnit,"(*(g0.15,:,' '))") "Nonsense. These two must be equal ", ip, id, WeightedData%NormedData(ip,id), AutoCorr%NormedDataFFT1(ip,id)
1009 : end if
1010 : ! LCOV_EXCL_STOP
1011 : end do
1012 :
1013 : end do
1014 :
1015 : ! read reference AutoCorrFFT_ref from the input data
1016 :
1017 1 : if (allocated(AutoCorr%AutoCorrFFT_ref)) deallocate(AutoCorr%AutoCorrFFT_ref)
1018 1 : allocate( AutoCorr%AutoCorrFFT_ref(AutoCorr%paddedLen, WeightedData%nd) )
1019 : open( file = Test%inDir//"/Test_CrossCorr_mod@AutoCorrFFT@Identity.txt" & ! LCOV_EXCL_LINE
1020 : , newunit = fileUnit & ! LCOV_EXCL_LINE
1021 : , status = "old" & ! LCOV_EXCL_LINE
1022 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
1023 : , SHARED & ! LCOV_EXCL_LINE
1024 : #endif
1025 1 : )
1026 257 : do ip = 1, AutoCorr%paddedLen
1027 257 : read(fileUnit,*) ilag, AutoCorr%AutoCorrFFT_ref(ip,1)
1028 : end do
1029 1 : close(fileUnit)
1030 :
1031 : ! Gfortran 7.1 fails to automatically reallocate this array. This is not implemented in Gfortran 7.0.0
1032 1 : if (allocated(Difference)) deallocate(Difference); allocate(Difference, mold = AutoCorr%AutoCorrWeightedFFT)
1033 :
1034 259 : Difference = abs( AutoCorr%AutoCorrWeightedFFT - AutoCorr%AutoCorrFFT_ref )
1035 258 : assertion = assertion .and. all( Difference <= tolerance )
1036 :
1037 1 : if (Test%isDebugMode .and. .not. assertion) then
1038 : ! LCOV_EXCL_START
1039 :
1040 : ! write data to output for further investigation
1041 :
1042 : open( file = Test%outDir//"/Test_CrossCorr_mod@AutoCorrFFT@Identity@getCrossCorrWeightedFFT."//num2str(Test%Image%id)//".out" & ! LCOV_EXCL_LINE
1043 : , newunit = fileUnit & ! LCOV_EXCL_LINE
1044 : , status="replace" & ! LCOV_EXCL_LINE
1045 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
1046 : , SHARED & ! LCOV_EXCL_LINE
1047 : #endif
1048 : )
1049 : do ip = 1, AutoCorr%paddedLen
1050 : write(fileUnit,"(*(g0.15,:,' '))") ip-1, AutoCorr%AutoCorrWeightedFFT(ip,1)
1051 : end do
1052 : close(fileUnit)
1053 :
1054 : end if
1055 : ! LCOV_EXCL_STOP
1056 :
1057 1 : end function Test_getCrossCorrWeightedFFT_3
1058 :
1059 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1060 :
1061 1 : function Test_getCumSumIAC_1() result(assertion)
1062 1 : use Constants_mod, only: RK
1063 : implicit none
1064 : logical :: assertion
1065 1 : real(RK) :: difference
1066 1 : real(RK) :: cumSumIAC
1067 : real(RK), parameter :: cumSumIAC_ref = 45.0461450858553_RK
1068 : real(RK), parameter :: tolerance = 1.e-12_RK
1069 1 : call WeightedData%read()
1070 1 : cumSumIAC = getCumSumIAC(np = WeightedData%np, Point = WeightedData%Data)
1071 1 : difference = abs( (cumSumIAC - cumSumIAC_ref) / cumSumIAC_ref)
1072 1 : assertion = difference < tolerance
1073 1 : if (Test%isDebugMode .and. .not. assertion) then
1074 : ! LCOV_EXCL_START
1075 : write(Test%outputUnit,"(*(g0.15,:,' '))")
1076 : write(Test%outputUnit,"(*(g0.15,:,' '))") "cumSumIAC_ref =", cumSumIAC_ref
1077 : write(Test%outputUnit,"(*(g0.15,:,' '))") "cumSumIAC =", cumSumIAC
1078 : write(Test%outputUnit,"(*(g0.15,:,' '))") "difference =", difference
1079 : write(Test%outputUnit,"(*(g0.15,:,' '))")
1080 : end if
1081 : ! LCOV_EXCL_STOP
1082 1 : end function Test_getCumSumIAC_1
1083 :
1084 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1085 :
1086 1 : function Test_getCumSumIAC_2() result(assertion)
1087 1 : use Constants_mod, only: RK
1088 : implicit none
1089 : logical :: assertion
1090 1 : real(RK) :: difference
1091 1 : real(RK) :: cumSumIAC
1092 : real(RK), parameter :: cumSumIAC_ref = 240.805734399049_RK
1093 : real(RK), parameter :: tolerance = 1.e-12_RK
1094 1 : call WeightedData%read()
1095 1 : cumSumIAC = getCumSumIAC(np = WeightedData%np, Point = WeightedData%Data, Weight = WeightedData%Weight)
1096 1 : difference = abs( (cumSumIAC - cumSumIAC_ref) / cumSumIAC_ref)
1097 1 : assertion = difference < tolerance
1098 1 : if (Test%isDebugMode .and. .not. assertion) then
1099 : ! LCOV_EXCL_START
1100 : write(Test%outputUnit,"(*(g0.15,:,' '))")
1101 : write(Test%outputUnit,"(*(g0.15,:,' '))") "cumSumIAC_ref =", cumSumIAC_ref
1102 : write(Test%outputUnit,"(*(g0.15,:,' '))") "cumSumIAC =", cumSumIAC
1103 : write(Test%outputUnit,"(*(g0.15,:,' '))") "difference =", difference
1104 : write(Test%outputUnit,"(*(g0.15,:,' '))")
1105 : end if
1106 : ! LCOV_EXCL_STOP
1107 1 : end function Test_getCumSumIAC_2
1108 :
1109 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1110 :
1111 1 : function Test_getCumSumIAC_3() result(assertion)
1112 1 : use Constants_mod, only: RK
1113 : implicit none
1114 : logical :: assertion
1115 1 : real(RK) :: difference
1116 1 : real(RK) :: cumSumIAC
1117 : real(RK), parameter :: significance = 1._RK
1118 : real(RK), parameter :: cumSumIAC_ref = 240.864727585537_RK
1119 : real(RK), parameter :: tolerance = 1.e-12_RK
1120 1 : call WeightedData%read()
1121 1 : cumSumIAC = getCumSumIAC(np = WeightedData%np, Point = WeightedData%Data, Weight = WeightedData%Weight, significance = significance)
1122 1 : difference = abs( (cumSumIAC - cumSumIAC_ref) / cumSumIAC_ref)
1123 1 : assertion = difference < tolerance
1124 1 : if (Test%isDebugMode .and. .not. assertion) then
1125 : ! LCOV_EXCL_START
1126 : write(Test%outputUnit,"(*(g0.15,:,' '))")
1127 : write(Test%outputUnit,"(*(g0.15,:,' '))") "cumSumIAC_ref =", cumSumIAC_ref
1128 : write(Test%outputUnit,"(*(g0.15,:,' '))") "cumSumIAC =", cumSumIAC
1129 : write(Test%outputUnit,"(*(g0.15,:,' '))") "difference =", difference
1130 : write(Test%outputUnit,"(*(g0.15,:,' '))")
1131 : end if
1132 : ! LCOV_EXCL_STOP
1133 1 : end function Test_getCumSumIAC_3
1134 :
1135 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1136 :
1137 1 : function Test_getMaxCumSumIAC_1() result(assertion)
1138 1 : use Constants_mod, only: RK
1139 : implicit none
1140 : logical :: assertion
1141 1 : real(RK) :: difference
1142 1 : real(RK) :: maxCumSumIAC
1143 : real(RK), parameter :: maxCumSumIAC_ref = 276.9829480126210_RK
1144 : real(RK), parameter :: tolerance = 1.e-12_RK
1145 1 : call WeightedData%read()
1146 1 : maxCumSumIAC = getMaxCumSumIAC(np = WeightedData%np, Point = WeightedData%Data)
1147 1 : difference = abs( (maxCumSumIAC - maxCumSumIAC_ref) / maxCumSumIAC_ref)
1148 1 : assertion = difference < tolerance
1149 1 : if (Test%isDebugMode .and. .not. assertion) then
1150 : ! LCOV_EXCL_START
1151 : write(Test%outputUnit,"(*(g0.15,:,' '))")
1152 : write(Test%outputUnit,"(*(g0.15,:,' '))") "maxCumSumIAC_ref =", maxCumSumIAC_ref
1153 : write(Test%outputUnit,"(*(g0.15,:,' '))") "maxCumSumIAC =", maxCumSumIAC
1154 : write(Test%outputUnit,"(*(g0.15,:,' '))") "difference =", difference
1155 : write(Test%outputUnit,"(*(g0.15,:,' '))")
1156 : end if
1157 : ! LCOV_EXCL_STOP
1158 1 : end function Test_getMaxCumSumIAC_1
1159 :
1160 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1161 :
1162 1 : function Test_getMaxCumSumIAC_2() result(assertion)
1163 1 : use Constants_mod, only: RK
1164 : implicit none
1165 : logical :: assertion
1166 1 : real(RK) :: difference
1167 1 : real(RK) :: maxCumSumIAC
1168 : real(RK), parameter :: maxCumSumIAC_ref = 1111.683837194696_RK
1169 : real(RK), parameter :: tolerance = 1.e-12_RK
1170 1 : call WeightedData%read()
1171 1 : maxCumSumIAC = getMaxCumSumIAC(np = WeightedData%np, Point = WeightedData%Data, Weight = WeightedData%Weight)
1172 1 : difference = abs( (maxCumSumIAC - maxCumSumIAC_ref) / maxCumSumIAC_ref)
1173 1 : assertion = difference < tolerance
1174 1 : if (Test%isDebugMode .and. .not. assertion) then
1175 : ! LCOV_EXCL_START
1176 : write(Test%outputUnit,"(*(g0.15,:,' '))")
1177 : write(Test%outputUnit,"(*(g0.15,:,' '))") "maxCumSumIAC_ref =", maxCumSumIAC_ref
1178 : write(Test%outputUnit,"(*(g0.15,:,' '))") "maxCumSumIAC =", maxCumSumIAC
1179 : write(Test%outputUnit,"(*(g0.15,:,' '))") "difference =", difference
1180 : write(Test%outputUnit,"(*(g0.15,:,' '))")
1181 : end if
1182 : ! LCOV_EXCL_STOP
1183 1 : end function Test_getMaxCumSumIAC_2
1184 :
1185 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1186 :
1187 1 : function Test_getBatchMeansIAC_1() result(assertion)
1188 1 : use Constants_mod, only: RK
1189 : implicit none
1190 : logical :: assertion
1191 1 : real(RK) :: difference
1192 1 : real(RK) :: batchMeansIAC
1193 : real(RK), parameter :: batchMeansIAC_ref = 52.5214820575914_RK
1194 : real(RK), parameter :: tolerance = 1.e-12_RK
1195 1 : call WeightedData%read()
1196 1 : batchMeansIAC = getBatchMeansIAC(np = WeightedData%np, Point = WeightedData%Data)
1197 1 : difference = abs( (batchMeansIAC - batchMeansIAC_ref) / batchMeansIAC_ref)
1198 1 : assertion = difference < tolerance
1199 1 : if (Test%isDebugMode .and. .not. assertion) then
1200 : ! LCOV_EXCL_START
1201 : write(Test%outputUnit,"(*(g0.15,:,' '))")
1202 : write(Test%outputUnit,"(*(g0.15,:,' '))") "batchMeansIAC_ref =", batchMeansIAC_ref
1203 : write(Test%outputUnit,"(*(g0.15,:,' '))") "batchMeansIAC =", batchMeansIAC
1204 : write(Test%outputUnit,"(*(g0.15,:,' '))") "difference =", difference
1205 : write(Test%outputUnit,"(*(g0.15,:,' '))")
1206 : end if
1207 : ! LCOV_EXCL_STOP
1208 1 : end function Test_getBatchMeansIAC_1
1209 :
1210 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1211 :
1212 1 : function Test_getBatchMeansIAC_2() result(assertion)
1213 1 : use Constants_mod, only: RK
1214 : implicit none
1215 : logical :: assertion
1216 1 : real(RK) :: difference
1217 1 : real(RK) :: batchMeansIAC
1218 : real(RK), parameter :: batchMeansIAC_ref = 190.438982011941_RK
1219 : real(RK), parameter :: tolerance = 1.e-12_RK
1220 1 : call WeightedData%read()
1221 1 : batchMeansIAC = getBatchMeansIAC(np = WeightedData%np, Point = WeightedData%Data, Weight = WeightedData%Weight)
1222 1 : difference = abs( (batchMeansIAC - batchMeansIAC_ref) / batchMeansIAC_ref)
1223 1 : assertion = difference < tolerance
1224 1 : if (Test%isDebugMode .and. .not. assertion) then
1225 : ! LCOV_EXCL_START
1226 : write(Test%outputUnit,"(*(g0.15,:,' '))")
1227 : write(Test%outputUnit,"(*(g0.15,:,' '))") "batchMeansIAC_ref =", batchMeansIAC_ref
1228 : write(Test%outputUnit,"(*(g0.15,:,' '))") "batchMeansIAC =", batchMeansIAC
1229 : write(Test%outputUnit,"(*(g0.15,:,' '))") "difference =", difference
1230 : write(Test%outputUnit,"(*(g0.15,:,' '))")
1231 : end if
1232 : ! LCOV_EXCL_STOP
1233 1 : end function Test_getBatchMeansIAC_2
1234 :
1235 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1236 :
1237 1 : function Test_getBatchMeansIAC_3() result(assertion)
1238 1 : use Constants_mod, only: RK
1239 : implicit none
1240 : logical :: assertion
1241 1 : real(RK) :: difference
1242 1 : real(RK) :: batchMeansIAC
1243 : real(RK) , parameter :: batchMeansIAC_ref = 66.8090158674070_RK
1244 : real(RK) , parameter :: tolerance = 1.e-12_RK
1245 : integer(IK) , parameter :: batchSize = 100_IK
1246 1 : call WeightedData%read()
1247 1 : batchMeansIAC = getBatchMeansIAC(np = WeightedData%np, Point = WeightedData%Data, Weight = WeightedData%Weight, batchSize = batchSize)
1248 1 : difference = abs( (batchMeansIAC - batchMeansIAC_ref) / batchMeansIAC_ref)
1249 1 : assertion = difference < tolerance
1250 1 : if (Test%isDebugMode .and. .not. assertion) then
1251 : ! LCOV_EXCL_START
1252 : write(Test%outputUnit,"(*(g0.15,:,' '))")
1253 : write(Test%outputUnit,"(*(g0.15,:,' '))") "batchMeansIAC_ref =", batchMeansIAC_ref
1254 : write(Test%outputUnit,"(*(g0.15,:,' '))") "batchMeansIAC =", batchMeansIAC
1255 : write(Test%outputUnit,"(*(g0.15,:,' '))") "difference =", difference
1256 : write(Test%outputUnit,"(*(g0.15,:,' '))")
1257 : end if
1258 : ! LCOV_EXCL_STOP
1259 1 : end function Test_getBatchMeansIAC_3
1260 :
1261 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1262 :
1263 : end module Test_CrossCorr_mod ! LCOV_EXCL_LINE
|