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 `outputFileName` 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_OutputFileName_mod
49 :
50 : use Path_mod, only: Path_type
51 : implicit none
52 :
53 : character(*), parameter :: MODULE_NAME = "@SpecBase_OutputFileName_mod"
54 :
55 : character(:), allocatable :: outputFileName ! namelist input
56 :
57 : type, extends(Path_type) :: OutputFileName_type
58 : character(:), allocatable :: def
59 : character(:), allocatable :: namePrefix
60 : character(:), allocatable :: pathPrefix
61 : character(:), allocatable :: null
62 : character(:), allocatable :: desc
63 : contains
64 : procedure, pass :: set => setOutputFileName, nullifyNameListVar
65 : end type OutputFileName_type
66 :
67 : interface OutputFileName_type
68 : module procedure :: constructOutputFileName
69 : end interface OutputFileName_type
70 :
71 : private :: constructOutputFileName, setOutputFileName, nullifyNameListVar
72 :
73 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
74 :
75 : contains
76 :
77 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
78 :
79 1047 : function constructOutputFileName(methodName) result(OutputFileNameObj)
80 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
81 : !DEC$ ATTRIBUTES DLLEXPORT :: constructOutputFileName
82 : #endif
83 :
84 : use Path_mod, only: MAX_FILE_PATH_LEN
85 : use Constants_mod, only: NULL_SK
86 : use Decoration_mod, only: TAB
87 :
88 : implicit none
89 :
90 : character(*), intent(in) :: methodName
91 : type(OutputFileName_type) :: OutputFileNameObj
92 : character(8) :: date
93 : character(10) :: time
94 :
95 1047 : call date_and_time(date,time)
96 1047 : OutputFileNameObj%def = methodName // "_run_" // date // "_" // time(1:6) // "_" // time(8:10)
97 :
98 1047 : OutputFileNameObj%null = repeat(NULL_SK, MAX_FILE_PATH_LEN)
99 : OutputFileNameObj%desc = &
100 : "outputFileName contains the path and the base of the filename for " // methodName // " output files. &
101 : &If not provided by the user, the default outputFileName is constructed from the current date and time:\n\n" &
102 : // TAB // methodName // "_run_yyyymmdd_hhmmss_mmm\n\n&
103 : &where yyyy, mm, dd, hh, mm, ss, mmm stand respectively for the current year, month, day, hour, minute, second, &
104 : &and millisecond. In such a case, the default directory for the output files will be the current working directory of " &
105 : // methodName // ". If outputFileName is provided, but ends with a separator character '/' or '\' (as in Linux or Windows OS), &
106 : &then its value will be used as the directory to which " // methodName // " output files will be written. In this case, &
107 : &the output file naming convention described above will be used. Also, the given directory will be automatically created &
108 1047 : &if it does not exist already."
109 :
110 1047 : end function constructOutputFileName
111 :
112 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
113 :
114 1047 : subroutine nullifyNameListVar(OutputFileNameObj)
115 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
116 : !DEC$ ATTRIBUTES DLLEXPORT :: nullifyNameListVar
117 : #endif
118 1047 : use Path_mod, only: Path_type, MAX_FILE_PATH_LEN
119 : implicit none
120 : class(OutputFileName_type), intent(in) :: OutputFileNameObj
121 1047 : outputFileName = OutputFileNameObj%null
122 1047 : end subroutine nullifyNameListVar
123 :
124 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
125 :
126 2088 : subroutine setOutputFileName(OutputFileNameObj,outputFileName)
127 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
128 : !DEC$ ATTRIBUTES DLLEXPORT :: setOutputFileName
129 : #endif
130 : implicit none
131 : class(OutputFileName_type), intent(inout) :: OutputFileNameObj
132 : character(*) :: outputFileName
133 2088 : OutputFileNameObj%original = trim(adjustl(outputFileName))
134 2088 : if ( OutputFileNameObj%original==trim(adjustl(OutputFileNameObj%null)) ) then
135 1035 : OutputFileNameObj%original = OutputFileNameObj%def
136 : end if
137 :
138 : ! set the outputFileName the same on all images. This becomes relevant in two scenarios:
139 : ! 1. when outputFileName is missing as input.
140 : ! 2. when outputFileName is present, but is not the same on all images (for example when called from Python)
141 :
142 : #if defined CAF_ENABLED
143 3 : block
144 : character(63), save :: co_defaultOutputFileName[*]
145 2088 : if (this_image()==1) then
146 696 : co_defaultOutputFileName = OutputFileNameObj%def
147 696 : sync images(*)
148 : else
149 1392 : sync images(1)
150 1392 : OutputFileNameObj%def = trim(adjustl(co_defaultOutputFileName[1]))
151 : end if
152 : end block
153 : #elif defined MPI_ENABLED
154 : block
155 : use mpi
156 : integer :: ierrMPI
157 : character(63) :: co_defaultOutputFileName
158 : co_defaultOutputFileName = OutputFileNameObj%def
159 : ! bcast co_defaultOutputFileName from image one to all others
160 : call mpi_bcast ( co_defaultOutputFileName & ! buffer
161 : , 63 & ! count
162 : , mpi_character & ! datatype
163 : , 0 & ! root
164 : , mpi_comm_world & ! comm
165 : , ierrMPI & ! ierr
166 : )
167 : OutputFileNameObj%def = trim(adjustl(co_defaultOutputFileName))
168 : end block
169 : #endif
170 :
171 1047 : end subroutine setOutputFileName
172 :
173 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
174 :
175 : end module SpecBase_OutputFileName_mod ! LCOV_EXCL_LINE
|