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 `parallelizationModel` 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_ParallelizationModel_mod
49 :
50 : use Constants_mod, only: IK
51 : implicit none
52 :
53 : character(*), parameter :: MODULE_NAME = "@SpecBase_ParallelizationModel_mod"
54 :
55 : integer(IK), parameter :: MAX_LEN_PARALLELIZATION_MODEL = 63
56 :
57 : character(MAX_LEN_PARALLELIZATION_MODEL) :: parallelizationModel
58 :
59 : type :: ParallelizationModel_type
60 : logical :: isSinglChain
61 : logical :: isMultiChain
62 : logical :: isForkJoin
63 : character(10) :: multiChain
64 : character(11) :: singlChain
65 : character(:), allocatable :: def
66 : character(:), allocatable :: val
67 : character(:), allocatable :: null
68 : character(:), allocatable :: desc
69 : contains
70 : procedure, pass :: set => setParallelizationModel, checkForSanity, nullifyNameListVar
71 : end type ParallelizationModel_type
72 :
73 : interface ParallelizationModel_type
74 : module procedure :: constructParallelizationModel
75 : end interface ParallelizationModel_type
76 :
77 : private :: constructParallelizationModel, setParallelizationModel, checkForSanity, nullifyNameListVar
78 :
79 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
80 :
81 : contains
82 :
83 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
84 :
85 349 : function constructParallelizationModel(methodName) result(ParallelizationModelObj)
86 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
87 : !DEC$ ATTRIBUTES DLLEXPORT :: constructParallelizationModel
88 : #endif
89 : use, intrinsic :: iso_fortran_env, only: output_unit
90 : use Constants_mod, only: NULL_SK, IK, PMSM
91 : use Decoration_mod, only: TAB
92 : use String_mod, only: num2str
93 : implicit none
94 : character(*), intent(in) :: methodName
95 : type(ParallelizationModel_type) :: ParallelizationModelObj
96 :
97 349 : ParallelizationModelObj%isSinglChain = .false.
98 349 : ParallelizationModelObj%isMultiChain = .false.
99 349 : ParallelizationModelObj%singlChain = "singleChain"
100 349 : ParallelizationModelObj%multiChain = "multiChain"
101 349 : ParallelizationModelObj%def = ParallelizationModelObj%singlChain
102 349 : ParallelizationModelObj%null = repeat(NULL_SK, MAX_LEN_PARALLELIZATION_MODEL)
103 :
104 : ParallelizationModelObj%desc = &
105 : "parallelizationModel is a string variable that represents the parallelization method to be used in "// methodName //". &
106 349 : &The string value must be enclosed by either single or double quotation marks when provided as input. "
107 349 : if (methodName==PMSM%ParaDRAM .or. methodName==PMSM%ParaDISE) then
108 : ParallelizationModelObj%desc = ParallelizationModelObj%desc // &
109 : "Two options are currently supported:\n\n&
110 : & parallelizationModel = '" // ParallelizationModelObj%multiChain // "'\n\n&
111 : & This method uses the Prefect Parallelism scheme in which multiple MCMC chains are generated &
112 : &independently of each other. In this case, multiple output MCMC chain files will also be generated.\n\n&
113 : & parallelizationModel = '" // ParallelizationModelObj%singlChain // "'\n\n&
114 : & This method uses the fork-style parallelization scheme. &
115 : &A single MCMC chain file will be generated in this case. At each MCMC step multiple proposal steps &
116 : &will be checked in parallel until one proposal is accepted.\n\n&
117 : &Note that in serial mode, there is no parallelism. Therefore, this option does not affect non-parallel simulations &
118 : &and its value is ignored. The serial mode is equivalent to either of the parallelism methods with only one simulation &
119 : &image (processor, core, or thread). &
120 : &The default value is parallelizationModel = '" // ParallelizationModelObj%def // "'. &
121 349 : &Note that the input values are case-insensitive and white-space characters are ignored."
122 : ! LCOV_EXCL_START
123 : else
124 : block
125 : use Err_mod, only: Err_type, abort
126 : type(Err_type) :: Err
127 : Err%occurred = .true.
128 : Err%msg = MODULE_NAME//": Catastrophic internal error occurred. The simulation method name is not recognized."
129 : call abort(Err)
130 : error stop
131 : end block
132 : ! LCOV_EXCL_STOP
133 : end if
134 349 : end function constructParallelizationModel
135 :
136 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
137 :
138 349 : subroutine nullifyNameListVar(ParallelizationModelObj)
139 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
140 : !DEC$ ATTRIBUTES DLLEXPORT :: nullifyNameListVar
141 : #endif
142 : implicit none
143 : class(ParallelizationModel_type), intent(in) :: ParallelizationModelObj
144 349 : parallelizationModel = ParallelizationModelObj%null
145 349 : end subroutine nullifyNameListVar
146 :
147 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
148 :
149 381 : subroutine setParallelizationModel(ParallelizationModelObj,parallelizationModel)
150 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
151 : !DEC$ ATTRIBUTES DLLEXPORT :: setParallelizationModel
152 : #endif
153 349 : use String_mod, only: getLowerCase, replaceStr
154 : implicit none
155 : class(ParallelizationModel_type), intent(inout) :: ParallelizationModelObj
156 : character(*), intent(in) :: parallelizationModel
157 381 : character(:), allocatable :: parallelizationModelLowerCase
158 381 : ParallelizationModelObj%val = trim(adjustl(replaceStr(parallelizationModel," ", "")))
159 381 : if (ParallelizationModelObj%val==trim(adjustl(ParallelizationModelObj%null))) ParallelizationModelObj%val = trim(adjustl(ParallelizationModelObj%def))
160 381 : parallelizationModelLowerCase = getLowerCase(ParallelizationModelObj%val)
161 381 : ParallelizationModelObj%isSinglChain = parallelizationModelLowerCase == getLowerCase(ParallelizationModelObj%singlChain)
162 381 : ParallelizationModelObj%isMultiChain = parallelizationModelLowerCase == getLowerCase(ParallelizationModelObj%multiChain)
163 381 : end subroutine setParallelizationModel
164 :
165 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
166 :
167 345 : subroutine checkForSanity(ParallelizationModel,Err,methodName)
168 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
169 : !DEC$ ATTRIBUTES DLLEXPORT :: checkForSanity
170 : #endif
171 381 : use Err_mod, only: Err_type
172 : use String_mod, only: num2str
173 : implicit none
174 : class(ParallelizationModel_type), intent(in) :: ParallelizationModel
175 : character(*), intent(in) :: methodName
176 : type(Err_type), intent(inout) :: Err
177 : character(*), parameter :: PROCEDURE_NAME = "@checkForSanity()"
178 345 : if ( .not.(ParallelizationModel%isSinglChain .or. ParallelizationModel%isMultiChain) ) then
179 : ! LCOV_EXCL_START
180 : Err%occurred = .true.
181 : Err%msg = Err%msg // &
182 : MODULE_NAME // PROCEDURE_NAME // ": Error occurred. &
183 : &The input requested parallelization method (" // ParallelizationModel%val // &
184 : ") represented by variable parallelizationModel cannot be anything other than &
185 : &'singleChain' or 'multiChain'. If you don't know an appropriate value &
186 : &for ParallelizationModel, drop it from the input list. " // methodName // &
187 : " will automatically assign an appropriate value to it.\n\n"
188 : end if
189 : ! LCOV_EXCL_STOP
190 690 : end subroutine checkForSanity
191 :
192 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
193 :
194 : end module SpecBase_ParallelizationModel_mod ! LCOV_EXCL_LINE
|