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 `delayedRejectionCount` attribute of samplers of class [ParaDRAM_type](@ref paradram_mod::paradram_type).
45 : !> For more information, see the description of this attribute in the body of the module.
46 : !> \author Amir Shahmoradi
47 :
48 : module SpecDRAM_DelayedRejectionCount_mod
49 :
50 : use Constants_mod, only: IK
51 : implicit none
52 :
53 : character(*), parameter :: MODULE_NAME = "@SpecDRAM_DelayedRejectionCount_mod"
54 : integer(IK) , parameter :: MAX_DELAYED_REJECTION_COUNT = 1000_IK
55 : integer(IK) , parameter :: MIN_DELAYED_REJECTION_COUNT = 0_IK
56 :
57 : integer(IK) :: delayedRejectionCount ! namelist input
58 :
59 : type :: DelayedRejectionCount_type
60 : integer(IK) :: val
61 : integer(IK) :: def
62 : integer(IK) :: null
63 : character(:), allocatable :: desc
64 : contains
65 : procedure, pass :: set => setDelayedRejectionCount, checkForSanity, nullifyNameListVar
66 : end type DelayedRejectionCount_type
67 :
68 : interface DelayedRejectionCount_type
69 : module procedure :: constructDelayedRejectionCount
70 : end interface DelayedRejectionCount_type
71 :
72 : private :: constructDelayedRejectionCount, setDelayedRejectionCount, checkForSanity, nullifyNameListVar
73 :
74 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
75 :
76 : contains
77 :
78 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
79 :
80 1047 : function constructDelayedRejectionCount(methodName) result(self)
81 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
82 : !DEC$ ATTRIBUTES DLLEXPORT :: constructDelayedRejectionCount
83 : #endif
84 : use Constants_mod, only: IK, NULL_IK
85 : use String_mod, only: num2str
86 : use Decoration_mod, only: TAB
87 : implicit none
88 : character(*), intent(in) :: methodName
89 : type(DelayedRejectionCount_type) :: self
90 1047 : self%def = 0_IK
91 1047 : self%null = NULL_IK
92 : self%desc = &
93 : num2str(MIN_DELAYED_REJECTION_COUNT) // " <= delayedRejectionCount <= " // num2str(MAX_DELAYED_REJECTION_COUNT) // &
94 : " is an integer that represents the total number of stages for which rejections of new proposals &
95 : &will be tolerated by "//methodName//" before going back to the previously accepted point (state). &
96 : &Possible values are:\n\n&
97 : & delayedRejectionCount = 0\n\n&
98 : & indicating no deployment of the delayed rejection algorithm.\n\n&
99 : & delayedRejectionCount > 0\n\n&
100 : & which implies a maximum delayedRejectionCount number of rejections will be tolerated.\n\n&
101 : &For example, delayedRejectionCount = 1, means that at any point during the sampling, if a proposal is rejected, "&
102 : //methodName//" will not go back to the last sampled state. Instead, it will continue to propose a new state from the last &
103 : &rejected proposal. If the new state is again rejected based on the rules of "//methodName//", then the algorithm will not &
104 : &tolerate further rejections, because the maximum number of rejections to be tolerated has been set by the user to be &
105 : &delayedRejectionCount = 1. The algorithm then goes back to the original last-accepted state and will begin proposing &
106 : &new states from that location. &
107 1047 : &The default value is delayedRejectionCount = "// num2str(self%def) // "."
108 1047 : end function constructDelayedRejectionCount
109 :
110 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
111 :
112 1047 : subroutine nullifyNameListVar(self)
113 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
114 : !DEC$ ATTRIBUTES DLLEXPORT :: nullifyNameListVar
115 : #endif
116 : implicit none
117 : class(DelayedRejectionCount_type), intent(in) :: self
118 1047 : delayedRejectionCount = self%null
119 2094 : end subroutine nullifyNameListVar
120 :
121 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
122 :
123 1095 : pure subroutine setDelayedRejectionCount(self,delayedRejectionCount)
124 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
125 : !DEC$ ATTRIBUTES DLLEXPORT :: setDelayedRejectionCount
126 : #endif
127 1047 : use Constants_mod, only: IK
128 : implicit none
129 : class(DelayedRejectionCount_type), intent(inout) :: self
130 : integer(IK), intent(in) :: delayedRejectionCount
131 1095 : self%val = delayedRejectionCount
132 1017 : if (self%val==self%null) self%val = self%def
133 1095 : end subroutine setDelayedRejectionCount
134 :
135 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
136 :
137 1035 : subroutine checkForSanity(self,Err,methodName)
138 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
139 : !DEC$ ATTRIBUTES DLLEXPORT :: checkForSanity
140 : #endif
141 1095 : use Constants_mod, only: IK
142 : use Err_mod, only: Err_type
143 : use String_mod, only: num2str
144 : implicit none
145 : class(DelayedRejectionCount_type), intent(in) :: self
146 : character(*), intent(in) :: methodName
147 : type(Err_type), intent(inout) :: Err
148 : character(*), parameter :: PROCEDURE_NAME = "@checkForSanity()"
149 1035 : if ( self%val < MIN_DELAYED_REJECTION_COUNT ) then
150 6 : Err%occurred = .true.
151 : Err%msg = Err%msg // MODULE_NAME // PROCEDURE_NAME // ": Error occurred. " // & ! LCOV_EXCL_LINE
152 : "The input requested value for delayedRejectionCount (" // num2str(self%val) // & ! LCOV_EXCL_LINE
153 : ") can not be negative. If you are not sure of the appropriate value for delayedRejectionCount, drop it " // & ! LCOV_EXCL_LINE
154 : "from the input list. " // methodName // " will automatically assign an appropriate value to it.\n\n" ! LCOV_EXCL_LINE
155 1029 : elseif ( self%val > MAX_DELAYED_REJECTION_COUNT ) then
156 : Err%occurred = .true. ! LCOV_EXCL_LINE
157 : Err%msg = Err%msg // MODULE_NAME // PROCEDURE_NAME // ": Error occurred. " // & ! LCOV_EXCL_LINE
158 : "The input requested value for delayedRejectionCount (" // num2str(self%val) // & ! LCOV_EXCL_LINE
159 : ") can not be > " // num2str(MAX_DELAYED_REJECTION_COUNT) // & ! LCOV_EXCL_LINE
160 : ". If you are not sure of the appropriate value for delayedRejectionCount, drop it " // & ! LCOV_EXCL_LINE
161 : "from the input list. " // methodName // " will automatically assign an appropriate value to it.\n\n" ! LCOV_EXCL_LINE
162 : end if
163 2070 : end subroutine checkForSanity
164 :
165 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
166 :
167 : end module SpecDRAM_DelayedRejectionCount_mod ! LCOV_EXCL_LINE
|