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 `sampleRefinementCount` 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_SampleRefinementCount_mod
49 :
50 : use Constants_mod, only: IK
51 : implicit none
52 :
53 : character(*), parameter :: MODULE_NAME = "@SpecMCMC_SampleRefinementCount_mod"
54 :
55 : integer(IK) :: sampleRefinementCount ! namelist input
56 :
57 : type :: SampleRefinementCount_type
58 : integer(IK) :: val
59 : integer(IK) :: def
60 : integer(IK) :: null
61 : character(:), allocatable :: str
62 : character(:), allocatable :: desc
63 : contains
64 : procedure, pass :: set => setSampleRefinementCount, checkForSanity, nullifyNameListVar
65 : end type SampleRefinementCount_type
66 :
67 : interface SampleRefinementCount_type
68 : module procedure :: constructSampleRefinementCount
69 : end interface SampleRefinementCount_type
70 :
71 : private :: constructSampleRefinementCount, setSampleRefinementCount, nullifyNameListVar
72 :
73 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
74 :
75 : contains
76 :
77 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
78 :
79 349 : function constructSampleRefinementCount(methodName) result(SampleRefinementCountObj)
80 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
81 : !DEC$ ATTRIBUTES DLLEXPORT :: constructSampleRefinementCount
82 : #endif
83 : use Constants_mod, only: IK, NULL_IK, POSINF_IK
84 : use String_mod, only: num2str
85 : use Decoration_mod, only: TAB
86 : implicit none
87 : character(*), intent(in) :: methodName
88 : type(SampleRefinementCount_type) :: SampleRefinementCountObj
89 349 : SampleRefinementCountObj%def = POSINF_IK
90 349 : SampleRefinementCountObj%null = NULL_IK
91 : SampleRefinementCountObj%desc = &
92 : "When sampleSize < 0, the integer variable sampleRefinementCount dictates the maximum number of times &
93 : &the MCMC chain will be refined to remove the autocorrelation within the output MCMC sample. For example,\n\n&
94 : & if sampleRefinementCount = 0,\n\n&
95 : & no refinement of the output MCMC chain will be performed, the resulting MCMC sample will simply correspond &
96 : &to the full MCMC chain in verbose format (i.e., each sampled state has a weight of one).\n\n&
97 : & if sampleRefinementCount = 1,\n\n&
98 : & the refinement of the output MCMC chain will be done only once if needed, and no more, &
99 : &even though there may still exist some residual autocorrelation in the output MCMC sample. &
100 : &In practice, only one refinement of the final output MCMC Chain should be enough to remove &
101 : &the existing autocorrelations in the final output sample. Exceptions occur when the Integrated &
102 : &Autocorrelation (IAC) of the output MCMC chain is comparable to or larger than the length of the chain. &
103 : &In such cases, neither the BatchMeans method nor any other method of IAC computation will be able to &
104 : &accurately compute the IAC. Consequently, the samples generated based on the computed IAC values will &
105 : &likely not be i.i.d. and will still be significantly autocorrelated. In such scenarios, more than &
106 : &one refinement of the MCMC chain will be necessary. Very small sample size resulting from multiple &
107 : &refinements of the sample could be a strong indication of the bad mixing of the MCMC chain and &
108 : &the output chain may not contain true i.i.d. samples from the target objective function.\n\n&
109 : & if sampleRefinementCount > 1,\n\n&
110 : & the refinement of the output MCMC chain will be done for a maximum sampleRefinementCount number of times, &
111 : &even though there may still exist some residual autocorrelation in the final output MCMC sample.\n\n&
112 : & if sampleRefinementCount >> 1 (e.g., comparable to or larger than the length of the MCMC chain),\n\n&
113 : & the refinement of the output MCMC chain will continue until the integrated autocorrelation of the resulting &
114 : &final sample is less than 2, virtually implying that an independent identically-distributed (i.i.d.) sample &
115 : &has finally been obtained.\n\n&
116 : &Note that to obtain i.i.d. samples from a multidimensional chain, "//methodName//" will, by default, use the maximum of &
117 : &Integrated Autocorrelation (IAC) among all dimensions of the chain to refine the chain. &
118 : &Note that the value specified for sampleRefinementCount is used only when the variable sampleSize < 0, otherwise, &
119 349 : &it will be ignored. The default value is sampleRefinementCount = "// num2str(SampleRefinementCountObj%def) //"."
120 349 : end function constructSampleRefinementCount
121 :
122 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
123 :
124 349 : subroutine nullifyNameListVar(SampleRefinementCountObj)
125 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
126 : !DEC$ ATTRIBUTES DLLEXPORT :: nullifyNameListVar
127 : #endif
128 : implicit none
129 : class(SampleRefinementCount_type), intent(in) :: SampleRefinementCountObj
130 349 : sampleRefinementCount = SampleRefinementCountObj%null
131 349 : end subroutine nullifyNameListVar
132 :
133 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
134 :
135 351 : subroutine setSampleRefinementCount(SampleRefinementCountObj,sampleRefinementCount)
136 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
137 : !DEC$ ATTRIBUTES DLLEXPORT :: setSampleRefinementCount
138 : #endif
139 349 : use String_mod, only: num2str
140 : use Constants_mod, only: IK
141 : implicit none
142 : class(SampleRefinementCount_type), intent(inout) :: SampleRefinementCountObj
143 : integer(IK), intent(in) :: sampleRefinementCount
144 351 : SampleRefinementCountObj%val = sampleRefinementCount
145 351 : if (SampleRefinementCountObj%val==SampleRefinementCountObj%null) then
146 345 : SampleRefinementCountObj%val = SampleRefinementCountObj%def
147 : end if
148 351 : SampleRefinementCountObj%str = num2str(SampleRefinementCountObj%val)
149 351 : end subroutine setSampleRefinementCount
150 :
151 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
152 :
153 345 : subroutine checkForSanity(SampleRefinementCountObj,Err,methodName)
154 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
155 : !DEC$ ATTRIBUTES DLLEXPORT :: checkForSanity
156 : #endif
157 351 : use Err_mod, only: Err_type
158 : use String_mod, only: num2str
159 : implicit none
160 : class(SampleRefinementCount_type), intent(in) :: SampleRefinementCountObj
161 : character(*), intent(in) :: methodName
162 : type(Err_type), intent(inout) :: Err
163 : character(*), parameter :: PROCEDURE_NAME = "@checkForSanity()"
164 345 : if ( SampleRefinementCountObj%val<0 ) then
165 4 : Err%occurred = .true.
166 : Err%msg = Err%msg // &
167 : MODULE_NAME // PROCEDURE_NAME // ": Error occurred. &
168 : &The input value for variable sampleRefinementCount must be a non-negative integer. &
169 : &If you are not sure about the appropriate value for this variable, simply drop it from the input. " // &
170 4 : methodName // " will automatically assign an appropriate value to it.\n\n"
171 : end if
172 690 : end subroutine checkForSanity
173 :
174 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
175 :
176 : end module SpecMCMC_SampleRefinementCount_mod ! LCOV_EXCL_LINE
|