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 classes and procedures for decorating and outputting text.
44 : !> \author Amir Shahmoradi
45 :
46 : module Decoration_mod
47 :
48 : use Constants_mod, only: IK
49 : use JaggedArray_mod, only: CharVec_type
50 :
51 : implicit none
52 :
53 : character(*), parameter :: MODULE_NAME = "@Decoration_mod"
54 :
55 : integer(IK) , parameter :: DECORATION_WIDTH = 132
56 : integer(IK) , parameter :: DECORATION_THICKNESS_HORZ = 4
57 : integer(IK) , parameter :: DECORATION_THICKNESS_VERT = 1
58 : character(*), parameter :: STAR = "*"
59 : character(*), parameter :: TAB = " "
60 : character(*), parameter :: INDENT = TAB // TAB
61 :
62 : character(*), parameter :: GENERIC_OUTPUT_FORMAT = "(*(g0,:,' '))"
63 : character(*), parameter :: GENERIC_TABBED_FORMAT = "('" // TAB // TAB // "',*(g0,:,' '))"
64 :
65 : ! ANSI string style
66 :
67 : integer(IK) , parameter :: ANSI_ATTRIBUTE_LIST_LEN = 8
68 : integer(IK) , parameter :: ANSI_COLOR_LIST_LEN = 16
69 :
70 : type, extends(CharVec_type) :: Ansi_type
71 : character(:), allocatable :: code
72 : end type
73 :
74 : type(Ansi_type), allocatable :: mc_AnsiAttributeList(:)
75 : type(Ansi_type), allocatable :: mc_AnsiForegroundColorList(:)
76 : type(Ansi_type), allocatable :: mc_AnsiBackgroundColorList(:)
77 :
78 : !> The decoration class
79 : type :: decoration_type
80 : character(:), allocatable :: tab
81 : character(:), allocatable :: text
82 : character(:), allocatable :: symbol
83 : type(CharVec_type), allocatable :: List(:)
84 : contains
85 : procedure, nopass :: write, writeDecoratedText, writeDecoratedList, wrapText, style
86 : !generic :: write => writeDecoratedText, writeDecoratedList
87 : end type decoration_type
88 :
89 : interface decoration_type
90 : module procedure :: constructDecoration
91 : end interface decoration_type
92 :
93 : type :: wrapper_type
94 : type(CharVec_type), allocatable :: Line(:)
95 : contains
96 : procedure, nopass :: wrap => wrapText
97 : end type wrapper_type
98 :
99 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
100 :
101 : interface
102 : module function constructDecoration(tabStr,symbol,text,List) result(Decoration)
103 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
104 : !DEC$ ATTRIBUTES DLLEXPORT :: constructDecoration
105 : #endif
106 : use JaggedArray_mod, only: CharVec_type
107 : implicit none
108 : character(*), intent(in), optional :: tabStr, symbol, text
109 : type(CharVec_type), intent(in), optional :: List
110 : type(Decoration_type) :: Decoration
111 : end function constructDecoration
112 : end interface
113 :
114 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
115 :
116 : interface
117 : module subroutine writeDecoratedText(text,symbol,width,thicknessHorz,thicknessVert,marginTop,marginBot,outputUnit,newLine)
118 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
119 : !DEC$ ATTRIBUTES DLLEXPORT :: writeDecoratedText
120 : #endif
121 : use, intrinsic :: iso_fortran_env, only: output_unit
122 : use Constants_mod, only: IK
123 : implicit none
124 : character(*), intent(in) :: text
125 : character(*), intent(in), optional :: symbol,newLine
126 : integer(IK) , intent(in), optional :: width,thicknessHorz,thicknessVert,marginTop,marginBot
127 : integer(IK) , intent(in), optional :: outputUnit
128 : end subroutine writeDecoratedText
129 : end interface
130 :
131 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
132 :
133 : interface
134 : module subroutine writeDecoratedList(List,symbol,width,thicknessHorz,thicknessVert,marginTop,marginBot,outputUnit)
135 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
136 : !DEC$ ATTRIBUTES DLLEXPORT :: writeDecoratedList
137 : #endif
138 : use, intrinsic :: iso_fortran_env, only: output_unit
139 : use Constants_mod, only: IK
140 : implicit none
141 : type(CharVec_type), allocatable , intent(in) :: List(:)
142 : character(*) , intent(in), optional :: symbol
143 : integer(IK) , intent(in), optional :: width,thicknessHorz,thicknessVert,marginTop,marginBot
144 : integer(IK) , intent(in), optional :: outputUnit
145 : end subroutine writeDecoratedList
146 : end interface
147 :
148 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
149 :
150 : interface
151 : pure module function drawLine(symbol,width) result(line)
152 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
153 : !DEC$ ATTRIBUTES DLLEXPORT :: drawLine
154 : #endif
155 : use Constants_mod, only: IK
156 : implicit none
157 : character(*), intent(in), optional :: symbol
158 : integer(IK), intent(in) , optional :: width
159 : character(:), allocatable :: line
160 : end function drawLine
161 : end interface
162 :
163 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
164 :
165 : interface
166 : pure module function sandwich(text,symbol,width,thicknessHorz) result(sandwichedText)
167 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
168 : !DEC$ ATTRIBUTES DLLEXPORT :: sandwich
169 : #endif
170 : use Constants_mod, only: IK
171 : implicit none
172 : character(*), intent(in), optional :: text, symbol
173 : integer(IK), intent(in) , optional :: width,thicknessHorz
174 : character(:), allocatable :: sandwichedText
175 : end function sandwich
176 : end interface
177 :
178 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
179 :
180 : interface
181 : module subroutine write ( outputUnit &
182 : , marginTop &
183 : , marginBot &
184 : , count &
185 : , string &
186 : #if defined MEXPRINT_ENABLED
187 : , advance &
188 : #endif
189 : )
190 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
191 : !DEC$ ATTRIBUTES DLLEXPORT :: write
192 : #endif
193 : use, intrinsic :: iso_fortran_env, only: output_unit
194 : use Constants_mod, only: IK
195 : implicit none
196 : integer(IK) , intent(in), optional :: outputUnit
197 : integer(IK) , intent(in), optional :: marginTop, marginBot, count
198 : character(*), intent(in), optional :: string
199 : #if defined MEXPRINT_ENABLED
200 : logical , intent(in), optional :: advance
201 : #endif
202 : end subroutine write
203 : end interface
204 :
205 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
206 :
207 : interface
208 : module function getListOfLines(string,delimiter) result(ListOfLines)
209 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
210 : !DEC$ ATTRIBUTES DLLEXPORT :: getListOfLines
211 : #endif
212 : implicit none
213 : character(len=*) , intent(in) :: string
214 : character(len=*) , intent(in), optional :: delimiter
215 : type(CharVec_type), allocatable :: ListOfLines(:)
216 : end function getListOfLines
217 : end interface
218 :
219 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
220 :
221 : interface
222 : module function wrapText(string,width,split, pad) result(ListOfLines)
223 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
224 : !DEC$ ATTRIBUTES DLLEXPORT :: wrapText
225 : #endif
226 : use Constants_mod, only: IK
227 : implicit none
228 : character(*), intent(in) :: string
229 : integer(IK) , intent(in) :: width
230 : character(*), intent(in), optional :: split, pad
231 : type(CharVec_type), allocatable :: ListOfLines(:)
232 : end function wrapText
233 : end interface
234 :
235 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
236 :
237 : ! interface
238 : ! module function style(string, attr, clbg, clfg, isUnixShell) result(modifiedString)
239 : !#if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
240 : ! !DEC$ ATTRIBUTES DLLEXPORT :: style
241 : !#endif
242 : ! implicit none
243 : ! character(*), intent(in) :: string
244 : ! character(*), intent(in), optional :: attr, clbg, clfg
245 : ! logical, intent(in), optional :: isUnixShell
246 : ! character(:), allocatable :: modifiedString
247 : ! end function style
248 : ! end interface
249 :
250 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
251 :
252 : contains
253 :
254 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
255 :
256 : !> \brief
257 : !> Wrap the input text with ANSI/VT100 Control sequences to stylize and color the string.
258 : !>
259 : !> @param[in] string : The input string to be stylized.
260 : !> @param[in] attr : The requested attribute (**optional**). It can be:
261 : !> + `"off"` : All attributes off (0).
262 : !> + `"bold"` : Boldface text (1)
263 : !> + `"bright"` : Bright text (1)
264 : !> + `"dim"` : Dimmed text (2)
265 : !> + `"underlined"` : Underlined text (4)
266 : !> + `"blinking"` : Blinking text (5)
267 : !> + `"reverse"` : Reversed attributes text (7)
268 : !> + `"hidden"` : Hidden text (8)
269 : !> The **default** value is "off".
270 : !> @param[in] clfg : The Foreground color of the text (**optional**, see below for possible colors).
271 : !> @param[in] clbg : The Background color of the text (**optional**, see below for possible colors).
272 : !>
273 : !> \return
274 : !> `modifiedString` : The output string wrapped with the requested style and coloring.
275 : !>
276 : !> \remark
277 : !> Possible Foreground / Background colors are the following:
278 : !> + `"black"` : (30) / (40)
279 : !> + `"red"` : (31) / (41)
280 : !> + `"green"` : (32) / (42)
281 : !> + `"yellow"` : (33) / (43)
282 : !> + `"blue"` : (34) / (44)
283 : !> + `"magenta"` : (35) / (45)
284 : !> + `"cyan"` : (36) / (46)
285 : !> + `"light gray"` : (37) / (47)
286 : !> + `"dark gray"` : (90) / (100)
287 : !> + `"light red"` : (91) / (101)
288 : !> + `"light green"` : (92) / (102)
289 : !> + `"light yellow"` : (93) / (103)
290 : !> + `"light blue"` : (94) / (104)
291 : !> + `"light magenta"` : (95) / (105)
292 : !> + `"light cyan"` : (96) / (106)
293 : !> + `"white"` : (97) / (107)
294 : !
295 : ! For more information, see: https://misc.flogisoft.com/bash/tip_colors_and_formatting
296 43 : function style(string, attr, clfg, clbg) result(modifiedString)
297 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
298 : !DEC$ ATTRIBUTES DLLEXPORT :: style
299 : #endif
300 : use Constants_mod, only: ESC
301 : implicit none
302 : character(*), intent(in) :: string
303 : character(*), intent(in), optional :: attr, clfg, clbg
304 : character(:), allocatable :: modifiedString
305 : integer :: i
306 :
307 : ! cache the attribute / color list codes
308 :
309 43 : if (.not.allocated(mc_AnsiAttributeList)) then
310 27 : allocate(mc_AnsiAttributeList(ANSI_ATTRIBUTE_LIST_LEN))
311 3 : mc_AnsiAttributeList(1)%record = "off" ; mc_AnsiAttributeList(1)%code = "0"
312 3 : mc_AnsiAttributeList(2)%record = "bold" ; mc_AnsiAttributeList(2)%code = "1"
313 3 : mc_AnsiAttributeList(3)%record = "bright" ; mc_AnsiAttributeList(3)%code = "1"
314 3 : mc_AnsiAttributeList(4)%record = "dim" ; mc_AnsiAttributeList(4)%code = "2"
315 3 : mc_AnsiAttributeList(5)%record = "underlined" ; mc_AnsiAttributeList(5)%code = "4"
316 3 : mc_AnsiAttributeList(6)%record = "blinking" ; mc_AnsiAttributeList(6)%code = "5"
317 3 : mc_AnsiAttributeList(7)%record = "reverse" ; mc_AnsiAttributeList(7)%code = "7"
318 3 : mc_AnsiAttributeList(8)%record = "hidden" ; mc_AnsiAttributeList(8)%code = "8"
319 : end if
320 :
321 43 : if (.not.allocated(mc_AnsiForegroundColorList)) then
322 51 : allocate(mc_AnsiForegroundColorList(ANSI_COLOR_LIST_LEN))
323 3 : mc_AnsiForegroundColorList(1) %record = "black" ; mc_AnsiForegroundColorList(1) %code = "30"
324 3 : mc_AnsiForegroundColorList(2) %record = "red" ; mc_AnsiForegroundColorList(2) %code = "31"
325 3 : mc_AnsiForegroundColorList(3) %record = "green" ; mc_AnsiForegroundColorList(3) %code = "32"
326 3 : mc_AnsiForegroundColorList(4) %record = "yellow" ; mc_AnsiForegroundColorList(4) %code = "33"
327 3 : mc_AnsiForegroundColorList(5) %record = "blue" ; mc_AnsiForegroundColorList(5) %code = "34"
328 3 : mc_AnsiForegroundColorList(6) %record = "magenta" ; mc_AnsiForegroundColorList(6) %code = "35"
329 3 : mc_AnsiForegroundColorList(7) %record = "cyan" ; mc_AnsiForegroundColorList(7) %code = "36"
330 3 : mc_AnsiForegroundColorList(8) %record = "light gray" ; mc_AnsiForegroundColorList(8) %code = "37"
331 3 : mc_AnsiForegroundColorList(9) %record = "dark gray" ; mc_AnsiForegroundColorList(9) %code = "90"
332 3 : mc_AnsiForegroundColorList(10)%record = "light red" ; mc_AnsiForegroundColorList(10)%code = "91"
333 3 : mc_AnsiForegroundColorList(11)%record = "light green" ; mc_AnsiForegroundColorList(11)%code = "92"
334 3 : mc_AnsiForegroundColorList(12)%record = "light yellow" ; mc_AnsiForegroundColorList(12)%code = "93"
335 3 : mc_AnsiForegroundColorList(13)%record = "light blue" ; mc_AnsiForegroundColorList(13)%code = "94"
336 3 : mc_AnsiForegroundColorList(14)%record = "light magenta" ; mc_AnsiForegroundColorList(14)%code = "95"
337 3 : mc_AnsiForegroundColorList(15)%record = "light cyan" ; mc_AnsiForegroundColorList(15)%code = "96"
338 3 : mc_AnsiForegroundColorList(16)%record = "white" ; mc_AnsiForegroundColorList(16)%code = "97"
339 : end if
340 :
341 43 : if (.not.allocated(mc_AnsiBackgroundColorList)) then
342 51 : allocate(mc_AnsiBackgroundColorList(ANSI_COLOR_LIST_LEN))
343 3 : mc_AnsiBackgroundColorList(1) %record = "black" ; mc_AnsiBackgroundColorList(1) %code = "40"
344 3 : mc_AnsiBackgroundColorList(2) %record = "red" ; mc_AnsiBackgroundColorList(2) %code = "41"
345 3 : mc_AnsiBackgroundColorList(3) %record = "green" ; mc_AnsiBackgroundColorList(3) %code = "42"
346 3 : mc_AnsiBackgroundColorList(4) %record = "yellow" ; mc_AnsiBackgroundColorList(4) %code = "43"
347 3 : mc_AnsiBackgroundColorList(5) %record = "blue" ; mc_AnsiBackgroundColorList(5) %code = "44"
348 3 : mc_AnsiBackgroundColorList(6) %record = "magenta" ; mc_AnsiBackgroundColorList(6) %code = "45"
349 3 : mc_AnsiBackgroundColorList(7) %record = "cyan" ; mc_AnsiBackgroundColorList(7) %code = "46"
350 3 : mc_AnsiBackgroundColorList(8) %record = "light gray" ; mc_AnsiBackgroundColorList(8) %code = "47"
351 3 : mc_AnsiBackgroundColorList(9) %record = "dark gray" ; mc_AnsiBackgroundColorList(9) %code = "100"
352 3 : mc_AnsiBackgroundColorList(10)%record = "light red" ; mc_AnsiBackgroundColorList(10)%code = "101"
353 3 : mc_AnsiBackgroundColorList(11)%record = "light green" ; mc_AnsiBackgroundColorList(11)%code = "102"
354 3 : mc_AnsiBackgroundColorList(12)%record = "light yellow" ; mc_AnsiBackgroundColorList(12)%code = "103"
355 3 : mc_AnsiBackgroundColorList(13)%record = "light blue" ; mc_AnsiBackgroundColorList(13)%code = "104"
356 3 : mc_AnsiBackgroundColorList(14)%record = "light magenta" ; mc_AnsiBackgroundColorList(14)%code = "105"
357 3 : mc_AnsiBackgroundColorList(15)%record = "light cyan" ; mc_AnsiBackgroundColorList(15)%code = "106"
358 3 : mc_AnsiBackgroundColorList(16)%record = "white" ; mc_AnsiBackgroundColorList(16)%code = "107"
359 : end if
360 :
361 : ! construct the escape sequence
362 :
363 43 : modifiedString = ESC//"[0"
364 :
365 43 : if (present(attr)) then
366 129 : do i = 1, ANSI_ATTRIBUTE_LIST_LEN
367 129 : if (attr==mc_AnsiAttributeList(i)%record) then
368 43 : modifiedString = modifiedString // ";" // mc_AnsiAttributeList(i)%code
369 43 : exit
370 : end if
371 : end do
372 : end if
373 :
374 43 : if (present(clfg)) then
375 161 : do i = 1, ANSI_COLOR_LIST_LEN
376 161 : if (clfg==mc_AnsiForegroundColorList(i)%record) then
377 43 : modifiedString = modifiedString // ";" // mc_AnsiForegroundColorList(i)%code
378 43 : exit
379 : end if
380 : end do
381 : end if
382 :
383 43 : if (present(clbg)) then
384 0 : do i = 1, ANSI_COLOR_LIST_LEN
385 0 : if (clbg==mc_AnsiBackgroundColorList(i)%record) then
386 0 : modifiedString = modifiedString // ";" // mc_AnsiBackgroundColorList(i)%code
387 0 : exit
388 : end if
389 : end do
390 : end if
391 :
392 43 : modifiedString = modifiedString // "m" // string // ESC // "[0m"
393 :
394 86 : end function style
395 :
396 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
397 :
398 : !> \brief
399 : !> Return an IO Fortran format given the input characteristics.
400 : !> @param[in] width : The width of the target IO record (**optional**, default = dynamically set).
401 : !> @param[in] precision : The precision of the target IO record if it happens to be a real number (**optional**, default = dynamically set).
402 : !> @param[in] delim : The delimiter of the target IO record if it happens multiple entries (**optional**, default = "").
403 : !> @param[in] prefix : The prefix of the target IO record (**optional**, default = "").
404 : !>
405 : !> \return
406 : !> `formatStr` : The output format string to be used in IO.
407 1050 : pure function getGenericFormat(width,precision,delim,prefix) result(formatStr)
408 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
409 : !DEC$ ATTRIBUTES DLLEXPORT :: getGenericFormat
410 : #endif
411 : ! generates IO format strings, primarily for use in the output report files of ParaMonte
412 43 : use Constants_mod, only: IK
413 : use String_mod, only: num2str
414 : implicit none
415 : integer(IK) , intent(in), optional :: width
416 : integer(IK) , intent(in), optional :: precision
417 : character(*), intent(in), optional :: delim
418 : character(*), intent(in), optional :: prefix
419 1050 : character(:), allocatable :: widthStr
420 : character(:), allocatable :: formatStr
421 1050 : character(:), allocatable :: precisionStr
422 1050 : character(:), allocatable :: delimDefault
423 :
424 1050 : widthStr = "0"; if (present(width)) widthStr = num2str(width)
425 1050 : precisionStr = ""; if (present(precision)) precisionStr = "."//num2str(precision)
426 1050 : delimDefault = ""; if (present(delim)) delimDefault = ",:,'"//delim//"'"
427 1050 : formatStr = "*(g"//widthStr//precisionStr//delimDefault//"))"
428 1050 : if (present(prefix)) then
429 1038 : formatStr = "('" // prefix // "'," // formatStr
430 : else
431 12 : formatStr = "(" // formatStr
432 : end if
433 :
434 1050 : end function getGenericFormat
435 :
436 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
437 :
438 : end module Decoration_mod ! LCOV_EXCL_LINE
|