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 [Decoration_mod](@ref decoration_mod).
44 : !> \author Amir Shahmoradi
45 :
46 : module Test_Decoration_mod
47 :
48 : !use, intrinsic :: iso_fortran_env, only: output_unit
49 : use Test_mod, only: Test_type
50 : use Constants_mod, only: IK
51 : use Decoration_mod
52 :
53 : implicit none
54 :
55 : type(Test_type) :: Test
56 :
57 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
58 :
59 : contains
60 :
61 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
62 :
63 1 : subroutine test_Decoration()
64 :
65 : implicit none
66 1 : Test = Test_type(moduleName=MODULE_NAME)
67 1 : call Test%run(test_wrapText, "test_wrapText")
68 1 : call Test%run(test_drawLine_1, "test_drawLine_1")
69 1 : call Test%run(test_drawLine_2, "test_drawLine_2")
70 1 : call Test%run(test_drawLine_3, "test_drawLine_3")
71 1 : call Test%run(test_sandwich_1, "test_sandwich_1")
72 1 : call Test%run(test_sandwich_2, "test_sandwich_2")
73 1 : call Test%run(test_sandwich_3, "test_sandwich_3")
74 1 : call Test%run(test_sandwich_4, "test_sandwich_4")
75 1 : call Test%run(test_sandwich_5, "test_sandwich_5")
76 1 : call Test%run(test_getGenericFormat_1, "test_getGenericFormat_1")
77 1 : call Test%run(test_getGenericFormat_2, "test_getGenericFormat_2")
78 1 : call Test%run(test_getGenericFormat_3, "test_getGenericFormat_3")
79 1 : call Test%run(test_getGenericFormat_4, "test_getGenericFormat_4")
80 1 : call Test%run(test_getGenericFormat_5, "test_getGenericFormat_5")
81 1 : call Test%run(test_writeDecoratedText_1, "test_writeDecoratedText_1")
82 1 : call Test%run(test_writeDecoratedText_2, "test_writeDecoratedText_2")
83 1 : call Test%run(test_writeDecoratedList_1, "test_writeDecoratedList_1")
84 1 : call Test%run(test_writeDecoratedList_2, "test_writeDecoratedList_2")
85 1 : call Test%run(test_constructDecoration_1, "test_constructDecoration_1")
86 1 : call Test%run(test_constructDecoration_2, "test_constructDecoration_2")
87 1 : call Test%finalize()
88 :
89 1 : end subroutine test_Decoration
90 :
91 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
92 :
93 1 : function test_constructDecoration_1() result(assertion)
94 1 : use Constants_mod, only: IK
95 : implicit none
96 : logical :: assertion
97 : character(*), parameter :: tab_ref = "!!!!!"
98 1 : type(Decoration_type) :: Decoration
99 1 : Decoration = Decoration_type(tabStr = tab_ref)
100 1 : assertion = Decoration%tab == tab_ref
101 1 : if (Test%isDebugMode .and. .not. assertion) then
102 : ! LCOV_EXCL_START
103 : write(Test%outputUnit,"(*(g0.15,:,' '))")
104 : write(Test%outputUnit,"(*(g0.15,:,' '))") "tab_ref =", tab_ref
105 : write(Test%outputUnit,"(*(g0.15,:,' '))") "Decoration%tab =", Decoration%tab
106 : write(Test%outputUnit,"(*(g0.15,:,' '))")
107 : end if
108 : ! LCOV_EXCL_STOP
109 1 : end function test_constructDecoration_1
110 :
111 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
112 :
113 1 : function test_constructDecoration_2() result(assertion)
114 1 : use Constants_mod, only: IK
115 : implicit none
116 : logical :: assertion
117 : character(*), parameter :: symbol_ref = "!!!!!"
118 1 : type(Decoration_type) :: Decoration
119 1 : Decoration = Decoration_type(symbol = symbol_ref)
120 1 : assertion = Decoration%symbol == symbol_ref
121 1 : if (Test%isDebugMode .and. .not. assertion) then
122 : ! LCOV_EXCL_START
123 : write(Test%outputUnit,"(*(g0.15,:,' '))")
124 : write(Test%outputUnit,"(*(g0.15,:,' '))") "symbol_ref =", symbol_ref
125 : write(Test%outputUnit,"(*(g0.15,:,' '))") "Decoration%symbol =", Decoration%symbol
126 : write(Test%outputUnit,"(*(g0.15,:,' '))")
127 : end if
128 : ! LCOV_EXCL_STOP
129 1 : end function test_constructDecoration_2
130 :
131 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
132 :
133 1 : function test_getGenericFormat_1() result(assertion)
134 1 : use Constants_mod, only: IK
135 : implicit none
136 : logical :: assertion
137 : character(*), parameter :: genericFormat_ref = "('ParaMonte',*(g25.10,:,','))"
138 1 : character(:), allocatable :: genericFormat
139 1 : genericFormat = getGenericFormat(width = 25_IK, precision = 10_IK, delim = ",", prefix = "ParaMonte")
140 1 : assertion = genericFormat == genericFormat_ref
141 1 : if (Test%isDebugMode .and. .not. assertion) then
142 : ! LCOV_EXCL_START
143 : write(Test%outputUnit,"(*(g0.15,:,' '))")
144 : write(Test%outputUnit,"(*(g0.15,:,' '))") "genericFormat_ref =", genericFormat_ref
145 : write(Test%outputUnit,"(*(g0.15,:,' '))") "genericFormat =", genericFormat
146 : write(Test%outputUnit,"(*(g0.15,:,' '))")
147 : end if
148 : ! LCOV_EXCL_STOP
149 1 : end function test_getGenericFormat_1
150 :
151 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
152 :
153 1 : function test_getGenericFormat_2() result(assertion)
154 1 : use Constants_mod, only: IK
155 : implicit none
156 : logical :: assertion
157 : character(*), parameter :: genericFormat_ref = "(*(g25.10,:,','))"
158 1 : character(:), allocatable :: genericFormat
159 1 : genericFormat = getGenericFormat(width = 25_IK, precision = 10_IK, delim = ",")
160 1 : assertion = genericFormat == genericFormat_ref
161 1 : if (Test%isDebugMode .and. .not. assertion) then
162 : ! LCOV_EXCL_START
163 : write(Test%outputUnit,"(*(g0.15,:,' '))")
164 : write(Test%outputUnit,"(*(g0.15,:,' '))") "genericFormat_ref =", genericFormat_ref
165 : write(Test%outputUnit,"(*(g0.15,:,' '))") "genericFormat =", genericFormat
166 : write(Test%outputUnit,"(*(g0.15,:,' '))")
167 : end if
168 : ! LCOV_EXCL_STOP
169 1 : end function test_getGenericFormat_2
170 :
171 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
172 :
173 1 : function test_getGenericFormat_3() result(assertion)
174 1 : use Constants_mod, only: IK
175 : implicit none
176 : logical :: assertion
177 : character(*), parameter :: genericFormat_ref = "(*(g25.10))"
178 1 : character(:), allocatable :: genericFormat
179 1 : genericFormat = getGenericFormat(width = 25_IK, precision = 10_IK)
180 1 : assertion = genericFormat == genericFormat_ref
181 1 : if (Test%isDebugMode .and. .not. assertion) then
182 : ! LCOV_EXCL_START
183 : write(Test%outputUnit,"(*(g0.15,:,' '))")
184 : write(Test%outputUnit,"(*(g0.15,:,' '))") "genericFormat_ref =", genericFormat_ref
185 : write(Test%outputUnit,"(*(g0.15,:,' '))") "genericFormat =", genericFormat
186 : write(Test%outputUnit,"(*(g0.15,:,' '))")
187 : end if
188 : ! LCOV_EXCL_STOP
189 1 : end function test_getGenericFormat_3
190 :
191 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
192 :
193 1 : function test_getGenericFormat_4() result(assertion)
194 1 : use Constants_mod, only: IK
195 : implicit none
196 : logical :: assertion
197 : character(*), parameter :: genericFormat_ref = "(*(g25))"
198 1 : character(:), allocatable :: genericFormat
199 1 : genericFormat = getGenericFormat(width = 25_IK)
200 1 : assertion = genericFormat == genericFormat_ref
201 1 : if (Test%isDebugMode .and. .not. assertion) then
202 : ! LCOV_EXCL_START
203 : write(Test%outputUnit,"(*(g0.15,:,' '))")
204 : write(Test%outputUnit,"(*(g0.15,:,' '))") "genericFormat_ref =", genericFormat_ref
205 : write(Test%outputUnit,"(*(g0.15,:,' '))") "genericFormat =", genericFormat
206 : write(Test%outputUnit,"(*(g0.15,:,' '))")
207 : end if
208 : ! LCOV_EXCL_STOP
209 1 : end function test_getGenericFormat_4
210 :
211 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
212 :
213 1 : function test_getGenericFormat_5() result(assertion)
214 1 : use Constants_mod, only: IK
215 : implicit none
216 : logical :: assertion
217 : character(*), parameter :: genericFormat_ref = "(*(g0))"
218 1 : character(:), allocatable :: genericFormat
219 1 : genericFormat = getGenericFormat()
220 1 : assertion = genericFormat == genericFormat_ref
221 1 : if (Test%isDebugMode .and. .not. assertion) then
222 : ! LCOV_EXCL_START
223 : write(Test%outputUnit,"(*(g0.15,:,' '))")
224 : write(Test%outputUnit,"(*(g0.15,:,' '))") "genericFormat_ref =", genericFormat_ref
225 : write(Test%outputUnit,"(*(g0.15,:,' '))") "genericFormat =", genericFormat
226 : write(Test%outputUnit,"(*(g0.15,:,' '))")
227 : end if
228 : ! LCOV_EXCL_STOP
229 1 : end function test_getGenericFormat_5
230 :
231 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
232 :
233 1 : function test_writeDecoratedText_1() result(assertion)
234 :
235 1 : use JaggedArray_mod, only: CharVec_type
236 : use Constants_mod, only: IK
237 : use String_mod, only: num2str
238 : implicit none
239 : logical :: assertion
240 : logical :: assertionCurrent
241 1 : type(Decoration_type) :: Decoration
242 1 : type(CharVec_type), allocatable :: OutputList_ref(:)
243 1 : type(CharVec_type), allocatable :: OutputList(:)
244 : integer(IK) :: fileUnit, i, iostat
245 : integer(IK), parameter :: NLINE = 19_IK
246 :
247 1 : assertion = .true.
248 :
249 20 : if (allocated(OutputList)) deallocate(OutputList); allocate(OutputList(NLINE))
250 20 : if (allocated(OutputList_ref)) deallocate(OutputList_ref); allocate(OutputList_ref(NLINE))
251 :
252 1 : OutputList_ref( 1)%record = ""
253 1 : OutputList_ref( 2)%record = ""
254 1 : OutputList_ref( 3)%record = "&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&"
255 1 : OutputList_ref( 4)%record = "&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&"
256 1 : OutputList_ref( 5)%record = "&&&& &&&&"
257 1 : OutputList_ref( 6)%record = "&&&& &&&&"
258 1 : OutputList_ref( 7)%record = "&&&&Have you asked yourself:&&&&"
259 1 : OutputList_ref( 8)%record = "&&&& &&&&"
260 1 : OutputList_ref( 9)%record = "&&&&s the Universe bother to&&&&"
261 1 : OutputList_ref(10)%record = "&&&& &&&&"
262 1 : OutputList_ref(11)%record = "&&&& the origin of mass and &&&&"
263 1 : OutputList_ref(12)%record = "&&&& &&&&"
264 1 : OutputList_ref(13)%record = "&&&&at is the origin of life&&&&"
265 1 : OutputList_ref(14)%record = "&&&& &&&&"
266 1 : OutputList_ref(15)%record = "&&&& &&&&"
267 1 : OutputList_ref(16)%record = "&&&& &&&&"
268 1 : OutputList_ref(17)%record = "&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&"
269 1 : OutputList_ref(18)%record = "&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&"
270 1 : OutputList_ref(19)%record = ""
271 :
272 5 : allocate(Decoration%List(4))
273 :
274 1 : Decoration%List(1)%record = "Have you asked yourself:"
275 1 : Decoration%List(2)%record = "Why does the Universe bother to exist?"
276 1 : Decoration%List(3)%record = "What is the origin of mass and matter?"
277 1 : Decoration%List(4)%record = "What is the origin of life?"
278 :
279 : Decoration%text = "\n\n" // & ! LCOV_EXCL_LINE
280 : Decoration%List(1)%record // "\n\n" // & ! LCOV_EXCL_LINE
281 : Decoration%List(2)%record // "\n\n" // & ! LCOV_EXCL_LINE
282 : Decoration%List(3)%record // "\n\n" // & ! LCOV_EXCL_LINE
283 1 : Decoration%List(4)%record // "\n\n\n"
284 :
285 1 : open(newunit = fileUnit, status = "scratch")
286 : !open(newunit = fileUnit, file = Test%outDir//"/Test_Decoration_mod@test_writeDecoratedText_1."//num2str(Test%Image%id)//".out", status = "replace")
287 :
288 : call Decoration%writeDecoratedText ( Decoration%text & ! LCOV_EXCL_LINE
289 : , newLine="\n" & ! LCOV_EXCL_LINE
290 : , width = 32_IK & ! LCOV_EXCL_LINE
291 : , symbol = "&" & ! LCOV_EXCL_LINE
292 : , thicknessHorz = 4_IK & ! LCOV_EXCL_LINE
293 : , thicknessVert = 2_IK & ! LCOV_EXCL_LINE
294 : , marginTop = 2_IK & ! LCOV_EXCL_LINE
295 : , marginBot = 1_IK & ! LCOV_EXCL_LINE
296 : , outputUnit = fileUnit & ! LCOV_EXCL_LINE
297 1 : )
298 :
299 1 : rewind(fileUnit)
300 :
301 20 : do i = 1, NLINE
302 :
303 19 : if(allocated(OutputList(i)%record)) deallocate(OutputList(i)%record)
304 19 : allocate(character(132) :: OutputList(i)%record)
305 19 : read(fileUnit,"(A132)", iostat = iostat) OutputList(i)%record
306 19 : assertion = iostat == 0_IK
307 : if (.not. assertion) return ! LCOV_EXCL_LINE
308 19 : OutputList(i)%record = trim(adjustl(OutputList(i)%record))
309 :
310 19 : assertionCurrent = OutputList(i)%record == OutputList_ref(i)%record
311 19 : assertion = assertion .and. assertionCurrent
312 :
313 20 : if (Test%isDebugMode .and. .not. assertionCurrent) then
314 : ! LCOV_EXCL_START
315 : write(Test%outputUnit,"(*(g0))")
316 : write(Test%outputUnit,"(*(g0))") "OutputList_ref(",num2str(i),")%record = ", OutputList_ref(i)%record
317 : write(Test%outputUnit,"(*(g0))") "OutputList (",num2str(i),")%record = ", OutputList(i)%record
318 : write(Test%outputUnit,"(*(g0))")
319 : end if
320 : ! LCOV_EXCL_STOP
321 :
322 : end do
323 :
324 43 : end function test_writeDecoratedText_1
325 :
326 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
327 :
328 1 : function test_writeDecoratedText_2() result(assertion)
329 :
330 1 : use JaggedArray_mod, only: CharVec_type
331 : use Constants_mod, only: IK, NLC
332 : use String_mod, only: num2str
333 : implicit none
334 : logical :: assertion
335 : logical :: assertionCurrent
336 1 : type(Decoration_type) :: Decoration
337 1 : type(CharVec_type), allocatable :: OutputList_ref(:)
338 1 : type(CharVec_type), allocatable :: OutputList(:)
339 : integer(IK) :: fileUnit, i, iostat
340 : integer(IK), parameter :: NLINE = 14_IK
341 :
342 1 : assertion = .true.
343 :
344 15 : if (allocated(OutputList)) deallocate(OutputList); allocate(OutputList(NLINE))
345 15 : if (allocated(OutputList_ref)) deallocate(OutputList_ref); allocate(OutputList_ref(NLINE))
346 :
347 1 : OutputList_ref( 1)%record = "************************************************************************************************************************************"
348 1 : OutputList_ref( 2)%record = "**** ****"
349 1 : OutputList_ref( 3)%record = "**** ****"
350 1 : OutputList_ref( 4)%record = "**** Have you asked yourself: ****"
351 1 : OutputList_ref( 5)%record = "**** ****"
352 1 : OutputList_ref( 6)%record = "**** Why does the Universe bother to exist? ****"
353 1 : OutputList_ref( 7)%record = "**** ****"
354 1 : OutputList_ref( 8)%record = "**** What is the origin of mass and matter? ****"
355 1 : OutputList_ref( 9)%record = "**** ****"
356 1 : OutputList_ref(10)%record = "**** What is the origin of life? ****"
357 1 : OutputList_ref(11)%record = "**** ****"
358 1 : OutputList_ref(12)%record = "**** ****"
359 1 : OutputList_ref(13)%record = "**** ****"
360 1 : OutputList_ref(14)%record = "************************************************************************************************************************************"
361 :
362 5 : allocate(Decoration%List(4))
363 :
364 1 : Decoration%List(1)%record = "Have you asked yourself:"
365 1 : Decoration%List(2)%record = "Why does the Universe bother to exist?"
366 1 : Decoration%List(3)%record = "What is the origin of mass and matter?"
367 1 : Decoration%List(4)%record = "What is the origin of life?"
368 :
369 : Decoration%text = NLC//NLC// & ! LCOV_EXCL_LINE
370 : Decoration%List(1)%record // NLC//NLC// & ! LCOV_EXCL_LINE
371 : Decoration%List(2)%record // NLC//NLC// & ! LCOV_EXCL_LINE
372 : Decoration%List(3)%record // NLC//NLC// & ! LCOV_EXCL_LINE
373 1 : Decoration%List(4)%record // NLC//NLC//NLC
374 :
375 1 : open(newunit = fileUnit, status = "scratch")
376 : !open(newunit = fileUnit, file = Test%outDir//"/Test_Decoration_mod@test_writeDecoratedText_2."//num2str(Test%Image%id)//".out", status = "replace")
377 :
378 : call Decoration%writeDecoratedText ( Decoration%text & ! LCOV_EXCL_LINE
379 : , newLine = NLC & ! LCOV_EXCL_LINE
380 : , outputUnit = fileUnit & ! LCOV_EXCL_LINE
381 1 : )
382 :
383 1 : rewind(fileUnit)
384 :
385 15 : do i = 1, NLINE
386 :
387 14 : if(allocated(OutputList(i)%record)) deallocate(OutputList(i)%record)
388 14 : allocate(character(132) :: OutputList(i)%record)
389 14 : read(fileUnit,"(A132)", iostat = iostat) OutputList(i)%record
390 14 : assertion = iostat == 0_IK
391 : if (.not. assertion) return ! LCOV_EXCL_LINE
392 14 : OutputList(i)%record = trim(adjustl(OutputList(i)%record))
393 :
394 14 : assertionCurrent = OutputList(i)%record == OutputList_ref(i)%record
395 14 : assertion = assertion .and. assertionCurrent
396 :
397 15 : if (Test%isDebugMode .and. .not. assertionCurrent) then
398 : ! LCOV_EXCL_START
399 : write(Test%outputUnit,"(*(g0))")
400 : write(Test%outputUnit,"(*(g0))") "OutputList_ref(",num2str(i),")%record = ", OutputList_ref(i)%record
401 : write(Test%outputUnit,"(*(g0))") "OutputList (",num2str(i),")%record = ", OutputList(i)%record
402 : write(Test%outputUnit,"(*(g0))")
403 : end if
404 : ! LCOV_EXCL_STOP
405 :
406 : end do
407 :
408 34 : end function test_writeDecoratedText_2
409 :
410 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
411 :
412 1 : function test_writeDecoratedList_1() result(assertion)
413 :
414 1 : use JaggedArray_mod, only: CharVec_type
415 : use Constants_mod, only: IK
416 : use String_mod, only: num2str
417 : implicit none
418 : logical :: assertion
419 : logical :: assertionCurrent
420 1 : type(Decoration_type) :: Decoration
421 1 : type(CharVec_type), allocatable :: OutputList_ref(:)
422 1 : type(CharVec_type), allocatable :: OutputList(:)
423 : integer(IK) :: fileUnit, i, iostat
424 : integer(IK), parameter :: NLINE = 6_IK
425 :
426 1 : assertion = .true.
427 :
428 7 : if (allocated(OutputList)) deallocate(OutputList); allocate(OutputList(NLINE))
429 7 : if (allocated(OutputList_ref)) deallocate(OutputList_ref); allocate(OutputList_ref(NLINE))
430 :
431 1 : OutputList_ref(1)%record = "************************************************************************************************************************************"
432 1 : OutputList_ref(2)%record = "**** Have you asked yourself: ****"
433 1 : OutputList_ref(3)%record = "**** Why does the Universe bother to exist? ****"
434 1 : OutputList_ref(4)%record = "**** What is the origin of mass and matter? ****"
435 1 : OutputList_ref(5)%record = "**** What is the origin of life? ****"
436 1 : OutputList_ref(6)%record = "************************************************************************************************************************************"
437 :
438 5 : allocate(Decoration%List(4))
439 :
440 1 : Decoration%List(1)%record = "Have you asked yourself:"
441 1 : Decoration%List(2)%record = "Why does the Universe bother to exist?"
442 1 : Decoration%List(3)%record = "What is the origin of mass and matter?"
443 1 : Decoration%List(4)%record = "What is the origin of life?"
444 :
445 1 : open(newunit = fileUnit, status = "scratch")
446 : !open(newunit = fileUnit, file = Test%outDir//"/Test_Decoration_mod@test_writeDecoratedList_1."//num2str(Test%Image%id)//".out", status = "replace")
447 :
448 1 : call Decoration%writeDecoratedList(Decoration%List, outputUnit = fileUnit)
449 :
450 1 : rewind(fileUnit)
451 :
452 7 : do i = 1, NLINE
453 :
454 6 : if(allocated(OutputList(i)%record)) deallocate(OutputList(i)%record)
455 6 : allocate(character(132) :: OutputList(i)%record)
456 6 : read(fileUnit,"(A132)", iostat = iostat) OutputList(i)%record
457 6 : assertion = iostat == 0_IK
458 : if (.not. assertion) return ! LCOV_EXCL_LINE
459 6 : OutputList(i)%record = trim(adjustl(OutputList(i)%record))
460 :
461 6 : assertionCurrent = OutputList(i)%record == OutputList_ref(i)%record
462 6 : assertion = assertion .and. assertionCurrent
463 :
464 7 : if (Test%isDebugMode .and. .not. assertionCurrent) then
465 : ! LCOV_EXCL_START
466 : write(Test%outputUnit,"(*(g0))")
467 : write(Test%outputUnit,"(*(g0))") "OutputList_ref(",num2str(i),")%record = ", OutputList_ref(i)%record
468 : write(Test%outputUnit,"(*(g0))") "OutputList (",num2str(i),")%record = ", OutputList(i)%record
469 : write(Test%outputUnit,"(*(g0))")
470 : end if
471 : ! LCOV_EXCL_STOP
472 :
473 : end do
474 :
475 17 : end function test_writeDecoratedList_1
476 :
477 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
478 :
479 1 : function test_writeDecoratedList_2() result(assertion)
480 :
481 1 : use JaggedArray_mod, only: CharVec_type
482 : use Constants_mod, only: IK
483 : use String_mod, only: num2str
484 : implicit none
485 : logical :: assertion
486 : logical :: assertionCurrent
487 1 : type(Decoration_type) :: Decoration
488 1 : type(CharVec_type), allocatable :: OutputList_ref(:)
489 1 : type(CharVec_type), allocatable :: OutputList(:)
490 : integer(IK) :: fileUnit, i, iostat
491 : integer(IK), parameter :: NLINE = 11_IK
492 :
493 1 : assertion = .true.
494 :
495 12 : if (allocated(OutputList)) deallocate(OutputList); allocate(OutputList(NLINE))
496 12 : if (allocated(OutputList_ref)) deallocate(OutputList_ref); allocate(OutputList_ref(NLINE))
497 :
498 1 : OutputList_ref( 1)%record = ""
499 1 : OutputList_ref( 2)%record = "%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%"
500 1 : OutputList_ref( 3)%record = "%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%"
501 1 : OutputList_ref( 4)%record = "%% Have you asked yourself: %%"
502 1 : OutputList_ref( 5)%record = "%% Why does the Universe bother to exist? %%"
503 1 : OutputList_ref( 6)%record = "%% What is the origin of mass and matter? %%"
504 1 : OutputList_ref( 7)%record = "%% What is the origin of life? %%"
505 1 : OutputList_ref( 8)%record = "%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%"
506 1 : OutputList_ref( 9)%record = "%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%"
507 1 : OutputList_ref(10)%record = ""
508 1 : OutputList_ref(11)%record = ""
509 :
510 5 : allocate(Decoration%List(4))
511 :
512 1 : Decoration%List(1)%record = "Have you asked yourself:"
513 1 : Decoration%List(2)%record = "Why does the Universe bother to exist?"
514 1 : Decoration%List(3)%record = "What is the origin of mass and matter?"
515 1 : Decoration%List(4)%record = "What is the origin of life?"
516 :
517 1 : open(newunit = fileUnit, status = "scratch")
518 : !open(newunit = fileUnit, file = Test%outDir//"/Test_Decoration_mod@test_writeDecoratedList_2."//num2str(Test%Image%id)//".out", status = "replace")
519 :
520 : call Decoration%writeDecoratedList ( Decoration%List &
521 : , symbol = "%" &
522 : , width = 128_IK &
523 : , thicknessHorz = 2_IK &
524 : , thicknessVert = 2_IK &
525 : , marginTop = 1_IK &
526 : , marginBot = 2_IK &
527 : , outputUnit = fileUnit &
528 1 : )
529 :
530 1 : rewind(fileUnit)
531 :
532 12 : do i = 1, NLINE
533 :
534 11 : if(allocated(OutputList(i)%record)) deallocate(OutputList(i)%record)
535 11 : allocate(character(132) :: OutputList(i)%record)
536 11 : read(fileUnit,"(A132)", iostat = iostat) OutputList(i)%record
537 11 : assertion = iostat == 0_IK
538 : if (.not. assertion) return ! LCOV_EXCL_LINE
539 11 : OutputList(i)%record = trim(adjustl(OutputList(i)%record))
540 :
541 11 : assertionCurrent = OutputList(i)%record == OutputList_ref(i)%record
542 11 : assertion = assertion .and. assertionCurrent
543 :
544 12 : if (Test%isDebugMode .and. .not. assertionCurrent) then
545 : ! LCOV_EXCL_START
546 : write(Test%outputUnit,"(*(g0))")
547 : write(Test%outputUnit,"(*(g0))") "OutputList_ref(",num2str(i),")%record = ", OutputList_ref(i)%record
548 : write(Test%outputUnit,"(*(g0))") "OutputList (",num2str(i),")%record = ", OutputList(i)%record
549 : write(Test%outputUnit,"(*(g0))")
550 : end if
551 : ! LCOV_EXCL_STOP
552 :
553 : end do
554 :
555 27 : end function test_writeDecoratedList_2
556 :
557 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
558 :
559 1 : function test_drawLine_1() result(assertion)
560 1 : use Constants_mod, only: IK
561 : implicit none
562 : logical :: assertion
563 : character(*), parameter :: line_ref = "HelloWorld!HelloWorld!HelloWorld!HelloWorld!HelloWorld!HelloWorld!&
564 : &HelloWorld!HelloWorld!HelloWorld!HelloWorld!Hello"
565 1 : character(:), allocatable :: line
566 1 : line = drawLine(symbol = "HelloWorld!", width = 115_IK)
567 1 : assertion = line == line_ref
568 : ! LCOV_EXCL_START
569 : if (Test%isDebugMode .and. .not. assertion) then
570 : write(Test%outputUnit,"(*(g0.15,:,' '))")
571 : write(Test%outputUnit,"(*(g0.15,:,' '))") "line_ref =", line_ref
572 : write(Test%outputUnit,"(*(g0.15,:,' '))") "line =", line
573 : write(Test%outputUnit,"(*(g0.15,:,' '))")
574 : end if
575 : ! LCOV_EXCL_STOP
576 1 : end function test_drawLine_1
577 :
578 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
579 :
580 1 : function test_drawLine_2() result(assertion)
581 1 : use Constants_mod, only: IK
582 : implicit none
583 : logical :: assertion
584 : character(*), parameter :: line_ref = "HelloWorld!HelloWorld!HelloWorld!HelloWorld!HelloWorld!HelloWorld!&
585 : &HelloWorld!HelloWorld!HelloWorld!HelloWorld!HelloWorld!HelloWorld!"
586 1 : character(:), allocatable :: line
587 1 : line = drawLine(symbol = "HelloWorld!")
588 1 : assertion = line == line_ref
589 1 : if (Test%isDebugMode .and. .not. assertion) then
590 : ! LCOV_EXCL_START
591 : write(Test%outputUnit,"(*(g0.15,:,' '))")
592 : write(Test%outputUnit,"(*(g0.15,:,' '))") "line_ref =", line_ref
593 : write(Test%outputUnit,"(*(g0.15,:,' '))") "line =", line
594 : write(Test%outputUnit,"(*(g0.15,:,' '))")
595 : end if
596 : ! LCOV_EXCL_STOP
597 1 : end function test_drawLine_2
598 :
599 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
600 :
601 1 : function test_drawLine_3() result(assertion)
602 1 : use Constants_mod, only: IK
603 : implicit none
604 : logical :: assertion
605 : character(*), parameter :: line_ref = "******************************************************************&
606 : &******************************************************************"
607 1 : character(:), allocatable :: line
608 1 : line = drawLine()
609 1 : assertion = line == line_ref
610 1 : if (Test%isDebugMode .and. .not. assertion) then
611 : ! LCOV_EXCL_START
612 : write(Test%outputUnit,"(*(g0.15,:,' '))")
613 : write(Test%outputUnit,"(*(g0.15,:,' '))") "line_ref =", line_ref
614 : write(Test%outputUnit,"(*(g0.15,:,' '))") "line =", line
615 : write(Test%outputUnit,"(*(g0.15,:,' '))")
616 : end if
617 : ! LCOV_EXCL_STOP
618 1 : end function test_drawLine_3
619 :
620 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
621 :
622 1 : function test_sandwich_1() result(assertion)
623 1 : use Constants_mod, only: IK
624 : implicit none
625 : logical :: assertion
626 : character(*), parameter :: sandwichedText_ref = "% The absence of evidence is not evidence for absence. %"
627 1 : character(:), allocatable :: sandwichedText
628 : sandwichedText = sandwich ( text = "The absence of evidence is not evidence for absence." &
629 : , symbol = "%" &
630 : , width = 100_IK &
631 : , thicknessHorz = 1_IK &
632 1 : )
633 1 : assertion = sandwichedText == sandwichedText_ref
634 1 : if (Test%isDebugMode .and. .not. assertion) then
635 : ! LCOV_EXCL_START
636 : write(Test%outputUnit,"(*(g0.15,:,' '))")
637 : write(Test%outputUnit,"(*(g0.15,:,' '))") "sandwichedText_ref =", sandwichedText_ref
638 : write(Test%outputUnit,"(*(g0.15,:,' '))") "sandwichedText =", sandwichedText
639 : write(Test%outputUnit,"(*(g0.15,:,' '))")
640 : end if
641 : ! LCOV_EXCL_STOP
642 1 : end function test_sandwich_1
643 :
644 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
645 :
646 1 : function test_sandwich_2() result(assertion)
647 1 : use Constants_mod, only: IK
648 : implicit none
649 : logical :: assertion
650 : character(*), parameter :: sandwichedText_ref = "%%%% The absence of evidence is not evidence for absence. %%%%"
651 1 : character(:), allocatable :: sandwichedText
652 : sandwichedText = sandwich ( text = "The absence of evidence is not evidence for absence." &
653 : , symbol = "%" &
654 : , width = 100_IK &
655 1 : )
656 1 : assertion = sandwichedText == sandwichedText_ref
657 1 : if (Test%isDebugMode .and. .not. assertion) then
658 : ! LCOV_EXCL_START
659 : write(Test%outputUnit,"(*(g0.15,:,' '))")
660 : write(Test%outputUnit,"(*(g0.15,:,' '))") "sandwichedText_ref =", sandwichedText_ref
661 : write(Test%outputUnit,"(*(g0.15,:,' '))") "sandwichedText =", sandwichedText
662 : write(Test%outputUnit,"(*(g0.15,:,' '))")
663 : end if
664 : ! LCOV_EXCL_STOP
665 1 : end function test_sandwich_2
666 :
667 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
668 :
669 1 : function test_sandwich_3() result(assertion)
670 1 : use Constants_mod, only: IK
671 : implicit none
672 : logical :: assertion
673 : character(*), parameter :: sandwichedText_ref = "%%%% The absence of evidence is not evidence for absence. %%%%"
674 1 : character(:), allocatable :: sandwichedText
675 : sandwichedText = sandwich ( text = "The absence of evidence is not evidence for absence." &
676 : , symbol = "%" &
677 1 : )
678 1 : assertion = sandwichedText == sandwichedText_ref
679 1 : if (Test%isDebugMode .and. .not. assertion) then
680 : ! LCOV_EXCL_START
681 : write(Test%outputUnit,"(*(g0.15,:,' '))")
682 : write(Test%outputUnit,"(*(g0.15,:,' '))") "sandwichedText_ref =", sandwichedText_ref
683 : write(Test%outputUnit,"(*(g0.15,:,' '))") "sandwichedText =", sandwichedText
684 : write(Test%outputUnit,"(*(g0.15,:,' '))")
685 : end if
686 : ! LCOV_EXCL_STOP
687 1 : end function test_sandwich_3
688 :
689 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
690 :
691 1 : function test_sandwich_4() result(assertion)
692 1 : use Constants_mod, only: IK
693 : implicit none
694 : logical :: assertion
695 : character(*), parameter :: sandwichedText_ref = "**** The absence of evidence is not evidence for absence. ****"
696 1 : character(:), allocatable :: sandwichedText
697 1 : sandwichedText = sandwich( text = "The absence of evidence is not evidence for absence." )
698 1 : assertion = sandwichedText == sandwichedText_ref
699 1 : if (Test%isDebugMode .and. .not. assertion) then
700 : ! LCOV_EXCL_START
701 : write(Test%outputUnit,"(*(g0.15,:,' '))")
702 : write(Test%outputUnit,"(*(g0.15,:,' '))") "sandwichedText_ref =", sandwichedText_ref
703 : write(Test%outputUnit,"(*(g0.15,:,' '))") "sandwichedText =", sandwichedText
704 : write(Test%outputUnit,"(*(g0.15,:,' '))")
705 : end if
706 : ! LCOV_EXCL_STOP
707 1 : end function test_sandwich_4
708 :
709 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
710 :
711 1 : function test_sandwich_5() result(assertion)
712 1 : use Constants_mod, only: IK
713 : implicit none
714 : logical :: assertion
715 : character(*), parameter :: sandwichedText_ref = "**** ****"
716 1 : character(:), allocatable :: sandwichedText
717 1 : sandwichedText = sandwich()
718 1 : assertion = sandwichedText == sandwichedText_ref
719 1 : if (Test%isDebugMode .and. .not. assertion) then
720 : ! LCOV_EXCL_START
721 : write(Test%outputUnit,"(*(g0.15,:,' '))")
722 : write(Test%outputUnit,"(*(g0.15,:,' '))") "sandwichedText_ref =", sandwichedText_ref
723 : write(Test%outputUnit,"(*(g0.15,:,' '))") "sandwichedText =", sandwichedText
724 : write(Test%outputUnit,"(*(g0.15,:,' '))")
725 : end if
726 : ! LCOV_EXCL_STOP
727 1 : end function test_sandwich_5
728 :
729 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
730 :
731 1 : function test_wrapText() result(assertion)
732 1 : use Constants_mod, only: IK
733 : use String_mod, only: num2str
734 : implicit none
735 : logical :: assertion, assertionCurrent
736 1 : type(CharVec_type), allocatable :: ListOfLines_ref(:)
737 1 : type(CharVec_type), allocatable :: ListOfLines(:)
738 : integer(IK) , parameter :: nline_ref = 6_IK
739 1 : character(:), allocatable :: string
740 : integer(IK) :: nline, i
741 :
742 1 : assertion = .true.
743 :
744 : string = "ParaMonte is a serial/parallel library of Monte Carlo routines for sampling mathematical objective &
745 : &functions of arbitrary-dimensions, in particular, the posterior distributions of Bayesian models in &
746 : &data science, Machine Learning, and scientific inference, with the design goal of unifying the &
747 : &automation (of Monte Carlo simulations), user-friendliness (of the library), accessibility &
748 : &(from multiple programming environments), high-performance (at runtime), and scalability &
749 1 : &(across many parallel processors)."
750 :
751 7 : if (allocated(ListOfLines_ref)) deallocate(ListOfLines_ref); allocate(ListOfLines_ref(nline_ref))
752 1 : ListOfLines_ref(1)%record = "ParaMonte is a serial/parallel library of Monte Carlo routines for sampling mathematical objective "
753 1 : ListOfLines_ref(2)%record = "functions of arbitrary-dimensions, in particular, the posterior distributions of Bayesian models in "
754 1 : ListOfLines_ref(3)%record = "data science, Machine Learning, and scientific inference, with the design goal of unifying the "
755 1 : ListOfLines_ref(4)%record = "automation (of Monte Carlo simulations), user-friendliness (of the library), accessibility (from "
756 1 : ListOfLines_ref(5)%record = "multiple programming environments), high-performance (at runtime), and scalability (across many "
757 1 : ListOfLines_ref(6)%record = "parallel processors)."
758 :
759 14 : ListOfLines = wrapText(string = string, width = 100_IK, split = " ", pad = " ")
760 1 : nline = size(ListOfLines)
761 :
762 1 : assertion = nline == nline_ref
763 :
764 1 : if (assertion) then
765 7 : do i = 1, nline
766 6 : assertionCurrent = ListOfLines(i)%record == ListOfLines_ref(i)%record
767 6 : assertion = assertion .and. assertionCurrent
768 7 : if (Test%isDebugMode .and. .not. assertionCurrent) then
769 : ! LCOV_EXCL_START
770 : write(Test%outputUnit,"(*(g0))")
771 : write(Test%outputUnit,"(*(g0))") "ListOfLines_ref(",num2str(i),")%record = '", ListOfLines_ref(i)%record, "'"
772 : write(Test%outputUnit,"(*(g0))") "ListOfLines (",num2str(i),")%record = '", ListOfLines(i)%record, "'"
773 : write(Test%outputUnit,"(*(g0))")
774 : end if
775 : ! LCOV_EXCL_STOP
776 : end do
777 : ! LCOV_EXCL_START
778 : else
779 : if (Test%isDebugMode .and. .not. assertion) then
780 : write(Test%outputUnit,"(*(g0))")
781 : write(Test%outputUnit,"(*(g0))") "nline_ref = ", nline_ref
782 : write(Test%outputUnit,"(*(g0))") "nline = ", nline
783 : write(Test%outputUnit,"(*(g0))")
784 : end if
785 : return
786 : end if
787 : ! LCOV_EXCL_STOP
788 :
789 13 : end function test_wrapText
790 :
791 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
792 :
793 : end module Test_Decoration_mod ! LCOV_EXCL_LINE
|