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 `chainFileFormat` 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_ChainFileFormat_mod
49 :
50 : use Constants_mod, only: IK
51 : implicit none
52 :
53 : character(*), parameter :: MODULE_NAME = "@SpecBase_ChainFileFormat_mod"
54 :
55 : integer(IK), parameter :: MAX_LEN_CHAIN_FILE_FORMAT = 63_IK
56 :
57 : character(MAX_LEN_CHAIN_FILE_FORMAT) :: chainFileFormat
58 :
59 : type :: ChainFileFormat_type
60 : logical :: isCompact
61 : logical :: isVerbose
62 : logical :: isBinary
63 : character(7) :: compact
64 : character(7) :: verbose
65 : character(6) :: binary
66 : character(:), allocatable :: def
67 : character(:), allocatable :: val
68 : character(:), allocatable :: null
69 : character(:), allocatable :: desc
70 : contains
71 : procedure, pass :: set => setChainFileFormat, checkForSanity, nullifyNameListVar
72 : end type ChainFileFormat_type
73 :
74 : interface ChainFileFormat_type
75 : module procedure :: constructChainFileFormat
76 : end interface ChainFileFormat_type
77 :
78 : private :: constructChainFileFormat, setChainFileFormat, checkForSanity, nullifyNameListVar
79 :
80 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
81 :
82 : contains
83 :
84 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
85 :
86 1047 : function constructChainFileFormat(methodName) result(ChainFileFormatObj)
87 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
88 : !DEC$ ATTRIBUTES DLLEXPORT :: constructChainFileFormat
89 : #endif
90 : use Constants_mod, only: NULL_SK, FILE_EXT, FILE_TYPE
91 : use String_mod, only: num2str
92 : implicit none
93 : character(*), intent(in) :: methodName
94 : type(ChainFileFormat_type) :: ChainFileFormatObj
95 :
96 1047 : ChainFileFormatObj%isCompact = .false.
97 1047 : ChainFileFormatObj%isVerbose = .false.
98 1047 : ChainFileFormatObj%isBinary = .false.
99 1047 : ChainFileFormatObj%compact = "compact"
100 1047 : ChainFileFormatObj%verbose = "verbose"
101 1047 : ChainFileFormatObj%binary = FILE_TYPE%binary
102 1047 : ChainFileFormatObj%def = ChainFileFormatObj%compact
103 :
104 1047 : ChainFileFormatObj%null = repeat(NULL_SK, MAX_LEN_CHAIN_FILE_FORMAT)
105 :
106 : ChainFileFormatObj%desc = &
107 : "chainFileFormat is a string variable that represents the format of the output chain file(s) of "// methodName // &
108 : " simulation. The string value must be enclosed by either single or double quotation marks when provided as input. &
109 : &Three values are possible:\n\n&
110 : & chainFileFormat = 'compact'\n\n&
111 : & This is the ASCII (text) file format which is human-readable but does not preserve the full accuracy of the &
112 : &output values. It is also a significantly slower mode of chain file generation, compared to the binary file format (see below). &
113 : &If the compact format is specified, each of the repeating MCMC states will be condensed into a single entry (row) in &
114 : &the output MCMC chain file. Each entry will be then assigned a sample-weight that is equal to the number of repetitions of &
115 : &that state in the MCMC chain. Thus, each row in the output chain file will represent a unique sample from the objective function. &
116 : &This will lead to a significantly smaller ASCII chain file and faster output size compared to the verbose chain file format (see below).\n\n&
117 : & chainFileFormat = 'verbose'\n\n&
118 : & This is the ASCII (text) file format which is human-readable but does not preserve the full accuracy of &
119 : &the output values. It is also a significantly slower mode of chain file generation, &
120 : &compared to both compact and binary chain file formats (see above and below). &
121 : &If the verbose format is specified, all MCMC states will have equal sample-weights of 1 in the output chain file. &
122 : &The verbose format can lead to much larger chain file sizes than the compact and binary file formats. &
123 : &This is especially true if the target objective function has a very high-dimensional state space.\n\n&
124 : & chainFileFormat = '" // ChainFileFormatObj%binary // "'\n\n&
125 : & This is the binary file format which is not human-readable, but preserves the exact values in the output &
126 : &MCMC chain file. It is also often the fastest mode of chain file generation. If the binary file format is chosen, the chain &
127 : &will be automatically output in the compact format (but as binary) to ensure the production of the smallest-possible output chain file. &
128 : &Binary chain files will have the " // FILE_EXT%binary // " file extensions. Use the binary format if you need full accuracy representation &
129 : &of the output values while having the smallest-size output chain file in the shortest time possible.\n\n&
130 : &The default value is chainFileFormat = '" // ChainFileFormatObj%def // "' as it provides a reasonable trade-off between &
131 1047 : &speed and output file size while generating human-readable chain file contents. Note that the input values are case-insensitive."
132 1047 : end function constructChainFileFormat
133 :
134 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
135 :
136 1047 : subroutine nullifyNameListVar(ChainFileFormatObj)
137 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
138 : !DEC$ ATTRIBUTES DLLEXPORT :: nullifyNameListVar
139 : #endif
140 : implicit none
141 : class(ChainFileFormat_type), intent(in) :: ChainFileFormatObj
142 1047 : chainFileFormat = ChainFileFormatObj%null
143 1047 : end subroutine nullifyNameListVar
144 :
145 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
146 :
147 1113 : subroutine setChainFileFormat(ChainFileFormatObj,chainFileFormat)
148 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
149 : !DEC$ ATTRIBUTES DLLEXPORT :: setChainFileFormat
150 : #endif
151 1047 : use String_mod, only: getLowerCase
152 : implicit none
153 : class(ChainFileFormat_type), intent(inout) :: ChainFileFormatObj
154 : character(*), intent(in) :: chainFileFormat
155 1113 : character(:), allocatable :: lowerCaseVal
156 1113 : ChainFileFormatObj%val = trim(adjustl(chainFileFormat))
157 1113 : if ( ChainFileFormatObj%val==trim(adjustl(ChainFileFormatObj%null)) ) then
158 1011 : ChainFileFormatObj%val = trim(adjustl(ChainFileFormatObj%def))
159 : end if
160 1113 : lowerCaseVal = getLowerCase(ChainFileFormatObj%val)
161 1113 : ChainFileFormatObj%iscompact = lowerCaseVal == getLowerCase(ChainFileFormatObj%compact)
162 1113 : ChainFileFormatObj%isverbose = lowerCaseVal == getLowerCase(ChainFileFormatObj%verbose)
163 1113 : ChainFileFormatObj%isBinary = lowerCaseVal == getLowerCase(ChainFileFormatObj%binary)
164 1113 : end subroutine setChainFileFormat
165 :
166 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
167 :
168 1035 : subroutine checkForSanity(ChainFileFormat,Err,methodName)
169 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
170 : !DEC$ ATTRIBUTES DLLEXPORT :: checkForSanity
171 : #endif
172 1113 : use Err_mod, only: Err_type
173 : use String_mod, only: num2str
174 : implicit none
175 : class(ChainFileFormat_type), intent(in) :: ChainFileFormat
176 : character(*), intent(in) :: methodName
177 : type(Err_type), intent(inout) :: Err
178 : character(*), parameter :: PROCEDURE_NAME = "@checkForSanity()"
179 1035 : if ( .not.(ChainFileFormat%isCompact .or. ChainFileFormat%isVerbose .or. ChainFileFormat%isBinary) ) then
180 12 : Err%occurred = .true.
181 : Err%msg = Err%msg // &
182 : MODULE_NAME // PROCEDURE_NAME // ": Error occurred. &
183 : &The input requested chain file format ('" // ChainFileFormat%val // &
184 : "') represented by the variable chainFileFormat cannot be anything other than '" // &
185 : ChainFileFormat%compact // "' or '" // ChainFileFormat%verbose // "' or '" // ChainFileFormat%binary // "'. &
186 : &If you don't know an appropriate value for chainFileFormat, drop it from the input list. " // methodName // &
187 12 : " will automatically assign an appropriate value to it.\n\n"
188 : end if
189 2070 : end subroutine checkForSanity
190 :
191 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
192 :
193 : end module SpecBase_ChainFileFormat_mod ! LCOV_EXCL_LINE
|