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 `scaleFactor` attribute of samplers of class [ParaMCMC_type](@ref paramcmc_mod::paramcmc_type).
45 : !> For more information, see the description of this attribute in the body of the module.
46 : !> \author Amir Shahmoradi
47 :
48 : module SpecMCMC_ScaleFactor_mod
49 :
50 : use Constants_mod, only: RK, IK
51 : implicit none
52 :
53 : character(*), parameter :: MODULE_NAME = "@SpecMCMC_ScaleFactor_mod"
54 : integer(IK), parameter :: MAX_LEN_STRING_SCALE_FACTOR = 127_IK
55 :
56 : character(:), allocatable :: scaleFactor
57 :
58 : type :: ScaleFactor_type
59 : real(RK) :: val, defVal
60 : character(:), allocatable :: str, defStr, null, desc
61 : contains
62 : procedure, pass :: set => setScaleFactor, checkForSanity, nullifyNameListVar
63 : end type ScaleFactor_type
64 :
65 : interface ScaleFactor_type
66 : module procedure :: constructScaleFactor
67 : end interface ScaleFactor_type
68 :
69 : private :: constructScaleFactor, setScaleFactor, checkForSanity, nullifyNameListVar
70 :
71 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
72 :
73 : contains
74 :
75 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
76 :
77 349 : function constructScaleFactor(nd,methodName) result(ScaleFactorObj)
78 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
79 : !DEC$ ATTRIBUTES DLLEXPORT :: constructScaleFactor
80 : #endif
81 : use Constants_mod, only: RK, IK, NULL_SK
82 : use String_mod, only: num2str
83 : use Decoration_mod, only: TAB
84 : implicit none
85 : integer(IK), intent(in) :: nd
86 : character(*), intent(in) :: methodName
87 : type(ScaleFactor_type) :: ScaleFactorObj
88 :
89 349 : ScaleFactorObj%defStr = "gelman"
90 349 : ScaleFactorObj%defVal = 2.38_RK/sqrt(real(nd,kind=RK)) ! Gelman, Roberts, Gilks (1996): Efficient Metropolis Jumping Rules
91 349 : ScaleFactorObj%null = repeat(NULL_SK, MAX_LEN_STRING_SCALE_FACTOR)
92 : ScaleFactorObj%desc = &
93 : "scaleFactor is a real-valued positive number (which must be given as string), by the square of which the &
94 : &covariance matrix of the proposal distribution of the MCMC sampler is scaled. In other words, &
95 : &the proposal distribution will be scaled in every direction by the value of scaleFactor. &
96 : &It can also be given in units of the string keyword 'gelman' (which is case-INsensitive) after the paper:\n\n" &
97 : // TAB // "Gelman, Roberts, and Gilks (1996): 'Efficient Metropolis Jumping Rules'.\n\n&
98 : &The paper finds that the optimal scaling factor for a Multivariate Gaussian proposal distribution for the &
99 : &Metropolis-Hastings Markov Chain Monte Carlo sampling of a target Multivariate Normal Distribution &
100 : &of dimension ndim is given by:\n\n&
101 : & scaleFactor = 2.38/sqrt(ndim) , in the limit of ndim -> Infinity.\n\n&
102 : &Multiples of the gelman scale factors are also acceptable as input and can be specified like the following examples:\n\n&
103 : & scaleFactor = '1'\n\n&
104 : & multiplies the ndim-dimensional proposal covariance matrix by 1, essentially no change occurs to &
105 : &the covariance matrix.\n\n" // &
106 : ' scaleFactor = "1"\n\n' // &
107 : " same as the previous example. The double-quotation marks act the same way as single-quotation marks.\n\n&
108 : & scaleFactor = '2.5'\n\n&
109 : & multiplies the ndim-dimensional proposal covariance matrix by 2.5.\n\n&
110 : & scaleFactor = '2.5*Gelman'\n\n&
111 : & multiplies the ndim-dimensional proposal covariance matrix by 2.5 * 2.38/sqrt(ndim).\n\n" // &
112 : ' scaleFactor = "2.5 * gelman"\n\n' // &
113 : " same as the previous example, but with double-quotation marks. space characters are ignored.\n\n" // &
114 : ' scaleFactor = "2.5 * gelman*gelman*2"\n\n' // &
115 : " equivalent to gelmanFactor-squared multiplied by 5.\n\n&
116 : &Note, however, that the result of Gelman et al. paper applies only to multivariate normal proposal distributions, in &
117 : &the limit of infinite dimensions. Therefore, care must be taken when using Gelman's scaling factor with non-Gaussian &
118 : &proposals and target objective functions. Note that only the product symbol (*) can be parsed &
119 : &in the string value of scaleFactor. The presence of other mathematical symbols or multiple appearances of the product &
120 : &symbol will lead to a simulation crash. Also, note that the prescription of an acceptance range specified by the input &
121 : &variable 'targetAcceptanceRate' will lead to dynamic modification of the initial input value of scaleFactor throughout sampling &
122 : &for adaptiveUpdateCount times. &
123 349 : &The default scaleFactor string-value is 'gelman' (for all proposals), which is subsequently converted to 2.38/sqrt(ndim)."
124 349 : end function constructScaleFactor
125 :
126 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
127 :
128 349 : subroutine nullifyNameListVar(ScaleFactorObj)
129 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
130 : !DEC$ ATTRIBUTES DLLEXPORT :: nullifyNameListVar
131 : #endif
132 : implicit none
133 : class(ScaleFactor_type), intent(in) :: ScaleFactorObj
134 349 : scaleFactor = ScaleFactorObj%null
135 349 : end subroutine nullifyNameListVar
136 :
137 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
138 :
139 371 : subroutine setScaleFactor(ScaleFactorObj,scaleFactor)
140 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
141 : !DEC$ ATTRIBUTES DLLEXPORT :: setScaleFactor
142 : #endif
143 349 : use Constants_mod, only: RK
144 : implicit none
145 : class(ScaleFactor_type), intent(inout) :: ScaleFactorObj
146 : character(*), intent(in) :: scaleFactor
147 371 : ScaleFactorObj%str = trim(adjustl(scaleFactor))
148 371 : if (ScaleFactorObj%str==ScaleFactorObj%null) then
149 335 : ScaleFactorObj%str = ScaleFactorObj%defStr
150 : end if
151 742 : end subroutine setScaleFactor
152 :
153 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
154 :
155 : ! ATTN: This subroutine also assigns the value of ScaleFactor. It MUST be executed by all images.
156 345 : subroutine checkForSanity(ScaleFactorObj,Err,methodName)
157 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
158 : !DEC$ ATTRIBUTES DLLEXPORT :: checkForSanity
159 : #endif
160 371 : use Constants_mod, only: IK, RK
161 : use String_mod, only: num2str, String_type
162 : use Err_mod, only: Err_type
163 : implicit none
164 : class(ScaleFactor_type), intent(inout) :: ScaleFactorObj
165 : character(*), intent(in) :: methodName
166 : type(Err_type), intent(inout) :: Err
167 : character(*), parameter :: PROCEDURE_NAME = "@checkForSanity()"
168 345 : type(String_type) :: String
169 : integer(IK) :: i
170 345 : real(RK) :: temp
171 :
172 : ! First convert the scaleFactor string to real value:
173 :
174 345 : String%value = String%replaceStr(ScaleFactorObj%str," ","") ! remove the white spaces
175 345 : if (len_trim(adjustl(String%value))==0) then
176 4 : Err%occurred = .true.
177 : Err%msg = Err%msg // &
178 : MODULE_NAME // PROCEDURE_NAME // ": Error occurred. &
179 : &The input string value (" // ScaleFactorObj%str // ") for the variable scaleFactor &
180 : &is empty. Make sure the input string follows the syntax rules of " &
181 : // methodName // " for this variable. Otherwise drop it from the input list. " &
182 4 : // methodName // " will automatically assign an appropriate value to it.\n\n"
183 4 : return
184 : end if
185 :
186 : ! Now split the string by "*" to real coefficient and character (gelman) parts for further evaluations
187 :
188 1416 : String%Parts = String%split(string = String%value, delim = "*", nPart = String%nPart)
189 341 : ScaleFactorObj%val = 1._RK
190 700 : do i = 1, String%nPart
191 1065 : if ( String%getLowerCase( String%Parts(i)%record ) == "gelman" ) then
192 335 : ScaleFactorObj%val = ScaleFactorObj%val * ScaleFactorObj%defVal
193 : else
194 30 : temp = String%str2real64( str=String%Parts(i)%record, iostat=Err%stat )
195 395 : if ( Err%stat/=0 ) then
196 6 : Err%occurred = .true.
197 : Err%msg = Err%msg // & ! LCOV_EXCL_LINE
198 : MODULE_NAME // PROCEDURE_NAME // ": Error occurred while reading real number.\n"//& ! LCOV_EXCL_LINE
199 : "The input string value for the variable scaleFactor (" // ScaleFactorObj%str // ") does not appear to follow "//& ! LCOV_EXCL_LINE
200 : "the standard syntax rules of "// methodName // " for this variable. '" // String%Parts(i)%record // & ! LCOV_EXCL_LINE
201 : "' cannot be parsed into any meaningful token. Please correct the input value, or drop it from the input list, "//& ! LCOV_EXCL_LINE
202 6 : "in which case, " // methodName // " will automatically assign an appropriate value to it.\n\n"
203 6 : return
204 : else
205 24 : ScaleFactorObj%val = ScaleFactorObj%val * temp
206 : end if
207 : end if
208 : end do
209 :
210 : ! Now check if the real value is positive
211 :
212 335 : if (ScaleFactorObj%val<=0) then
213 2 : Err%occurred = .true.
214 : Err%msg = Err%msg // &
215 : MODULE_NAME // PROCEDURE_NAME // ": Error occurred. &
216 : &The input string value (" // ScaleFactorObj%str // ") translates to a negative real value: " // &
217 : num2str(ScaleFactorObj%val) // ". &
218 : &Make sure the input string follows the syntax rules of " // methodName // " for this variable. &
219 : &Otherwise drop it from the input list. " // methodName // &
220 2 : " will automatically assign an appropriate value to it.\n\n"
221 2 : return
222 : end if
223 :
224 1053 : end subroutine checkForSanity
225 :
226 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
227 :
228 : end module SpecMCMC_ScaleFactor_mod ! LCOV_EXCL_LINE
|