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 [Err_mod](@ref err_mod).
44 : !> \author Amir Shahmoradi
45 :
46 : module Test_Err_mod
47 :
48 : use Err_mod
49 : use Decoration_mod, only: TAB
50 : use Test_mod, only: Test_type
51 : implicit none
52 :
53 : private
54 : public :: test_Err
55 :
56 : type(Test_type) :: Test
57 :
58 : character(*), parameter :: mc_prefix = TAB//TAB//"ParaMonte"
59 : character(*), parameter :: mc_msg = "What does a fish know about the water in which it swims all its life? Albert Einstein\n" // &
60 : "Everything should be made as simple as possible, but not simpler. Albert Einstein\n" // &
61 : "The absence of evidence is not evidence for absence. Carl Sagan\n" // &
62 : "If I have seen further, it is by standing on the shoulders of giants. Isaac Newton\n" // &
63 : "I don't pretend to understand the universe - it's much bigger than I am. Thomas Carlyle"
64 :
65 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
66 :
67 : contains
68 :
69 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
70 :
71 3 : subroutine test_Err()
72 :
73 : implicit none
74 :
75 3 : Test = Test_type(moduleName=MODULE_NAME)
76 3 : call Test%run(test_note_1, "test_note_1")
77 3 : call Test%run(test_note_2, "test_note_2")
78 3 : call Test%run(test_warn_1, "test_warn_1")
79 3 : call Test%run(test_warn_2, "test_warn_2")
80 3 : call Test%run(test_abort_1, "test_abort_1")
81 3 : call Test%run(test_abort_2, "test_abort_2")
82 3 : call Test%finalize()
83 :
84 3 : end subroutine test_Err
85 :
86 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
87 :
88 3 : function test_note_1() result(assertion)
89 :
90 3 : use JaggedArray_mod, only: CharVec_type
91 : use Constants_mod, only: IK
92 : use String_mod, only: num2str
93 :
94 : implicit none
95 :
96 : integer(IK) :: fileUnit, i, iostat
97 : logical :: assertion, assertionCurrent
98 : integer(IK), parameter :: NLINE = 5_IK
99 3 : type(CharVec_type), allocatable :: OutputList_ref(:)
100 3 : type(CharVec_type), allocatable :: OutputList(:)
101 :
102 3 : assertion = .true.
103 :
104 18 : if (allocated(OutputList)) deallocate(OutputList); allocate(OutputList(NLINE))
105 18 : if (allocated(OutputList_ref)) deallocate(OutputList_ref); allocate(OutputList_ref(NLINE))
106 :
107 3 : OutputList_ref(1)%record = " ParaMonte - NOTE: What does a fish know about the water in which it swims all its life? Albert Einstein"
108 3 : OutputList_ref(2)%record = " ParaMonte - NOTE: Everything should be made as simple as possible, but not simpler. Albert Einstein"
109 3 : OutputList_ref(3)%record = " ParaMonte - NOTE: The absence of evidence is not evidence for absence. Carl Sagan"
110 3 : OutputList_ref(4)%record = " ParaMonte - NOTE: If I have seen further, it is by standing on the shoulders of giants. Isaac Newton"
111 3 : OutputList_ref(5)%record = " ParaMonte - NOTE: I don't pretend to understand the universe - it's much bigger than I am. Thomas Carlyle"
112 :
113 3 : open(newunit = fileUnit, status = "scratch")
114 : !open(newunit = fileUnit, file = Test%outDir//"/Test_Err_mod@test_note_1."//num2str(Test%Image%id)//".out", status = "replace")
115 :
116 : call note ( msg = mc_msg &
117 : , prefix = mc_prefix &
118 : , newline = "\n" &
119 : , outputUnit = fileUnit &
120 : , marginTop = 0_IK &
121 : , marginBot = 0_IK &
122 3 : )
123 :
124 3 : rewind(fileUnit)
125 :
126 18 : do i = 1, NLINE
127 :
128 15 : if(allocated(OutputList(i)%record)) deallocate(OutputList(i)%record)
129 15 : allocate(character(132) :: OutputList(i)%record)
130 :
131 15 : read(fileUnit,"(A132)", iostat = iostat) OutputList(i)%record
132 15 : assertion = iostat == 0_IK
133 : if (.not. assertion) return ! LCOV_EXCL_LINE
134 :
135 15 : OutputList(i)%record = trim(OutputList(i)%record)
136 :
137 15 : assertionCurrent = OutputList(i)%record == OutputList_ref(i)%record
138 15 : assertion = assertion .and. assertionCurrent
139 :
140 18 : if (Test%isDebugMode .and. .not. assertionCurrent) then
141 : ! LCOV_EXCL_START
142 : write(Test%outputUnit,"(*(g0))")
143 : write(Test%outputUnit,"(*(g0))") "OutputList_ref(",num2str(i),")%record = ", OutputList_ref(i)%record
144 : write(Test%outputUnit,"(*(g0))") "OutputList (",num2str(i),")%record = ", OutputList(i)%record
145 : write(Test%outputUnit,"(*(g0))")
146 : end if
147 : ! LCOV_EXCL_STOP
148 :
149 : end do
150 :
151 33 : end function test_note_1
152 :
153 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
154 :
155 3 : function test_note_2() result(assertion)
156 :
157 3 : use JaggedArray_mod, only: CharVec_type
158 : use Constants_mod, only: IK, NLC
159 : use String_mod, only: num2str, replaceStr
160 :
161 : implicit none
162 :
163 : integer(IK) :: fileUnit, i, iostat
164 : logical :: assertion, assertionCurrent
165 : integer(IK), parameter :: NLINE = 7_IK
166 3 : type(CharVec_type), allocatable :: OutputList_ref(:)
167 3 : type(CharVec_type), allocatable :: OutputList(:)
168 :
169 3 : assertion = .true.
170 :
171 24 : if (allocated(OutputList)) deallocate(OutputList); allocate(OutputList(NLINE))
172 24 : if (allocated(OutputList_ref)) deallocate(OutputList_ref); allocate(OutputList_ref(NLINE))
173 :
174 3 : OutputList_ref(1)%record = ""
175 3 : OutputList_ref(2)%record = " - NOTE: What does a fish know about the water in which it swims all its life? Albert Einstein"
176 3 : OutputList_ref(3)%record = " - NOTE: Everything should be made as simple as possible, but not simpler. Albert Einstein"
177 3 : OutputList_ref(4)%record = " - NOTE: The absence of evidence is not evidence for absence. Carl Sagan"
178 3 : OutputList_ref(5)%record = " - NOTE: If I have seen further, it is by standing on the shoulders of giants. Isaac Newton"
179 3 : OutputList_ref(6)%record = " - NOTE: I don't pretend to understand the universe - it's much bigger than I am. Thomas Carlyle"
180 3 : OutputList_ref(7)%record = ""
181 :
182 3 : open(newunit = fileUnit, status = "scratch")
183 : !open(newunit = fileUnit, file = Test%outDir//"/Test_Err_mod@test_note_2."//num2str(Test%Image%id)//".out", status = "replace")
184 :
185 3 : call note ( msg = replaceStr(mc_msg, "\n", NLC) &
186 : , outputUnit = fileUnit &
187 : , newline = NLC &
188 6 : )
189 :
190 3 : rewind(fileUnit)
191 :
192 24 : do i = 1, NLINE
193 :
194 21 : if(allocated(OutputList(i)%record)) deallocate(OutputList(i)%record)
195 21 : allocate(character(132) :: OutputList(i)%record)
196 :
197 21 : read(fileUnit,"(A132)", iostat = iostat) OutputList(i)%record
198 21 : assertion = iostat == 0_IK
199 : if (.not. assertion) return ! LCOV_EXCL_LINE
200 :
201 21 : OutputList(i)%record = trim(OutputList(i)%record)
202 :
203 21 : assertionCurrent = OutputList(i)%record == OutputList_ref(i)%record
204 21 : assertion = assertion .and. assertionCurrent
205 :
206 24 : if (Test%isDebugMode .and. .not. assertionCurrent) then
207 : ! LCOV_EXCL_START
208 : write(Test%outputUnit,"(*(g0))")
209 : write(Test%outputUnit,"(*(g0))") "OutputList_ref(",num2str(i),")%record = ", OutputList_ref(i)%record
210 : write(Test%outputUnit,"(*(g0))") "OutputList (",num2str(i),")%record = ", OutputList(i)%record
211 : write(Test%outputUnit,"(*(g0))")
212 : end if
213 : ! LCOV_EXCL_STOP
214 :
215 : end do
216 :
217 45 : end function test_note_2
218 :
219 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
220 :
221 3 : function test_warn_1() result(assertion)
222 :
223 3 : use JaggedArray_mod, only: CharVec_type
224 : use Constants_mod, only: IK
225 : use String_mod, only: num2str
226 :
227 : implicit none
228 :
229 : integer(IK) :: fileUnit, i, iostat
230 : logical :: assertion, assertionCurrent
231 : integer(IK), parameter :: NLINE = 5_IK
232 3 : type(CharVec_type), allocatable :: OutputList_ref(:)
233 3 : type(CharVec_type), allocatable :: OutputList(:)
234 :
235 3 : assertion = .true.
236 :
237 18 : if (allocated(OutputList)) deallocate(OutputList); allocate(OutputList(NLINE))
238 18 : if (allocated(OutputList_ref)) deallocate(OutputList_ref); allocate(OutputList_ref(NLINE))
239 :
240 3 : OutputList_ref(1)%record = " ParaMonte - WARNING: What does a fish know about the water in which it swims all its life? Albert Einstein"
241 3 : OutputList_ref(2)%record = " ParaMonte - WARNING: Everything should be made as simple as possible, but not simpler. Albert Einstein"
242 3 : OutputList_ref(3)%record = " ParaMonte - WARNING: The absence of evidence is not evidence for absence. Carl Sagan"
243 3 : OutputList_ref(4)%record = " ParaMonte - WARNING: If I have seen further, it is by standing on the shoulders of giants. Isaac Newton"
244 3 : OutputList_ref(5)%record = " ParaMonte - WARNING: I don't pretend to understand the universe - it's much bigger than I am. Thomas Carlyle"
245 :
246 3 : open(newunit = fileUnit, status = "scratch")
247 : !open(newunit = fileUnit, file = Test%outDir//"/Test_Err_mod@test_warn_1."//num2str(Test%Image%id)//".out", status = "replace")
248 :
249 : call warn ( msg = mc_msg &
250 : , prefix = mc_prefix &
251 : , newline = "\n" &
252 : , outputUnit = fileUnit &
253 : , marginTop = 0_IK &
254 : , marginBot = 0_IK &
255 3 : )
256 :
257 3 : rewind(fileUnit)
258 :
259 18 : do i = 1, NLINE
260 :
261 15 : if(allocated(OutputList(i)%record)) deallocate(OutputList(i)%record)
262 15 : allocate(character(132) :: OutputList(i)%record)
263 :
264 15 : read(fileUnit,"(A132)", iostat = iostat) OutputList(i)%record
265 15 : assertion = iostat == 0_IK
266 : if (.not. assertion) return ! LCOV_EXCL_LINE
267 :
268 15 : OutputList(i)%record = trim(OutputList(i)%record)
269 :
270 15 : assertionCurrent = OutputList(i)%record == OutputList_ref(i)%record
271 15 : assertion = assertion .and. assertionCurrent
272 :
273 18 : if (Test%isDebugMode .and. .not. assertionCurrent) then
274 : ! LCOV_EXCL_START
275 : write(Test%outputUnit,"(*(g0))")
276 : write(Test%outputUnit,"(*(g0))") "OutputList_ref(",num2str(i),")%record = ", OutputList_ref(i)%record
277 : write(Test%outputUnit,"(*(g0))") "OutputList (",num2str(i),")%record = ", OutputList(i)%record
278 : write(Test%outputUnit,"(*(g0))")
279 : end if
280 : ! LCOV_EXCL_STOP
281 :
282 : end do
283 :
284 33 : end function test_warn_1
285 :
286 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
287 :
288 3 : function test_warn_2() result(assertion)
289 :
290 3 : use JaggedArray_mod, only: CharVec_type
291 : use Constants_mod, only: IK, NLC
292 : use String_mod, only: num2str, replaceStr
293 :
294 : implicit none
295 :
296 : integer(IK) :: fileUnit, i, iostat
297 : logical :: assertion, assertionCurrent
298 : integer(IK), parameter :: NLINE = 7_IK
299 3 : type(CharVec_type), allocatable :: OutputList_ref(:)
300 3 : type(CharVec_type), allocatable :: OutputList(:)
301 :
302 3 : assertion = .true.
303 :
304 24 : if (allocated(OutputList)) deallocate(OutputList); allocate(OutputList(NLINE))
305 24 : if (allocated(OutputList_ref)) deallocate(OutputList_ref); allocate(OutputList_ref(NLINE))
306 :
307 3 : OutputList_ref(1)%record = ""
308 3 : OutputList_ref(2)%record = " - WARNING: What does a fish know about the water in which it swims all its life? Albert Einstein"
309 3 : OutputList_ref(3)%record = " - WARNING: Everything should be made as simple as possible, but not simpler. Albert Einstein"
310 3 : OutputList_ref(4)%record = " - WARNING: The absence of evidence is not evidence for absence. Carl Sagan"
311 3 : OutputList_ref(5)%record = " - WARNING: If I have seen further, it is by standing on the shoulders of giants. Isaac Newton"
312 3 : OutputList_ref(6)%record = " - WARNING: I don't pretend to understand the universe - it's much bigger than I am. Thomas Carlyle"
313 3 : OutputList_ref(7)%record = ""
314 :
315 3 : open(newunit = fileUnit, status = "scratch")
316 : !open(newunit = fileUnit, file = Test%outDir//"/Test_Err_mod@test_warn_2."//num2str(Test%Image%id)//".out", status = "replace")
317 :
318 3 : call warn ( msg = replaceStr(mc_msg, "\n", NLC) &
319 : , outputUnit = fileUnit &
320 : , newline = NLC &
321 6 : )
322 :
323 3 : rewind(fileUnit)
324 :
325 24 : do i = 1, NLINE
326 :
327 21 : if(allocated(OutputList(i)%record)) deallocate(OutputList(i)%record)
328 21 : allocate(character(132) :: OutputList(i)%record)
329 :
330 21 : read(fileUnit,"(A132)", iostat = iostat) OutputList(i)%record
331 21 : assertion = iostat == 0_IK
332 : if (.not. assertion) return ! LCOV_EXCL_LINE
333 :
334 21 : OutputList(i)%record = trim(OutputList(i)%record)
335 :
336 21 : assertionCurrent = OutputList(i)%record == OutputList_ref(i)%record
337 21 : assertion = assertion .and. assertionCurrent
338 :
339 24 : if (Test%isDebugMode .and. .not. assertionCurrent) then
340 : ! LCOV_EXCL_START
341 : write(Test%outputUnit,"(*(g0))")
342 : write(Test%outputUnit,"(*(g0))") "OutputList_ref(",num2str(i),")%record = ", OutputList_ref(i)%record
343 : write(Test%outputUnit,"(*(g0))") "OutputList (",num2str(i),")%record = ", OutputList(i)%record
344 : write(Test%outputUnit,"(*(g0))")
345 : end if
346 : ! LCOV_EXCL_STOP
347 :
348 : end do
349 :
350 45 : end function test_warn_2
351 :
352 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
353 :
354 3 : function test_abort_1() result(assertion)
355 :
356 3 : use JaggedArray_mod, only: CharVec_type
357 : use Constants_mod, only: IK
358 : use String_mod, only: num2str
359 :
360 : implicit none
361 :
362 : integer(IK) :: fileUnit, i, iostat
363 : logical :: assertion, assertionCurrent
364 : integer(IK), parameter :: NLINE = 6_IK
365 3 : type(CharVec_type), allocatable :: OutputList_ref(:)
366 3 : type(CharVec_type), allocatable :: OutputList(:)
367 3 : type(Err_type) :: Err
368 :
369 3 : assertion = .true.
370 3 : mv_isTestingMode = .true.
371 :
372 21 : if (allocated(OutputList)) deallocate(OutputList); allocate(OutputList(NLINE))
373 21 : if (allocated(OutputList_ref)) deallocate(OutputList_ref); allocate(OutputList_ref(NLINE))
374 :
375 3 : OutputList_ref(1)%record = ""
376 3 : OutputList_ref(2)%record = " ParaMonte - FATAL: What does a fish know about the water in which it swims all its life? Albert Einstein"
377 3 : OutputList_ref(3)%record = " ParaMonte - FATAL: Everything should be made as simple as possible, but not simpler. Albert Einstein"
378 3 : OutputList_ref(4)%record = " ParaMonte - FATAL: The absence of evidence is not evidence for absence. Carl Sagan"
379 3 : OutputList_ref(5)%record = " ParaMonte - FATAL: If I have seen further, it is by standing on the shoulders of giants. Isaac Newton"
380 3 : OutputList_ref(6)%record = " ParaMonte - FATAL: I don't pretend to understand the universe - it's much bigger than I am. Thomas Carlyle"
381 :
382 3 : open(newunit = fileUnit, status = "scratch")
383 : !open(newunit = fileUnit, file = Test%outDir//"/Test_Err_mod@test_abort_1."//num2str(Test%Image%id)//".out", status = "replace")
384 :
385 3 : Err%msg = mc_msg
386 : call abort ( Err = Err &
387 : , prefix = mc_prefix &
388 : , newline = "\n" &
389 : , outputUnit = fileUnit &
390 : , returnEnabled = .true. &
391 3 : )
392 :
393 3 : rewind(fileUnit)
394 :
395 21 : do i = 1, NLINE
396 :
397 18 : if(allocated(OutputList(i)%record)) deallocate(OutputList(i)%record)
398 18 : allocate(character(132) :: OutputList(i)%record)
399 :
400 18 : read(fileUnit,"(A132)", iostat = iostat) OutputList(i)%record
401 18 : assertion = iostat == 0_IK
402 : if (.not. assertion) return ! LCOV_EXCL_LINE
403 :
404 18 : OutputList(i)%record = trim(OutputList(i)%record)
405 :
406 18 : assertionCurrent = OutputList(i)%record == OutputList_ref(i)%record
407 18 : assertion = assertion .and. assertionCurrent
408 :
409 21 : if (Test%isDebugMode .and. .not. assertionCurrent) then
410 : ! LCOV_EXCL_START
411 : write(Test%outputUnit,"(*(g0))")
412 : write(Test%outputUnit,"(*(g0))") "OutputList_ref(",num2str(i),")%record = ", OutputList_ref(i)%record
413 : write(Test%outputUnit,"(*(g0))") "OutputList (",num2str(i),")%record = ", OutputList(i)%record
414 : write(Test%outputUnit,"(*(g0))")
415 : end if
416 : ! LCOV_EXCL_STOP
417 :
418 : end do
419 :
420 39 : end function test_abort_1
421 :
422 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
423 :
424 : !> \brief
425 : !> Test the effects of an input non-null error code `Err%stat`.
426 : !> Test the effects of missing arguments `prefix`, `returnEnabled`, and `newline`.
427 3 : function test_abort_2() result(assertion)
428 :
429 3 : use JaggedArray_mod, only: CharVec_type
430 : use Constants_mod, only: IK, NLC
431 : use String_mod, only: num2str, replaceStr
432 :
433 : implicit none
434 :
435 : integer(IK) :: fileUnit, i, iostat
436 : logical :: assertion, assertionCurrent
437 : integer(IK), parameter :: NLINE = 7_IK
438 3 : type(CharVec_type), allocatable :: OutputList_ref(:)
439 3 : type(CharVec_type), allocatable :: OutputList(:)
440 3 : type(Err_type) :: Err
441 :
442 3 : assertion = .true.
443 3 : mv_isTestingMode = .true.
444 :
445 24 : if (allocated(OutputList)) deallocate(OutputList); allocate(OutputList(NLINE))
446 24 : if (allocated(OutputList_ref)) deallocate(OutputList_ref); allocate(OutputList_ref(NLINE))
447 :
448 3 : OutputList_ref(1)%record = ""
449 3 : OutputList_ref(2)%record = " - FATAL: What does a fish know about the water in which it swims all its life? Albert Einstein"
450 3 : OutputList_ref(3)%record = " - FATAL: Everything should be made as simple as possible, but not simpler. Albert Einstein"
451 3 : OutputList_ref(4)%record = " - FATAL: The absence of evidence is not evidence for absence. Carl Sagan"
452 3 : OutputList_ref(5)%record = " - FATAL: If I have seen further, it is by standing on the shoulders of giants. Isaac Newton"
453 3 : OutputList_ref(6)%record = " - FATAL: I don't pretend to understand the universe - it's much bigger than I am. Thomas Carlyle"
454 3 : OutputList_ref(7)%record = " - FATAL: Error Code: 123."
455 :
456 3 : open(newunit = fileUnit, status = "scratch")
457 : !open(newunit = fileUnit, file = Test%outDir//"/Test_Err_mod@test_abort_2."//num2str(Test%Image%id)//".out", status = "replace")
458 :
459 3 : Err%msg = replaceStr(mc_msg, "\n", NLC)
460 3 : Err%stat = 123_IK
461 : call abort ( Err = Err &
462 : , outputUnit = fileUnit &
463 3 : )
464 :
465 3 : rewind(fileUnit)
466 :
467 24 : do i = 1, NLINE
468 :
469 21 : if(allocated(OutputList(i)%record)) deallocate(OutputList(i)%record)
470 21 : allocate(character(132) :: OutputList(i)%record)
471 :
472 21 : read(fileUnit,"(A132)", iostat = iostat) OutputList(i)%record
473 21 : assertion = iostat == 0_IK
474 : if (.not. assertion) return ! LCOV_EXCL_LINE
475 :
476 21 : OutputList(i)%record = trim(OutputList(i)%record)
477 :
478 21 : assertionCurrent = OutputList(i)%record == OutputList_ref(i)%record
479 21 : assertion = assertion .and. assertionCurrent
480 :
481 24 : if (Test%isDebugMode .and. .not. assertionCurrent) then
482 : ! LCOV_EXCL_START
483 : write(Test%outputUnit,"(*(g0))")
484 : write(Test%outputUnit,"(*(g0))") "OutputList_ref(",num2str(i),")%record = '", OutputList_ref(i)%record, "'"
485 : write(Test%outputUnit,"(*(g0))") "OutputList (",num2str(i),")%record = '", OutputList(i)%record, "'"
486 : write(Test%outputUnit,"(*(g0))")
487 : end if
488 : ! LCOV_EXCL_STOP
489 :
490 : end do
491 :
492 45 : end function test_abort_2
493 :
494 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
495 :
496 : end module Test_Err_mod ! LCOV_EXCL_LINE
|