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 : !> \mainpage ParaMonte: Plain Powerful <b>Para</b>llel <b>Monte</b> Carlo Library
44 : !>
45 : !> This is the <b>`ParaMonte::Kernel`</b> developer documentation website.
46 : !>
47 : !> What is ParaMonte?
48 : !> ==================
49 : !>
50 : !> ParaMonte is a serial / parallel library of Monte Carlo routines for sampling
51 : !> mathematical objective functions of arbitrary-dimensions, in particular,
52 : !> the posterior distributions of Bayesian models in data science,
53 : !> Machine Learning, and scientific inference, with the design
54 : !> goal of unifying the
55 : !>
56 : !> + **automation** of Monte Carlo simulations,
57 : !> + **user-friendliness** of the library,
58 : !> + **accessibility** from multiple programming environments,
59 : !> + **high-performance** at runtime, and,
60 : !> + **scalability** across many parallel processors.
61 : !>
62 : !> ### ParaMonte project's repository
63 : !>
64 : !> The ParaMonte library is open-source is permanently located and maintained on **GitHub** at:
65 : !>
66 : !> [**https://github.com/cdslaborg/paramonte**](https://github.com/cdslaborg/paramonte)
67 : !>
68 : !> ### ParaMonte usage and examples website
69 : !>
70 : !> For information about the usage and examples visit **the ParaMonte documentation and examples website** at:
71 : !>
72 : !> [**https://www.cdslab.org/paramonte**](https://www.cdslab.org/paramonte)
73 : !>
74 : !> ### ParaMonte API documentation website
75 : !>
76 : !> For the API developer documentation, visit:
77 : !>
78 : !> [**https://www.cdslab.org/paramonte/notes/api/kernel**](https://www.cdslab.org/paramonte/notes/api/kernel)
79 : !>
80 : !> ParaMonte samplers
81 : !> ==================
82 : !>
83 : !> The routines currently supported by the ParaMonte kernel library include:
84 : !>
85 : !> ### ParaDRAM
86 : !>
87 : !> Parallel Delayed-Rejection Adaptive Metropolis-Hastings Markov
88 : !> Chain Monte Carlo Sampler. For a quick start, example scripts,
89 : !> and instructions on how to use he ParaDRAM sampler in your
90 : !> language of choice, visit:
91 : !>
92 : !> [**https://www.cdslab.org/paramonte/notes/usage/paradram/interface**](https://www.cdslab.org/paramonte/notes/usage/paradram/interface)
93 : !>
94 : !> Naming conventions
95 : !> ==================
96 : !>
97 : !> + The CamelCase naming style is used throughout the entire ParaMonte
98 : !> kernel library.
99 : !>
100 : !> + Although the Fortran language is case-insensitive, by convention,
101 : !> all scalar variable names begin with a lower case, whereas all vectors,
102 : !> arrays, types, and module names begin with an upper-case letter.
103 : !>
104 : !> + The name of any variable that represents a vector of values is normally
105 : !> suffixed with `Vec` or `Vector`, for example: `StartPointVec`, ...
106 : !>
107 : !> + The name of any variable that represents a matrix of values is normally
108 : !> suffixed with `Mat`, for example: `proposalStartCorMat`, ...
109 : !>
110 : !> + The name of any variable that represents a list of varying-size values
111 : !> is normally suffixed with `List`, like: `variableNameList`, ...
112 : !>
113 : !> + All static functions or methods of classes begin with a lowercase verb.
114 : !>
115 : !> + Significant attempt has been made to end all boolean variables with a
116 : !> passive verb, such that the full variable name virtually forms a
117 : !> proposition, that is, an English-language statement that should
118 : !> be either `.true.` or `.false.`, set by the user.
119 : !>
120 : !-------------------------------------------------------------------------------
121 :
122 : !> \brief This module contains the base class of all ParaMonte samplers and its associated methods.
123 : !> \author Amir Shahmoradi
124 :
125 : module ParaMonte_mod
126 :
127 : use Parallelism_mod, only: Image_type
128 : use Decoration_mod, only: Decoration_type
129 : use Constants_mod, only: RK, IK, HUGE_IK, HUGE_RK
130 : use String_mod, only: IntStr_type
131 : use System_mod, only: OS_type
132 : use Timer_mod, only: Timer_type
133 : use File_mod, only: File_type
134 : use Path_mod, only: MAX_FILE_PATH_LEN
135 : use Err_mod, only: Err_type, informUser, note, warn, abort
136 : use SpecBase_mod, only: SpecBase_type
137 : use ParaMonteChainFileContents_mod, only: ChainFileContents_type
138 :
139 : implicit none
140 :
141 : public
142 :
143 : character(*), parameter :: MODULE_NAME = "@ParaMonte_mod"
144 :
145 : !> The Quantile derived type containing the distribution quantiles.
146 : type :: QuantileProbability_type
147 : integer(IK) :: count = 9_IK
148 : real(RK) :: Value(9) = [0._RK,0.05_RK,0.10_RK,0.25_RK,0.50_RK,0.75_RK,0.90_RK,0.95_RK,1.0_RK]
149 : character(4) :: Name(9) = [" Q0"," Q5"," Q10"," Q25"," Q50"," Q75"," Q90"," Q95","Q100"]
150 : end type QuantileProbability_type
151 : type(QuantileProbability_type), parameter :: QPROB = QuantileProbability_type()
152 :
153 : !> The derived type containing the statistical moments of the objective function.
154 : type :: Moment_type
155 : integer(IK) :: count = 0_IK
156 : real(RK), allocatable :: Mean(:)
157 : real(RK), allocatable :: CovMat(:,:)
158 : real(RK), allocatable :: CorMat(:,:)
159 : real(RK), allocatable :: Quantile(:,:)
160 : end type Moment_type
161 :
162 : !> The derived type containing the number of function calls.
163 : type :: ParaMonteNumFunCall_type
164 : integer(IK) :: accepted !< The number of objective function calls accepted in the simulation.
165 : integer(IK) :: acceptedRejected !< The accepted + rejected function calls.
166 : end type ParaMonteNumFunCall_type
167 :
168 : !> The derived type containing information about the function mode.
169 : type :: ParaMonteLogFuncMode_type
170 : real(RK) :: val !< The function mode.
171 : real(RK), allocatable :: Crd(:) !< The location of the mode in the domain of the the objective function.
172 : end type ParaMonteLogFuncMode_type
173 :
174 : !> The derived type containing information about the statistics of the objective function and the runtime performance of the simulation.
175 : type :: ParaMonteStatistics_type
176 : real(RK) :: avgTimePerFunCalInSec = 0._RK !< Average time per objective function call.
177 : real(RK) :: avgCommTimePerFunCall = 0._RK !< Average inter-process communication time per function call.
178 : type(Moment_type) :: Sample !< The statistical moments of the objective function.
179 : end type ParaMonteStatistics_type
180 :
181 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
182 : ! ParaMonte IO variables and types
183 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
184 :
185 : type, extends(File_type) :: LogFile_type
186 : type(IntStr_type) :: maxColWidth
187 : character(6) :: suffix = "report"
188 : end type LogFile_type
189 :
190 : type, extends(File_type) :: TimeFile_type
191 : character(8) :: suffix = "progress"
192 : end type TimeFile_type
193 :
194 : type, extends(File_type) :: ChainFile_type
195 : character(5) :: suffix = "chain"
196 : end type ChainFile_type
197 :
198 : type, extends(File_type) :: SampleFile_type
199 : character(6) :: suffix = "sample"
200 : end type SampleFile_type
201 :
202 : type, extends(File_type) :: RestartFile_type
203 : integer(IK) :: counter = 0_IK
204 : character(7) :: suffix = "restart"
205 : end type RestartFile_type
206 :
207 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
208 : ! ParaMonte type
209 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
210 :
211 : !> The `ParaMonte_type` sampler base class.
212 : type :: ParaMonte_type
213 : type(IntStr_type) :: nd !< The number of dimensions of the domain of the objective function.
214 : character(8) :: name !< The ParaMonte sampler method name.
215 : character(16) :: brand !< The ParaMonte sampler brand (The decorated tabbed version of the sampler name).
216 : character(:), allocatable :: date !< The date of the simulation.
217 : character(:), allocatable :: version !< The ParaMonte version.
218 : logical :: isDryRun !< The logical flag that, if `.true.`, indicates the simulation is in restart mode.
219 : logical :: isFreshRun !< The logical flag that, if `.false.`, indicates the simulation is in new mode.
220 : logical :: procArgNeeded !< The logical flag that, if `.true.`, requires reading the simulation specification
221 : !< from the Object-Oriented interface of the sampler and prioritizing them over the
222 : !< corresponding values in the external input file.
223 : logical :: procArgHasPriority !< The logical flag that, if `.true.`, indicates that the simulation specifications
224 : !< have priority over the corresponding values from the external input file.
225 : logical :: inputFileArgIsPresent !< The logical flag that indicates whether the external input file has been provided by the user.
226 : type(OS_type) :: OS !< An object of class [OS_type](@ref system_mod::os_type) containing information about the Operating System.
227 : type(Err_type) :: Err !< An object of class [Err_type](@ref err_mod::err_type) containing error-handling information.
228 : !< about error occurrence and message during the simulation setup and runtime.
229 : type(Image_type) :: Image !< An object of type [Image_type](@ref parallelism_mod::image_type) containing information about
230 : !< the processor count and types in the simulation.
231 : type(SpecBase_type) :: SpecBase !< An object of class [SpecBase_type](@ref specbase_mod::specbase_type) containing information
232 : !< about the basic simulation specification properties.
233 : !type(ParaMonteStatistics_type) :: Stats
234 : type(Timer_type) :: Timer !< An object of class [Timer_type](@ref timer_mod::timer_type) used for timing of the simulation.
235 : type(File_type) :: InputFile !< An object of class [File_type](@ref file_mod::file_type) containing information about the simulation input file.
236 : type(LogFile_type) :: LogFile !< An object of class [LogFile_type](@ref logfile_type) containing information about the simulation report file.
237 : type(TimeFile_type) :: TimeFile !< An object of class [TimeFile_type](@ref timefile_type) containing information about the simulation timing.
238 : type(ChainFile_type) :: ChainFile !< An object of class [ChainFile_type](@ref chainfile_type) containing information about the simulation output chain.
239 : type(SampleFile_type) :: SampleFile !< An object of class [SampleFile_type](@ref samplefile_type) containing information about the simulation output sample.
240 : type(RestartFile_type) :: RestartFile !< An object of class [RestartFile_type](@ref restartfile_type) containing information about the simulation output restart.
241 : type(ChainFileContents_type) :: Chain !< An object of class [ChainFileContents_type](@ref paramontechainfilecontents_mod::chainfilecontents_type) containing information and methods for chain IO.
242 : type(Decoration_type) :: Decor !< An object of class [Decoration_type](@ref decoration_mod::decoration_type) containing IO decoration tools.
243 : #if defined CODECOV_ENABLED || defined SAMPLER_TEST_ENABLED
244 : !> These variables are exclusively used for testing the deterministic restart functionality of ParaDXXX samplers.
245 : !> This block must not be activated under any other circumstances.
246 : !> Under normal testing conditions (other than testing the restart functionality, self%testSamplingCountTarget > self%testSamplingCounter must always hold.
247 : !> To test the restart functionality under any serial or distributed parallelization schemes, set self%testSamplingCountTarget < chainSize.
248 : !> The simulation will automatically, but gracefully, interrupt when this target value is reached or surpassed.
249 : integer(IK) :: testSamplingCountTarget = huge(1_IK) !< The external user-specified target count at which the code will break with a simulation interruption error message.
250 : integer(IK) :: testSamplingCounter = 0_IK !< The sampling counter defined by all images. This is a private component not to be changed by the user.
251 : #endif
252 : contains
253 : procedure, pass :: reportDesc
254 : procedure, pass :: setupParaMonte
255 : procedure, pass :: addSplashScreen
256 : procedure, pass :: setupOutputFiles
257 : procedure, pass :: noteUserAboutEnvSetup
258 : procedure, pass :: addCompilerPlatformInfo
259 : procedure, pass :: warnUserAboutInputFilePresence
260 : procedure, pass :: setWarnAboutProcArgHasPriority
261 : procedure, pass :: warnUserAboutMissingNamelist
262 : procedure, nopass :: informUser, note, warn, abort
263 : end type ParaMonte_type
264 :
265 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
266 :
267 : contains
268 :
269 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
270 :
271 : !> \brief
272 : !> This procedure is a method of the [ParaMonte_type](@ref paramonte_type) class.
273 : !> Set up the ParaMonte sampler with the requested input specifications. This method,
274 : !> + sets up initial variables,
275 : !> + and constructs the default and null values for `SpecBase`.
276 : !> + `self%InputFile%exists = .true.` if the input file exists and opens and assigns to it a unit number and sets
277 : !> and `self%InputFile%isOpen = .true.` if the opening process is successful.
278 : !> + If the input file exists, the path used to open it successfully will be also written to `InpuFile%Path%modified`.
279 : !>
280 : !> @param[inout] self : An object of class [ParaMonte_type](@ref paramonte_type).
281 : !> @param[in] nd : The number of dimensions of the domain of the objective function.
282 : !> @param[in] name : The name of the sampler. Example: `ParaDRAM`.
283 : !> @param[in] inputFile : The path to the input file, or the contents of an input file.
284 : !>
285 : !> \warning
286 : !> This routine has to be called by all images (processes).
287 1047 : subroutine setupParaMonte(self,nd,name,inputFile)
288 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
289 : !DEC$ ATTRIBUTES DLLEXPORT :: setupParaMonte
290 : #endif
291 : use, intrinsic :: iso_fortran_env, only: output_unit
292 : use Decoration_mod, only: INDENT
293 : use Constants_mod, only: IK, NLC
294 : use String_mod, only: getLowerCase, num2str
295 : use System_mod, only: OS_type
296 : implicit none
297 : class(ParaMonte_type), intent(inout) :: self
298 : integer(IK), intent(in) :: nd
299 : character(*), intent(in) :: name !, date, version
300 : character(*), intent(in), optional :: inputFile
301 : character(*), parameter :: PROCEDURE_NAME = MODULE_NAME // "@setupParaMonte()"
302 :
303 1047 : self%LogFile%unit = output_unit ! temporarily set the report file to stdout.
304 1047 : self%Err%occurred = .false.
305 1047 : self%Err%msg = ""
306 :
307 1047 : self%Timer = Timer_type(self%Err)
308 1047 : if (self%Err%occurred) then
309 : ! LCOV_EXCL_START
310 : self%Err%msg = PROCEDURE_NAME // ": Error occurred while setting up the " // self%name // "timer."//NLC// self%Err%msg
311 : call self%abort( Err = self%Err, prefix = self%brand, newline = NLC, outputUnit = self%LogFile%unit )
312 : return
313 : end if
314 : ! LCOV_EXCL_STOP
315 :
316 1047 : self%nd%val = nd
317 1127 : self%Decor = Decoration_type() ! initialize the TAB character and decoration symbol to the default values.
318 :
319 1047 : self%name = name
320 1047 : self%brand = INDENT // self%name
321 : #if defined INTEL_COMPILER_ENABLED || GNU_COMPILER_ENABLED
322 1047 : self%date = "Build: " // __TIMESTAMP__
323 : #else
324 : self%date = "Unknown Release Date"
325 : #endif
326 : #if defined PARAMONTE_VERSION
327 : self%version = "Version " // PARAMONTE_VERSION
328 : #else
329 : ! WARNING: The following ParaMonte library version tag as it will be replaced by the version
330 : ! WARNING: that is generated by the preprocessing build script of the ParaMonte library.
331 : ! WARNING: This is superior to the above method of using the compiler Preprocessor
332 : ! WARNING: since CMAKE triggers a complete lengthy rebuild of the library when the
333 : ! WARNING: only the library version has changed.
334 1047 : self%version = "Unknown ParaMonte Version"
335 : #include "ParaMonte_mod@version@kernel.inc.f90"
336 : #endif
337 :
338 : ! setup general processor / coarray image variables
339 :
340 1047 : call self%Image%query()
341 :
342 : ! setup formatting variables
343 :
344 1047 : self%nd%str = num2str(self%nd%val)
345 :
346 : ! determine OS. Should be only needed by the Leader processes. But apparently not.
347 :
348 1047 : call self%OS%query()
349 1047 : if (self%OS%Err%occurred) then
350 : ! LCOV_EXCL_START
351 : self%Err = self%OS%Err
352 : self%Err%msg = PROCEDURE_NAME // ": Error occurred while querying OS type."//NLC//self%Err%msg
353 : call self%abort( Err = self%Err, prefix = self%brand, newline = NLC, outputUnit = self%LogFile%unit )
354 : return
355 : end if
356 : ! LCOV_EXCL_STOP
357 :
358 : ! This is where SystemInfo used to live, but not anymore.
359 :
360 : #if ! (defined CODECOV_ENABLED || defined SAMPLER_TEST_ENABLED)
361 : blockSplashByFirstImage: if (self%Image%isFirst) then
362 : call self%addSplashScreen()
363 : call self%noteUserAboutEnvSetup()
364 : end if blockSplashByFirstImage
365 : #endif
366 :
367 : ! check if input file exists by all images
368 :
369 1047 : self%InputFile%isInternal = .false.
370 1047 : self%inputFileArgIsPresent = present(inputFile)
371 1047 : blockInputFileExistence: if (self%inputFileArgIsPresent) then
372 504 : self%InputFile = File_type( path=inputFile, status="old", OS=self%OS )
373 504 : if (self%InputFile%Err%occurred) then
374 : ! LCOV_EXCL_START
375 : self%Err = self%InputFile%Err
376 : self%Err%msg = PROCEDURE_NAME//": Error occurred while attempting to setup the user's input file='"//inputFile//"'."//NLC//self%Err%msg
377 : call self%abort( Err = self%Err, prefix = self%brand, newline = NLC, outputUnit = self%LogFile%unit )
378 : return
379 : end if
380 : ! LCOV_EXCL_STOP
381 : ! determine if the file is internal
382 504 : self%InputFile%isInternal = self%inputFileArgIsPresent .and. .not.self%InputFile%exists .and. index(getLowerCase(inputFile),"&"//getLowerCase(self%name)) > 0
383 504 : if (.not.(self%InputFile%isInternal .or. self%InputFile%exists)) then
384 : ! file is given, but is neither a path to an external file, nor an internal file containing a namelist
385 : ! Therefore, there must be an error/mistake by the user.
386 : self%Err%msg = "The user's input file='"//inputFile//"' is neither the path to an existing " // &
387 : "external input file nor a string containing the input "//self%name//" specifications namelist. &
388 : &This may be due to the user's mistake, providing a wrong path to the input external file or &
389 : &a wrong list of input specifications for the " //self%name// " simulation. " //self%name//" will &
390 18 : &assume no input specifications file is given by the user..."
391 18 : if (self%Image%isFirst) call self%warn(msg=self%Err%msg, prefix=self%brand, newline=NLC, outputUnit=self%LogFile%unit)
392 18 : self%inputFileArgIsPresent = .false.
393 : end if
394 : end if blockInputFileExistence
395 :
396 1047 : if (self%Image%isFirst) call self%warnUserAboutInputFilePresence()
397 :
398 : ! Set the default and null values for ParaMonte SpecBase
399 :
400 1047 : self%SpecBase = SpecBase_type(nd=self%nd%val,methodName=self%name,imageID=self%Image%id,imageCount=self%Image%count)
401 :
402 1047 : end subroutine setupParaMonte
403 :
404 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
405 :
406 : !> \brief
407 : !> This procedure is a method of the [ParaMonte_type](@ref paramonte_type) class.
408 : !> Add a splash screen to the output report file.
409 : !>
410 : !> @param[inout] self : An object of class [ParaMonte_type](@ref paramonte_type).
411 : !>
412 : !> \remark
413 : !> This routine has to be called by all leader images (processes).
414 359 : subroutine addSplashScreen(self)
415 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
416 : !DEC$ ATTRIBUTES DLLEXPORT :: addSplashScreen
417 : #endif
418 : implicit none
419 : class(ParaMonte_type), intent(inout) :: self
420 :
421 : self%Decor%text = &
422 : "\n\n"// &
423 : !self%name // "\n" // &
424 : "ParaMonte\n"// &
425 : "Plain Powerful Parallel\n"// &
426 : "Monte Carlo Library\n"// &
427 : "\n"// &
428 : self%version // "\n" // &
429 : "\n"// &
430 : self%date // "\n" // &
431 : "\n"// &
432 : "Department of Physics\n"// &
433 : "Computational & Data Science Lab\n"// &
434 : "Data Science Program, College of Science\n"// &
435 : "The University of Texas at Arlington\n"// &
436 : "\n"// &
437 : "originally developed at\n"// &
438 : "\n"// &
439 : "Multiscale Modeling Group\n"// &
440 : "Center for Computational Oncology (CCO)\n"// &
441 : "Oden Institute for Computational Engineering and Sciences\n"// &
442 : "Department of Aerospace Engineering and Engineering Mechanics\n"// &
443 : "Department of Neurology, Dell-Seton Medical School\n"// &
444 : "Department of Biomedical Engineering\n"// &
445 : "The University of Texas at Austin\n"// &
446 : "\n"// &
447 : "For questions and further information, please contact:\n"// &
448 : "\n"// &
449 : "Amir Shahmoradi\n"// &
450 : "\n"// &
451 : "shahmoradi@utexas.edu\n"// &
452 : "amir.shahmoradi@uta.edu\n"// &
453 : "ashahmoradi@gmail.com\n"// &
454 : !"amir@physics.utexas.edu\n"// &
455 : !"amir@austin.utexas.edu\n"// &
456 : !"amir@ph.utexas.edu\n"// &
457 : "\n"// &
458 : !"https://www.shahmoradi.org\n"// &
459 : !"shahmoradi.org\n"// &
460 : "cdslab.org/pm\n"// &
461 : "\n"// &
462 : "https://www.cdslab.org/paramonte/\n"// &
463 359 : "\n"
464 :
465 : call self%Decor%writeDecoratedText ( text=self%Decor%text & ! LCOV_EXCL_LINE
466 : , symbol="*" & ! LCOV_EXCL_LINE
467 : , width=132 & ! LCOV_EXCL_LINE
468 : , thicknessHorz=4 & ! LCOV_EXCL_LINE
469 : , thicknessVert=2 & ! LCOV_EXCL_LINE
470 : , marginTop=1 & ! LCOV_EXCL_LINE
471 : , marginBot=2 & ! LCOV_EXCL_LINE
472 : , outputUnit=self%LogFile%unit & ! LCOV_EXCL_LINE
473 : , newLine="\n" & ! LCOV_EXCL_LINE
474 359 : )
475 :
476 1047 : end subroutine addSplashScreen
477 :
478 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
479 :
480 : !> \brief
481 : !> Add information about the compiler and the platform/OS to the output report file(s).
482 : !>
483 : !> @param[inout] self : An object of class [ParaMonte_type](@ref paramonte_type).
484 : !>
485 : !> \remark
486 : !> This procedure is a method of the [ParaMonte_type](@ref paramonte_type) class.
487 : !>
488 : !> \remark
489 : !> This routine has to be called by all leader images (processes).
490 359 : subroutine addCompilerPlatformInfo(self)
491 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
492 : !DEC$ ATTRIBUTES DLLEXPORT :: addCompilerPlatformInfo
493 : #endif
494 : use, intrinsic :: iso_fortran_env, only: compiler_version, compiler_options
495 : use System_mod, only: SystemInfo_type ! LCOV_EXCL_LINE
496 : use Constants_mod, only: NLC
497 : implicit none
498 : integer(IK) :: i, j
499 : class(ParaMonte_type), intent(inout) :: self
500 359 : type(SystemInfo_type) :: SystemInfo !< An object of class [SystemInfo_type](@ref system_mod::systeminfo_type)
501 : !< containing information about the operating system and platform.
502 :
503 : character(*), parameter :: PROCEDURE_NAME = MODULE_NAME//"@addCompilerPlatformInfo()"
504 :
505 : ! report the interface type to ParaMonte
506 :
507 : call self%Decor%writeDecoratedText ( text="\nParaMonte library interface specifications\n" &
508 : , symbol="*" &
509 : , width=132 &
510 : , thicknessHorz=4 &
511 : , thicknessVert=1 &
512 : , marginTop=2 &
513 : , marginBot=1 &
514 : , outputUnit=self%LogFile%unit &
515 : , newLine="\n" &
516 359 : )
517 1795 : self%Decor%List = self%Decor%wrapText( self%SpecBase%InterfaceType%val , 132 )
518 718 : do i = 1, size(self%Decor%List)
519 718 : write(self%LogFile%unit,"(*(g0))") self%Decor%List(i)%record
520 : end do
521 :
522 : ! report the ParaMonte compiler version and options
523 :
524 : call self%Decor%writeDecoratedText ( text="\nParaMonte library compiler version\n" &
525 : , symbol="*" &
526 : , width=132 &
527 : , thicknessHorz=4 &
528 : , thicknessVert=1 &
529 : , marginTop=2 &
530 : , marginBot=1 &
531 : , outputUnit=self%LogFile%unit &
532 : , newLine="\n" &
533 359 : )
534 1077 : self%Decor%List = self%Decor%wrapText( compiler_version() , 132 )
535 718 : do i = 1,size(self%Decor%List)
536 718 : write(self%LogFile%unit,"(*(g0))") self%Decor%List(i)%record
537 : end do
538 :
539 : call self%Decor%writeDecoratedText (text="\nParaMonte library compiler options\n" &
540 : , symbol="*" &
541 : , width=132 &
542 : , thicknessHorz=4 &
543 : , thicknessVert=1 &
544 : , marginTop=2 &
545 : , marginBot=1 &
546 : , outputUnit=self%LogFile%unit &
547 : , newLine="\n" &
548 359 : )
549 6462 : self%Decor%List = self%Decor%wrapText( compiler_options() , 132 )
550 2872 : do i = 1,size(self%Decor%List)
551 2872 : write(self%LogFile%unit,"(*(g0))") self%Decor%List(i)%record
552 : end do
553 :
554 : call self%Decor%writeDecoratedText ( text="\nRuntime platform specifications\n" &
555 : , symbol="*" &
556 : , width=132 &
557 : , thicknessHorz=4 &
558 : , thicknessVert=1 &
559 : , marginTop=2 &
560 : , marginBot=1 &
561 : , outputUnit=self%LogFile%unit &
562 : , newLine="\n" &
563 359 : )
564 :
565 : ! Get system info by all images. why? Not anymore.
566 : ! On many parallel processors via singlChain this leads to
567 : ! the creation of thousands of files on the system, simultaneously.
568 : ! this is not needed by any process other than the leader images.
569 :
570 359 : SystemInfo = SystemInfo_type(OS = self%OS, path = self%SpecBase%SystemInfoFilePath%val)
571 359 : if (SystemInfo%Err%occurred) then
572 : ! LCOV_EXCL_START
573 : self%Err = SystemInfo%Err
574 : self%Err%msg = PROCEDURE_NAME//": Error occurred while collecting system info."//NLC//self%Err%msg
575 : call self%abort( Err = self%Err, prefix = self%brand, newline = NLC, outputUnit = self%LogFile%unit )
576 : return
577 : end if
578 : ! LCOV_EXCL_STOP
579 :
580 : ! write the system info to the output file
581 :
582 12206 : do j = 1, SystemInfo%nRecord
583 42003 : self%Decor%List = self%Decor%wrapText( SystemInfo%Records(j)%record , 132 )
584 25130 : do i = 1,size(self%Decor%List)
585 24771 : write(self%LogFile%unit,"(A)") self%Decor%List(i)%record
586 : end do
587 : end do
588 359 : call self%Decor%write(self%LogFile%unit)
589 :
590 12565 : end subroutine addCompilerPlatformInfo
591 :
592 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
593 :
594 : !> \brief
595 : !> This procedure is a method of the [ParaMonte_type](@ref paramonte_type) class.
596 : !> Write to the output report file, the relevant platform setup messages.
597 : !>
598 : !> @param[inout] self : An object of class [ParaMonte_type](@ref paramonte_type).
599 : !>
600 : !> \remark
601 : !> This routine has to be called by all leader images (processes).
602 359 : subroutine noteUserAboutEnvSetup(self)
603 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
604 : !DEC$ ATTRIBUTES DLLEXPORT :: noteUserAboutEnvSetup
605 : #endif
606 : implicit none
607 : class(ParaMonte_type), intent(inout) :: self
608 : call self%Decor%writeDecoratedText ( text = "\nSetting up the " // self%name // " simulation environment\n" &
609 : , marginTop = 1 &
610 : , marginBot = 1 &
611 : , newline = "\n" &
612 359 : , outputUnit = self%LogFile%unit )
613 359 : end subroutine noteUserAboutEnvSetup
614 :
615 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
616 :
617 : !> \brief
618 : !> If the relevant method name is missing in the namelist input file, then warn the user about this issue.
619 : !>
620 : !> @param[in] self : An object of class [ParaMonte_type](@ref paramonte_type).
621 : !> @param[inout] namelist : The name of the missing namelist.
622 48 : subroutine warnUserAboutMissingNamelist(self, namelist)
623 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
624 : !DEC$ ATTRIBUTES DLLEXPORT :: warnUserAboutMissingNamelist
625 : #endif
626 : use, intrinsic :: iso_fortran_env, only: output_unit
627 : use Constants_mod, only: NLC ! LCOV_EXCL_LINE
628 : use Constants_mod, only: IK
629 : use Err_mod, only: warn
630 : implicit none
631 : class(ParaMonte_type), intent(in) :: self
632 : character(*), intent(in) :: namelist
633 48 : character(:), allocatable :: msg
634 64 : if (self%Image%isFirst .or. self%Image%isLeader) then
635 : msg = "No namelist group of variables named "//namelist//" was detected in user's input file for "//self%name//" options."//NLC//&
636 16 : "All " // self%name // " options will be assigned appropriate default values."
637 16 : call warn( prefix = self%brand, outputUnit = self%LogFile%unit, newline = "\n", msg = msg )
638 16 : if (self%LogFile%unit == output_unit) then ! only the first image gets to print on the stdout
639 : if (self%Image%isFirst) call warn( prefix = self%brand, outputUnit = self%LogFile%unit, newline = NLC, msg = msg ) ! LCOV_EXCL_LINE
640 : ! LCOV_EXCL_START
641 : else
642 : call warn( prefix = self%brand, outputUnit = self%LogFile%unit, newline = "\n", msg = msg )
643 : end if
644 : ! LCOV_EXCL_STOP
645 : end if
646 48 : end subroutine warnUserAboutMissingNamelist
647 :
648 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
649 :
650 : !> \brief
651 : !> This procedure is a method of the [ParaMonte_type](@ref paramonte_type) class.
652 : !> Warn the user about whether the input file is missing, or is present, and other input file activities.
653 : !>
654 : !> @param[inout] self : An object of class [ParaMonte_type](@ref paramonte_type).
655 708 : subroutine warnUserAboutInputFilePresence(self)
656 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
657 : !DEC$ ATTRIBUTES DLLEXPORT :: warnUserAboutInputFilePresence
658 : #endif
659 : use Constants_mod, only: NLC ! LCOV_EXCL_LINE
660 : implicit none
661 : class(ParaMonte_type), intent(inout) :: self
662 708 : character(:), allocatable :: msg
663 : #if defined JULIA_ENABLED
664 : msg = "Interfacing Julia with "// self%name //"..."
665 : #elif defined MATLAB_ENABLED
666 : msg = "Interfacing MATLAB with "// self%name //"..."
667 : #elif defined MATTHEMATICA_ENABLED
668 : msg = "Interfacing Mathematica with "// self%name //"..."
669 : #elif defined PYTHON_ENABLED
670 : msg = "Interfacing Python with "// self%name //"..."
671 : #elif defined R_ENABLED
672 : msg = "Interfacing R with "// self%name //"..."
673 : #elif defined C_ENABLED || defined CPP_ENABLED || defined FORTRAN_ENABLED
674 708 : if (self%inputFileArgIsPresent) then
675 326 : if (self%InputFile%exists) then
676 : msg = "The user's input file for " // self%name // " options was detected."// NLC // &
677 : "All " // self%name // " specifications will be read from the input file."// NLC // &
678 14 : "Here is " // self%name // " input specifications file:"// NLC // self%inputFile%Path%modified
679 312 : elseif (self%InputFile%isInternal) then
680 : msg = "No external file corresponding to the user's input file for "//self%name//" options could be found."//NLC// &
681 312 : "The user-provided input file will be processed as an input string of "//self%name//" options."
682 : end if
683 : else
684 : msg = "No " // self%name // " input file is provided by the user."//NLC// &
685 : #if defined FORTRAN_ENABLED
686 : "Variable values from the procedure arguments will be used instead, where provided."//NLC//"Otherwise, "// &
687 : #else
688 : "Where needed, "// &
689 : #endif
690 382 : "the default options will be used."
691 : end if
692 : #endif
693 : call self%note ( prefix = self%brand &
694 : , outputUnit = self%LogFile%unit &
695 : , newline = NLC &
696 708 : , msg = msg )
697 708 : end subroutine warnUserAboutInputFilePresence
698 :
699 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
700 :
701 : !> \brief
702 : !> This procedure is a method of the [ParaMonte_type](@ref paramonte_type) class.
703 : !> Warn the user about whether the specifications setup from within the program are allowed or not.
704 : !>
705 : !> @param[inout] self : An object of class [RefinedChain_type](@ref paramcmcrefinedchain_mod::refinedchain_type).
706 1406 : subroutine setWarnAboutProcArgHasPriority(self)
707 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
708 : !DEC$ ATTRIBUTES DLLEXPORT :: setWarnAboutProcArgHasPriority
709 : #endif
710 : implicit none
711 : class(ParaMonte_type), intent(inout) :: self
712 : #if !defined CFI_ENABLED
713 1406 : character(:), allocatable :: msg
714 : #endif
715 1406 : self%procArgHasPriority = .not. self%SpecBase%InputFileHasPriority%val
716 1406 : self%procArgNeeded = self%procArgHasPriority .or. (.not.self%inputFileArgIsPresent)
717 :
718 : #if defined FORTRAN_ENABLED
719 1406 : if (self%procArgHasPriority) then
720 : msg = "Variable inputFileHasPriority = .false.\n&
721 : &All variable values will be overwritten by the corresponding procedure argument values,\n&
722 1400 : &only if provided as procedure arguments."
723 : else
724 : msg = "Variable inputFileHasPriority = .true.\n&
725 6 : &All variable values will be read from the user-provided input file"
726 : end if
727 : if (self%Image%isFirst) call self%note(prefix = self%brand, outputUnit = self%LogFile%unit, newline = "\n", msg = msg) ! LCOV_EXCL_LINE
728 : #endif
729 2114 : end subroutine setWarnAboutProcArgHasPriority
730 :
731 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
732 :
733 : !> \brief
734 : !> This procedure is a method of the [ParaMonte_type](@ref paramonte_type) class.
735 : !> Set up the output files of the simulation.
736 : !>
737 : !> @param[inout] self : An object of class [RefinedChain_type](@ref paramcmcrefinedchain_mod::refinedchain_type).
738 1047 : subroutine setupOutputFiles(self)
739 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
740 : !DEC$ ATTRIBUTES DLLEXPORT :: setupOutputFiles
741 : #endif
742 1406 : use Decoration_mod, only: getGenericFormat, INDENT
743 : use Constants_mod, only: NLC, FILE_EXT
744 : use String_mod, only: num2str
745 : use Path_mod, only: MAX_FILE_PATH_LEN, mkdir
746 :
747 : implicit none
748 :
749 : class(ParaMonte_type), intent(inout) :: self
750 1047 : character(:), allocatable :: msg, workingOn, currentWorkingDir
751 : character(*), parameter :: PROCEDURE_NAME = MODULE_NAME // "@setupOutputFiles()"
752 :
753 1047 : if (self%SpecBase%OutputFileName%original==self%SpecBase%OutputFileName%def) then
754 : msg = "No user-input filename prefix for " // self%name // " output files detected." // NLC // &
755 0 : "Generating appropriate filenames for " // self%name // " output files from the current date and time..."
756 : else
757 1047 : msg = "Variable outputFileName detected among the input variables to " // self%name // ":" //NLC// self%SpecBase%OutputFileName%original
758 : end if
759 :
760 1047 : call self%SpecBase%OutputFileName%query(OS=self%OS)
761 :
762 1047 : if (self%SpecBase%OutputFileName%Err%occurred) then
763 : ! LCOV_EXCL_START
764 : self%Err = self%SpecBase%OutputFileName%Err
765 : self%Err%msg = PROCEDURE_NAME // ": Error occurred while attempting to construct OutputFileName path type." //NLC// self%Err%msg
766 : call self%abort( Err = self%Err, prefix = self%brand, newline = NLC, outputUnit = self%LogFile%unit )
767 : return
768 : end if
769 : ! LCOV_EXCL_STOP
770 :
771 1041 : self%SpecBase%OutputFileName%namePrefix = self%SpecBase%OutputFileName%name // self%SpecBase%OutputFileName%ext
772 :
773 : ! get the current working directory
774 :
775 1041 : if (allocated(currentWorkingDir)) deallocate(currentWorkingDir)
776 1041 : allocate( character(MAX_FILE_PATH_LEN) :: currentWorkingDir )
777 : block
778 : #if defined INTEL_COMPILER_ENABLED
779 : use ifport ! only: getcwd
780 : #endif
781 : #if defined INTEL_COMPILER_ENABLED || GNU_COMPILER_ENABLED
782 1041 : self%Err%stat = getcwd(currentWorkingDir)
783 1041 : currentWorkingDir = trim(adjustl(currentWorkingDir))
784 : #else
785 : self%Err%stat = 0_IK
786 : currentWorkingDir = "."
787 : #endif
788 : end block
789 1041 : if (self%Err%stat/=0) then
790 : ! LCOV_EXCL_START
791 : self%Err%msg = PROCEDURE_NAME//": Error occurred while fetching the current working directory via getcwd()."//NLC
792 : call self%abort( Err = self%Err, prefix = self%brand, newline = NLC, outputUnit = self%LogFile%unit )
793 : return
794 : end if
795 : ! LCOV_EXCL_STOP
796 1041 : msg = msg //NLC//NLC// "Absolute path to the current working directory:"//NLC//currentWorkingDir
797 :
798 1041 : if (len_trim(adjustl(self%SpecBase%OutputFileName%dir))==0) then
799 0 : self%SpecBase%OutputFileName%dir = trim(adjustl(currentWorkingDir)) // self%SpecBase%OutputFileName%shellSlash
800 0 : msg = msg //NLC//NLC// "All output files will be written to the current working directory:"//NLC//self%SpecBase%OutputFileName%dir
801 : else
802 1041 : msg = msg //NLC//NLC// "Generating the requested directory for the "//self%name//" output files:"//NLC//self%SpecBase%OutputFileName%dir
803 : end if
804 :
805 : ! Generate the output files directory:
806 :
807 1041 : if (self%Image%isFirst) then
808 347 : self%Err = mkdir( dirPath = self%SpecBase%OutputFileName%dir, isUnixShell = self%OS%Shell%isUnix )
809 347 : if (self%Err%occurred) then
810 : ! LCOV_EXCL_START
811 : self%Err%msg = PROCEDURE_NAME//": Error occurred while making directory = '"//self%SpecBase%OutputFileName%dir//"'."//NLC//self%Err%msg
812 : call self%abort( Err = self%Err, prefix = self%brand, newline = NLC, outputUnit = self%LogFile%unit )
813 : return
814 : end if
815 : ! LCOV_EXCL_STOP
816 : end if
817 :
818 : ! in parallel mode, ensure the directory exists before moving on
819 :
820 1041 : call self%Image%sync()
821 :
822 1041 : if (len_trim(adjustl(self%SpecBase%OutputFileName%namePrefix))==0) then
823 : msg = msg //NLC//NLC// "No user-input filename prefix for " // self%name // " output files detected."//NLC//&
824 0 : "Generating appropriate filenames for " // self%name // " output files from the current date and time..."
825 0 : self%SpecBase%OutputFileName%namePrefix = self%SpecBase%OutputFileName%def
826 : end if
827 :
828 1041 : self%SpecBase%OutputFileName%pathPrefix = self%SpecBase%OutputFileName%dir // self%SpecBase%OutputFileName%namePrefix
829 :
830 : ! Variable msg will be used down this subroutine, so it should not be changed beyond this point
831 1041 : msg = msg //NLC//NLC// self%name // " output files will be prefixed with:"//NLC// self%SpecBase%OutputFileName%pathPrefix
832 : if (self%Image%isFirst) call self%note(prefix = self%brand, outputUnit = self%LogFile%unit, newline = NLC, msg = msg) ! LCOV_EXCL_LINE
833 :
834 : ! Generate the output filenames, search for pre-existing runs, and open the report file:
835 :
836 1041 : if (self%Image%isFirst) call self%note( prefix = self%brand, outputUnit = self%LogFile%unit, newline = NLC, msg = "Searching for previous runs of " // self%name // "..." )
837 :
838 : ! this block could be all executed by only the leader images
839 :
840 1041 : self%LogFile%Path%Ext = FILE_EXT%ascii
841 1041 : self%TimeFile%Path%Ext = FILE_EXT%ascii
842 1041 : self%ChainFile%Path%Ext = FILE_EXT%ascii
843 1041 : self%SampleFile%Path%Ext = FILE_EXT%ascii
844 1041 : self%RestartFile%Path%Ext = FILE_EXT%ascii
845 :
846 1041 : self%RestartFile%Form%value = "formatted"
847 1041 : if (self%SpecBase%RestartFileFormat%isBinary) then
848 975 : self%RestartFile%Form%value = "unformatted"
849 975 : self%RestartFile%Path%Ext = FILE_EXT%binary
850 : end if
851 :
852 1041 : self%ChainFile%Form%value = "formatted"
853 1041 : if (self%SpecBase%ChainFileFormat%isBinary) then
854 36 : self%ChainFile%Form%value = "unformatted"
855 36 : self%ChainFile%Path%Ext = FILE_EXT%binary
856 : end if
857 :
858 : block
859 : use Path_mod, only: Path_type
860 : integer(IK) :: imageID
861 : #if defined CAF_ENABLED || defined MPI_ENABLED
862 1041 : if (self%SpecBase%ParallelizationModel%isMultiChain) then
863 72 : imageID = self%Image%id
864 : else
865 : #endif
866 969 : imageID = 1_IK
867 : #if defined CAF_ENABLED || defined MPI_ENABLED
868 : end if
869 : #endif
870 1041 : self%SpecBase%OutputFileName%pathPrefix = self%SpecBase%OutputFileName%pathPrefix // "_process_" // num2str(imageID) // "_"
871 1041 : self%LogFile%Path = Path_type( inputPath = self%SpecBase%OutputFileName%pathPrefix // self%LogFile%suffix // self%LogFile%Path%Ext , OS = self%OS )
872 1041 : self%TimeFile%Path = Path_type( inputPath = self%SpecBase%OutputFileName%pathPrefix // self%TimeFile%suffix // self%TimeFile%Path%Ext , OS = self%OS )
873 1041 : self%ChainFile%Path = Path_type( inputPath = self%SpecBase%OutputFileName%pathPrefix // self%ChainFile%suffix // self%ChainFile%Path%Ext , OS = self%OS )
874 1041 : self%SampleFile%Path = Path_type( inputPath = self%SpecBase%OutputFileName%pathPrefix // self%SampleFile%suffix // self%SampleFile%Path%Ext , OS = self%OS )
875 1041 : self%RestartFile%Path = Path_type( inputPath = self%SpecBase%OutputFileName%pathPrefix // self%RestartFile%suffix // self%RestartFile%Path%Ext , OS = self%OS )
876 : end block
877 :
878 1041 : inquire( file = self%LogFile%Path%original, exist = self%LogFile%exists, iostat = self%LogFile%Err%stat )
879 1041 : self%Err = self%LogFile%getInqErr( self%LogFile%Err%stat )
880 1041 : if (self%Err%occurred) then
881 : ! LCOV_EXCL_START
882 : self%Err%msg = PROCEDURE_NAME // ": Error occurred while inquiring the existence of file='" // self%LogFile%Path%original // self%Err%msg
883 : call self%abort( Err = self%Err, prefix = self%brand, newline = NLC, outputUnit = self%LogFile%unit )
884 : return
885 : end if
886 : ! LCOV_EXCL_STOP
887 :
888 1041 : inquire( file = self%SampleFile%Path%original, exist = self%SampleFile%exists, iostat = self%SampleFile%Err%stat )
889 1041 : self%Err = self%SampleFile%getInqErr( self%SampleFile%Err%stat )
890 1041 : if (self%Err%occurred) then
891 : ! LCOV_EXCL_START
892 : self%Err%msg = PROCEDURE_NAME // ": Error occurred while inquiring the existence of file='" // self%SampleFile%Path%original // self%Err%msg
893 : call self%abort( Err = self%Err, prefix = self%brand, newline = NLC, outputUnit = self%LogFile%unit )
894 : return
895 : end if
896 : ! LCOV_EXCL_STOP
897 :
898 1041 : inquire( file = self%TimeFile%Path%original, exist = self%TimeFile%exists, iostat = self%TimeFile%Err%stat )
899 1041 : self%Err = self%TimeFile%getInqErr( self%TimeFile%Err%stat )
900 1041 : if (self%Err%occurred) then
901 : ! LCOV_EXCL_START
902 : self%Err%msg = PROCEDURE_NAME // ": Error occurred while inquiring the existence of file='" // self%TimeFile%Path%original // self%Err%msg
903 : call self%abort( Err = self%Err, prefix = self%brand, newline = NLC, outputUnit = self%LogFile%unit )
904 : return
905 : end if
906 : ! LCOV_EXCL_STOP
907 :
908 1041 : inquire( file = self%ChainFile%Path%original, exist = self%ChainFile%exists, iostat = self%ChainFile%Err%stat )
909 1041 : self%Err = self%ChainFile%getInqErr( self%ChainFile%Err%stat )
910 1041 : if (self%Err%occurred) then
911 : ! LCOV_EXCL_START
912 : self%Err%msg = PROCEDURE_NAME // ": Error occurred while inquiring the existence of file='" // self%ChainFile%Path%original // self%Err%msg
913 : call self%abort( Err = self%Err, prefix = self%brand, newline = NLC, outputUnit = self%LogFile%unit )
914 : return
915 : end if
916 : ! LCOV_EXCL_STOP
917 :
918 1041 : inquire( file = self%RestartFile%Path%original, exist = self%RestartFile%exists, iostat = self%RestartFile%Err%stat )
919 1041 : self%Err = self%RestartFile%getInqErr( self%RestartFile%Err%stat )
920 1041 : if (self%Err%occurred) then
921 : ! LCOV_EXCL_START
922 : self%Err%msg = PROCEDURE_NAME // ": Error occurred while inquiring the existence of file='" // self%RestartFile%Path%original // self%Err%msg
923 : call self%abort( Err = self%Err, prefix = self%brand, newline = NLC, outputUnit = self%LogFile%unit )
924 : return
925 : end if
926 : ! LCOV_EXCL_STOP
927 :
928 : self%isDryRun = (.not. self%SpecBase%OverwriteRequested%val) .and. & ! not fresh, if any file exists
929 1041 : (self%LogFile%exists .or. self%TimeFile%exists .or. self%RestartFile%exists .or. self%ChainFile%exists .or. self%SampleFile%exists)
930 1041 : self%isFreshRun = .not. self%isDryRun
931 :
932 1041 : if (self%isFreshRun) then
933 969 : if (self%Image%isFirst) call self%note( prefix = self%brand, outputUnit = self%LogFile%unit, newline = NLC, msg = "No pre-existing "//self%name//" run detected."//NLC//"Starting a fresh "//self%name//" run..." )
934 : else
935 72 : if (self%Image%isFirst) call self%note( prefix = self%brand, outputUnit = self%LogFile%unit, newline = NLC, msg = "Previous run of "//self%name//" detected."//NLC//"Searching for restart files..." )
936 72 : if (self%SampleFile%exists) then ! sampling is already complete
937 6 : self%Err%occurred = .true.
938 : self%Err%msg = PROCEDURE_NAME//": Error occurred. Output sample file detected: "//self%SampleFile%Path%original//&
939 : NLC//self%name//" cannot overwrite an already-completed simulation."//&
940 6 : NLC//"Please provide an alternative file name for the new simulation outputs."
941 66 : elseif (self%LogFile%exists .and. self%TimeFile%exists .and. self%RestartFile%exists .and. self%ChainFile%exists) then ! restart mode
942 66 : if (self%SpecBase%SampleSize%val==0_IK) then ! sampling is already complete
943 0 : self%Err%occurred = .true.
944 0 : self%Err%msg = PROCEDURE_NAME//": Error occurred. The input variable sampleSize = 0 indicates that the output files belong to a completed simulation."
945 : else
946 66 : self%Err%occurred = .false.
947 : end if
948 : else
949 0 : self%Err%occurred = .true.
950 0 : self%Err%msg = PROCEDURE_NAME//": Error occurred. For a successful simulation restart, all output files are necessary."//NLC//"List of missing simulation output files:"
951 0 : if (.not. self%LogFile%exists) self%Err%msg = self%Err%msg//NLC//self%LogFile%Path%original
952 0 : if (.not. self%TimeFile%exists) self%Err%msg = self%Err%msg//NLC//self%TimeFile%Path%original
953 0 : if (.not. self%ChainFile%exists) self%Err%msg = self%Err%msg//NLC//self%ChainFile%Path%original
954 0 : if (.not. self%RestartFile%exists) self%Err%msg = self%Err%msg//NLC//self%RestartFile%Path%original
955 : end if
956 72 : if (self%Err%occurred) then
957 6 : call self%abort( Err = self%Err, prefix = self%brand, newline = NLC, outputUnit = self%LogFile%unit )
958 6 : return
959 : end if
960 : end if
961 :
962 : ! open/append the output files:
963 :
964 1035 : if (self%Image%isLeader) then
965 393 : if (self%isFreshRun) then
966 359 : workingOn = "Generating the output "
967 359 : self%LogFile%status = "replace"
968 359 : self%TimeFile%status = "replace"
969 359 : self%ChainFile%status = "replace"
970 359 : self%SampleFile%status = "replace"
971 359 : self%RestartFile%status = "replace"
972 359 : self%LogFile%Position%value = "asis"
973 359 : self%TimeFile%Position%value = "asis"
974 359 : self%ChainFile%Position%value = "asis"
975 359 : self%SampleFile%Position%value = "asis"
976 359 : self%RestartFile%Position%value = "asis"
977 : else
978 34 : workingOn = "Appending to the existing "
979 34 : self%LogFile%status = "old"
980 34 : self%TimeFile%status = "old"
981 34 : self%ChainFile%status = "old"
982 34 : self%SampleFile%status = "replace"
983 34 : self%RestartFile%status = "old"
984 34 : self%LogFile%Position%value = "append"
985 34 : self%TimeFile%Position%value = "asis"
986 34 : self%ChainFile%Position%value = "asis"
987 34 : self%SampleFile%Position%value = "asis"
988 34 : self%RestartFile%Position%value = "asis"
989 : end if
990 : end if
991 :
992 : ! print the stdout message for generating / appending the output report file
993 :
994 1035 : blockLogFileListByFirstImage: if (self%Image%isFirst) then
995 : #if defined CAF_ENABLED || defined MPI_ENABLED
996 : ! LCOV_EXCL_START
997 : #endif
998 : ! print the stdout message for generating / appending the output report file(s)
999 :
1000 : call self%note ( prefix = self%brand &
1001 : , outputUnit = self%LogFile%unit &
1002 : , newline = NLC &
1003 : , marginBot = 0_IK &
1004 : , msg = workingOn // self%LogFile%suffix // " file:" )
1005 :
1006 : ! print the the output report file name of the images
1007 :
1008 : call self%note ( prefix = self%brand &
1009 : , outputUnit = self%LogFile%unit &
1010 : , newline = NLC &
1011 : , marginTop = 0_IK &
1012 : , marginBot = 0_IK &
1013 : , msg = self%LogFile%Path%original )
1014 :
1015 : #if defined CAF_ENABLED || defined MPI_ENABLED
1016 : if (self%SpecBase%ParallelizationModel%isMultiChain) then
1017 : block
1018 : use String_mod, only: replaceStr !, num2str
1019 : integer(IK) :: imageID
1020 : do imageID = 2, self%Image%count
1021 : call self%note ( prefix = self%brand &
1022 : , outputUnit = self%LogFile%unit &
1023 : , newline = NLC &
1024 : , marginTop = 0_IK &
1025 : , marginBot = 0_IK &
1026 : , msg = replaceStr( string = self%LogFile%Path%original, search = "process_1", substitute = "process_"//num2str(imageID) ) )
1027 : end do
1028 : end block
1029 : end if
1030 : self%Err%msg = "Running the simulation in parallel on " // num2str(self%Image%count) // " processes." // NLC
1031 : #else
1032 : self%Err%msg = "Running the simulation in serial on " // num2str(self%Image%count) // " process." // NLC
1033 : #endif
1034 :
1035 : call self%note ( prefix = self%brand &
1036 : , outputUnit = self%LogFile%unit &
1037 : , newline = NLC &
1038 : , marginTop = 3_IK &
1039 : , marginBot = 3_IK &
1040 : , msg = self%Err%msg // "Please see the output " // self%LogFile%suffix // " and " // self%TimeFile%suffix // " files for further realtime simulation details." &
1041 : )
1042 :
1043 : end if blockLogFileListByFirstImage
1044 : #if defined CAF_ENABLED || defined MPI_ENABLED
1045 : ! LCOV_EXCL_STOP
1046 : #endif
1047 :
1048 : ! ensure all images sync here to avoid wrong inquire result for the existence of the files
1049 :
1050 1035 : call self%Image%sync()
1051 :
1052 : ! open the output files
1053 : ! Intel ifort SHARED attribute is essential for file unlocking
1054 :
1055 1035 : blockLeaderFileSetup: if (self%Image%isLeader) then
1056 :
1057 393 : self%LogFile%unit = 1001 + self%Image%id ! for some unknown reason, if newunit is used, GFortran opens the file as an internal file
1058 : open( unit = self%LogFile%unit &
1059 : , file = self%LogFile%Path%original &
1060 : , status = self%LogFile%status &
1061 : , iostat = self%LogFile%Err%stat &
1062 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
1063 : , SHARED &
1064 : #endif
1065 393 : , position = self%LogFile%Position%value)
1066 393 : self%Err = self%LogFile%getOpenErr(self%LogFile%Err%stat)
1067 393 : if (self%Err%occurred) then
1068 : ! LCOV_EXCL_START
1069 : self%Err%msg = PROCEDURE_NAME // ": Error occurred while opening the " // self%name // " " // self%LogFile%suffix // " file='" // self%LogFile%Path%original // "'. "
1070 : if (scan(" ",trim(adjustl(self%LogFile%Path%original)))/=0) then
1071 : self%Err%msg = self%Err%msg // "It appears that absolute path used for the output files contains whitespace characters. " &
1072 : // "This could be one potential cause of the simulation failure. " &
1073 : // "The whitespace characters are always problematic in paths. " &
1074 : // "Ensure the path used for the output files does not contain whitespace characters. "
1075 : end if
1076 : call self%abort( Err = self%Err, prefix = self%brand, newline = NLC, outputUnit = self%LogFile%unit )
1077 : return
1078 : end if
1079 : ! LCOV_EXCL_STOP
1080 :
1081 : ! rewrite the same old stuff to all report files
1082 :
1083 393 : if (self%isFreshRun) then
1084 359 : call self%addSplashScreen()
1085 359 : if (self%SpecBase%SilentModeRequested%isFalse) call self%addCompilerPlatformInfo() ! this takes about 0.75 seconds to execute on Stampede Login nodes.
1086 359 : call self%noteUserAboutEnvSetup()
1087 359 : call self%warnUserAboutInputFilePresence()
1088 359 : call self%setWarnAboutProcArgHasPriority()
1089 359 : call self%note( prefix = self%brand, outputUnit = self%LogFile%unit, newline = NLC, msg = msg )
1090 : end if
1091 :
1092 : ! open/append the output files
1093 :
1094 393 : if (self%isFreshRun) call self%note( prefix = self%brand, outputUnit = self%LogFile%unit, newline = NLC, msg = workingOn//self%TimeFile%suffix//" file:"//NLC//self%TimeFile%Path%original )
1095 :
1096 393 : self%TimeFile%unit = 1000001 ! for some unknown reason, if newunit is used, GFortran opens the file as an internal file
1097 : open( unit = self%TimeFile%unit &
1098 : , file = self%TimeFile%Path%original &
1099 : , status = self%TimeFile%status &
1100 : , iostat = self%TimeFile%Err%stat &
1101 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
1102 : , SHARED &
1103 : #endif
1104 393 : , position = self%TimeFile%Position%value )
1105 393 : self%Err = self%TimeFile%getOpenErr(self%TimeFile%Err%stat)
1106 393 : if (self%Err%occurred) then
1107 : ! LCOV_EXCL_START
1108 : self%Err%msg = PROCEDURE_NAME // ": Error occurred while opening the " // self%name // " " // self%TimeFile%suffix // " file='" // self%TimeFile%Path%original // "'. "
1109 : call self%abort( Err = self%Err, prefix = self%brand, newline = NLC, outputUnit = self%LogFile%unit )
1110 : return
1111 : end if
1112 : ! LCOV_EXCL_STOP
1113 :
1114 393 : if (self%isFreshRun) call self%note( prefix = self%brand, outputUnit = self%LogFile%unit, newline = NLC, msg = workingOn//self%ChainFile%suffix//"file:"//NLC//self%ChainFile%Path%original )
1115 :
1116 393 : self%ChainFile%unit = 2000001 ! for some unknown reason, if newunit is used, GFortran opens the file as an internal file
1117 : open( unit = self%ChainFile%unit &
1118 : , file = self%ChainFile%Path%original &
1119 : , form = self%ChainFile%Form%value &
1120 : , status = self%ChainFile%status &
1121 : , iostat = self%ChainFile%Err%stat &
1122 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
1123 : , SHARED &
1124 : #endif
1125 393 : , position = self%ChainFile%Position%value )
1126 393 : self%Err = self%ChainFile%getOpenErr(self%ChainFile%Err%stat)
1127 393 : if (self%Err%occurred) then
1128 : ! LCOV_EXCL_START
1129 : self%Err%msg = PROCEDURE_NAME // ": Error occurred while opening the " // self%name // " " // self%ChainFile%suffix // " file='" // self%ChainFile%Path%original // "'. "
1130 : call self%abort( Err = self%Err, prefix = self%brand, newline = NLC, outputUnit = self%LogFile%unit )
1131 : return
1132 : end if
1133 : ! LCOV_EXCL_STOP
1134 :
1135 393 : self%RestartFile%unit = 3000001 ! for some unknown reason, if newunit is used, GFortran opens the file as an internal file
1136 : open( unit = self%RestartFile%unit &
1137 : , file = self%RestartFile%Path%original &
1138 : , form = self%RestartFile%Form%value &
1139 : , status = self%RestartFile%status &
1140 : , iostat = self%RestartFile%Err%stat &
1141 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
1142 : , SHARED &
1143 : #endif
1144 393 : , position = self%RestartFile%Position%value)
1145 393 : self%Err = self%RestartFile%getOpenErr(self%RestartFile%Err%stat)
1146 393 : if (self%Err%occurred) then
1147 : ! LCOV_EXCL_START
1148 : self%Err%msg = PROCEDURE_NAME // ": Error occurred while opening the " // self%name // " " // self%RestartFile%suffix // " file='" // self%RestartFile%Path%original // "'. "
1149 : call self%abort( Err = self%Err, prefix = self%brand, newline = NLC, outputUnit = self%LogFile%unit )
1150 : return
1151 : end if
1152 : ! LCOV_EXCL_STOP
1153 :
1154 393 : if (self%isFreshRun) then
1155 : call self%Decor%writeDecoratedText ( text = NLC // self%name // " simulation specifications" // NLC &
1156 : , marginTop = 1 &
1157 : , marginBot = 1 &
1158 : , newline = NLC &
1159 359 : , outputUnit = self%LogFile%unit )
1160 : end if
1161 :
1162 : end if blockLeaderFileSetup
1163 :
1164 : ! These must be defined for all images, because they may be passed as arguments to the kernel subroutines.
1165 :
1166 1035 : self%LogFile%maxColWidth%val = max(self%SpecBase%OutputRealPrecision%val, self%SpecBase%OutputColumnWidth%val, self%SpecBase%VariableNameList%MaxLen%val) + 9_IK
1167 1035 : self%LogFile%maxColWidth%str = num2str(self%LogFile%maxColWidth%val)
1168 : self%LogFile%format = getGenericFormat( width = self%LogFile%maxColWidth%val &
1169 : , precision = self%SpecBase%OutputRealPrecision%val &
1170 1035 : , prefix = INDENT ) ! this is the generic indented format required mostly in postprocessing report
1171 1035 : self%TimeFile%format = "(*(g" // self%SpecBase%OutputColumnWidth%str // "." // self%SpecBase%OutputRealPrecision%str // ",:,'" // self%SpecBase%OutputDelimiter%val // "'))"
1172 1035 : self%ChainFile%format = self%TimeFile%format
1173 1035 : self%SampleFile%format = self%ChainFile%format
1174 1035 : self%RestartFile%format = "(*(g0,:,'"//NLC//"'))"
1175 :
1176 1047 : end subroutine setupOutputFiles
1177 :
1178 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1179 :
1180 : !> \brief
1181 : !> This procedure is a method of the [ParaMonte_type](@ref paramonte_type) class.
1182 : !> Output the relevant description.
1183 : !>
1184 : !> @param[inout] self : An object of class [ParaMonte_type](@ref paramonte_type).
1185 : !> @param[inout] msg : The message to be output.
1186 12985 : subroutine reportDesc(self, msg) !, marginTop, marginBot)
1187 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
1188 : !DEC$ ATTRIBUTES DLLEXPORT :: reportDesc
1189 : #endif
1190 1047 : use Constants_mod, only: IK, NLC
1191 : implicit none
1192 : class(ParaMonte_type), intent(inout) :: self
1193 : character(*), intent(in) :: msg
1194 : !integer(IK) , intent(in) :: marginTop, marginBot
1195 : !integer(IK) :: marginTopDef, marginBotDef
1196 : call self%note ( prefix = self%brand &
1197 : , outputUnit = self%LogFile%unit &
1198 : , newline = NLC &
1199 : , marginTop = 1_IK &
1200 : , marginBot = 1_IK &
1201 12985 : , msg = msg )
1202 25970 : end subroutine reportDesc
1203 :
1204 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1205 :
1206 : end module ParaMonte_mod ! LCOV_EXCL_LINE
|