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 `maxNumDomainCheckToWarn` 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_MaxNumDomainCheckToWarn_mod
49 :
50 : use Constants_mod, only: IK
51 : implicit none
52 :
53 : character(*), parameter :: MODULE_NAME = "@SpecBase_MaxNumDomainCheckToWarn_mod"
54 :
55 : integer(IK) :: maxNumDomainCheckToWarn ! namelist input
56 :
57 : type :: MaxNumDomainCheckToWarn_type
58 : integer(IK) :: val
59 : integer(IK) :: def
60 : integer(IK) :: null
61 : character(:), allocatable :: desc
62 : contains
63 : procedure, pass :: set => setMaxNumDomainCheckToWarn, checkForSanity, nullifyNameListVar
64 : end type MaxNumDomainCheckToWarn_type
65 :
66 : interface MaxNumDomainCheckToWarn_type
67 : module procedure :: constructMaxNumDomainCheckToWarn
68 : end interface MaxNumDomainCheckToWarn_type
69 :
70 : private :: constructMaxNumDomainCheckToWarn, setMaxNumDomainCheckToWarn
71 :
72 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
73 :
74 : contains
75 :
76 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
77 :
78 349 : function constructMaxNumDomainCheckToWarn() result(MaxNumDomainCheckToWarnObj)
79 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
80 : !DEC$ ATTRIBUTES DLLEXPORT :: constructMaxNumDomainCheckToWarn
81 : #endif
82 : use Constants_mod, only: IK, NULL_IK
83 : use Decoration_mod, only: TAB
84 : use String_mod, only: num2str
85 : implicit none
86 : type(MaxNumDomainCheckToWarn_type) :: MaxNumDomainCheckToWarnObj
87 349 : MaxNumDomainCheckToWarnObj%def = 1000_IK
88 349 : MaxNumDomainCheckToWarnObj%null = NULL_IK
89 : MaxNumDomainCheckToWarnObj%desc = &
90 : "maxNumDomainCheckToWarn is an integer number beyond which the user will be warned about the newly-proposed points &
91 : &being excessively proposed outside the domain of the objective function. For every maxNumDomainCheckToWarn &
92 : &consecutively-proposed new points that fall outside the domain of the objective function, the user will be warned until &
93 : &maxNumDomainCheckToWarn = maxNumDomainCheckToStop, in which case the sampler returns a fatal error and the program stops &
94 : &globally. The counter for this warning message is reset after a proposal sample from within the domain of the &
95 : &objective function is obtained. &
96 : &When out-of-domain sampling happens frequently, it is a strong indication of something fundamentally wrong in the &
97 : &simulation. It is, therefore, important to closely inspect and monitor for such frequent out-of-domain samplings. &
98 : &This can be done by setting maxNumDomainCheckToWarn to an appropriate value determined by the user. &
99 349 : &The default value is " // num2str(MaxNumDomainCheckToWarnObj%def) // "."
100 349 : end function constructMaxNumDomainCheckToWarn
101 :
102 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
103 :
104 349 : subroutine nullifyNameListVar(MaxNumDomainCheckToWarnObj)
105 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
106 : !DEC$ ATTRIBUTES DLLEXPORT :: nullifyNameListVar
107 : #endif
108 : implicit none
109 : class(MaxNumDomainCheckToWarn_type), intent(in) :: MaxNumDomainCheckToWarnObj
110 349 : maxNumDomainCheckToWarn = MaxNumDomainCheckToWarnObj%null
111 349 : end subroutine nullifyNameListVar
112 :
113 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
114 :
115 351 : subroutine setMaxNumDomainCheckToWarn(MaxNumDomainCheckToWarnObj,maxNumDomainCheckToWarn)
116 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
117 : !DEC$ ATTRIBUTES DLLEXPORT :: setMaxNumDomainCheckToWarn
118 : #endif
119 349 : use Constants_mod, only: IK
120 : implicit none
121 : class(MaxNumDomainCheckToWarn_type), intent(inout) :: MaxNumDomainCheckToWarnObj
122 : integer(IK), intent(in) :: maxNumDomainCheckToWarn
123 351 : MaxNumDomainCheckToWarnObj%val = maxNumDomainCheckToWarn
124 351 : if (MaxNumDomainCheckToWarnObj%val==MaxNumDomainCheckToWarnObj%null) then
125 341 : MaxNumDomainCheckToWarnObj%val = MaxNumDomainCheckToWarnObj%def
126 : end if
127 351 : end subroutine setMaxNumDomainCheckToWarn
128 :
129 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
130 :
131 345 : subroutine checkForSanity(MaxNumDomainCheckToWarn,Err,methodName)
132 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
133 : !DEC$ ATTRIBUTES DLLEXPORT :: checkForSanity
134 : #endif
135 351 : use Err_mod, only: Err_type
136 : use String_mod, only: num2str
137 : implicit none
138 : class(MaxNumDomainCheckToWarn_type), intent(in) :: MaxNumDomainCheckToWarn
139 : character(*), intent(in) :: methodName
140 : type(Err_type), intent(inout) :: Err
141 : character(*), parameter :: PROCEDURE_NAME = "@checkForSanity()"
142 345 : if ( MaxNumDomainCheckToWarn%val<1 ) then
143 4 : Err%occurred = .true.
144 : Err%msg = Err%msg // &
145 : MODULE_NAME // PROCEDURE_NAME // ": Error occurred. &
146 : &The input value for variable maxNumDomainCheckToWarn must be a positive integer. If you are not sure &
147 : &about the appropriate value for this variable, simply drop it from the input. " // &
148 4 : methodName // " will automatically assign an appropriate value to it.\n\n"
149 : end if
150 690 : end subroutine checkForSanity
151 :
152 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
153 :
154 : end module SpecBase_MaxNumDomainCheckToWarn_mod ! LCOV_EXCL_LINE
|