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
44 : !> This module contains the classes and procedures for setting up the `outputDelimiter` attribute of ParaMonte samplers.
45 : !> For more information, see the description of this attribute in the body of the module.
46 : !> \author Amir Shahmoradi
47 :
48 : module SpecBase_OutputDelimiter_mod
49 :
50 : use Constants_mod, only: IK
51 : implicit none
52 :
53 : character(*), parameter :: MODULE_NAME = "@SpecBase_OutputDelimiter_mod"
54 : integer(IK), parameter :: MAX_DELIMITER_LEN = 63_IK
55 :
56 : character(:), allocatable :: outputDelimiter ! namelist input
57 :
58 : type :: OutputDelimiter_type
59 : character(:), allocatable :: val
60 : character(:), allocatable :: def
61 : character(:), allocatable :: null
62 : character(:), allocatable :: desc
63 : contains
64 : procedure, pass :: set => setOutputDelimiter, checkForSanity, nullifyNameListVar
65 : end type OutputDelimiter_type
66 :
67 : interface OutputDelimiter_type
68 : module procedure :: constructOutputDelimiter
69 : end interface OutputDelimiter_type
70 :
71 : private :: constructOutputDelimiter, setOutputDelimiter
72 :
73 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
74 :
75 : contains
76 :
77 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
78 :
79 1047 : function constructOutputDelimiter(methodName) result(OutputDelimiterObj)
80 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
81 : !DEC$ ATTRIBUTES DLLEXPORT :: constructOutputDelimiter
82 : #endif
83 : use Constants_mod, only: NULL_SK
84 : use String_mod, only: num2str
85 : implicit none
86 : type(OutputDelimiter_type) :: OutputDelimiterObj
87 : character(*), intent(in) :: methodName
88 1047 : OutputDelimiterObj%def = ","
89 1047 : if (allocated(OutputDelimiterObj%null)) deallocate(OutputDelimiterObj%null)
90 1047 : allocate(character(MAX_DELIMITER_LEN) :: OutputDelimiterObj%null)
91 1047 : OutputDelimiterObj%null = repeat(NULL_SK, MAX_DELIMITER_LEN)
92 : OutputDelimiterObj%desc = &
93 : "outputDelimiter is a string variable, containing a sequence of one or more characters (excluding digits, the period &
94 : &symbol '.', and the addition and subtraction operators: '+' and '-'), that is used to specify the boundary between &
95 : &separate, independent information elements in the tabular output files of " // methodName // ". &
96 : &The string value must be enclosed by either single or double quotation marks when provided as input. &
97 : &To output in Comma-Separated-Values (CSV) format, set outputDelimiter = ','. If the input value is not provided, &
98 : &the default delimiter '" // OutputDelimiterObj%def // "' will be used when input outputColumnWidth = 0, and a single &
99 : &space character, '" // OutputDelimiterObj%def // "' will be used when input outputColumnWidth > 0. &
100 : &A value of '\t' is interpreted as the TAB character. To avoid this interpretation, use '\\\t' to &
101 : &yield '\t' without being interpreted as the TAB character. &
102 1047 : &The default value is '" // OutputDelimiterObj%def // "'."
103 1047 : end function constructOutputDelimiter
104 :
105 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
106 :
107 1047 : subroutine nullifyNameListVar(DescriptionObj)
108 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
109 : !DEC$ ATTRIBUTES DLLEXPORT :: nullifyNameListVar
110 : #endif
111 : implicit none
112 : class(OutputDelimiter_type), intent(inout) :: DescriptionObj
113 : !allocate( character(MAX_DELIMITER_LEN) :: outputDelimiter )
114 1047 : outputDelimiter = DescriptionObj%null
115 1047 : end subroutine nullifyNameListVar
116 :
117 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
118 :
119 2088 : pure subroutine setOutputDelimiter(OutputDelimiterObj, outputColumnWidth, outputDelimiter)
120 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
121 : !DEC$ ATTRIBUTES DLLEXPORT :: setOutputDelimiter
122 : #endif
123 1047 : use Constants_mod, only: TAB
124 : implicit none
125 : class(OutputDelimiter_type), intent(inout) :: OutputDelimiterObj
126 : integer(IK) , intent(in) :: outputColumnWidth
127 : character(*), intent(in), optional :: outputDelimiter
128 1086 : if (present(outputDelimiter)) OutputDelimiterObj%val = trim(adjustl(outputDelimiter))
129 2088 : if (OutputDelimiterObj%val==OutputDelimiterObj%null) then
130 1029 : if (allocated(OutputDelimiterObj%val)) deallocate(OutputDelimiterObj%val)
131 1029 : if (outputColumnWidth==0_IK) then
132 1023 : OutputDelimiterObj%val = OutputDelimiterObj%def
133 : else
134 6 : OutputDelimiterObj%val = " "
135 : end if
136 1059 : elseif (OutputDelimiterObj%val=="") then
137 : !if (allocated(OutputDelimiterObj%val)) deallocate(OutputDelimiterObj%val)
138 12 : OutputDelimiterObj%val = " "
139 1047 : elseif (OutputDelimiterObj%val=="\t") then
140 6 : OutputDelimiterObj%val = TAB
141 1041 : elseif (OutputDelimiterObj%val=="\\t") then
142 6 : OutputDelimiterObj%val = "\t"
143 : end if
144 4176 : end subroutine setOutputDelimiter
145 :
146 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
147 :
148 1035 : subroutine checkForSanity(OutputDelimiterObj, Err, methodName)
149 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
150 : !DEC$ ATTRIBUTES DLLEXPORT :: checkForSanity
151 : #endif
152 2088 : use Err_mod, only: Err_type
153 : use String_mod, only: isDigit
154 : implicit none
155 : class(OutputDelimiter_type), intent(in) :: OutputDelimiterObj
156 : type(Err_type), intent(inout) :: Err
157 : character(*), intent(in) :: methodName
158 : character(*), parameter :: PROCEDURE_NAME = "@checkForSanity()"
159 1035 : character(:), allocatable :: delimiter
160 : integer :: delimiterLen, i
161 1035 : delimiter = trim(adjustl(OutputDelimiterObj%val))
162 1035 : delimiterLen = len(delimiter)
163 2178 : do i = 1, delimiterLen
164 2178 : if (isDigit(delimiter(i:i)).or.delimiter(i:i)==".".or.delimiter(i:i)=="-".or.delimiter(i:i)=="+") then
165 18 : Err%occurred = .true.
166 18 : exit
167 : end if
168 : end do
169 1035 : if (Err%occurred) then
170 : Err%msg = Err%msg // &
171 : MODULE_NAME // PROCEDURE_NAME // ": Error occurred. &
172 : &The input value for variable outputDelimiter cannot contain any digits or the period symbol '.' or '-' &
173 : &or '+'. If you are unsure about the appropriate value for this variable, simply drop it from the input." &
174 30 : // methodName // " will automatically assign an appropriate value to it.\n\n"
175 : end if
176 1035 : end subroutine checkForSanity
177 :
178 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
179 :
180 : end module SpecBase_OutputDelimiter_mod ! LCOV_EXCL_LINE
|