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 `proposalStartCovMat` 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_ProposalStartCovMat_mod
49 :
50 : use Constants_mod, only: RK
51 : implicit none
52 :
53 : character(*), parameter :: MODULE_NAME = "@SpecMCMC_ProposalStartCovMat_mod"
54 :
55 : real(RK), allocatable :: proposalStartCovMat(:,:) ! namelist input
56 :
57 : type :: ProposalStartCovMat_type
58 : logical :: isPresent
59 : real(RK), allocatable :: Def(:,:)
60 : real(RK), allocatable :: Val(:,:)
61 : real(RK) :: null
62 : character(:), allocatable :: desc
63 : contains
64 : procedure, pass :: set => setProposalStartCoVMat, checkForSanity, nullifyNameListVar
65 : end type ProposalStartCovMat_type
66 :
67 : interface ProposalStartCovMat_type
68 : module procedure :: constructProposalStartCovMat
69 : end interface ProposalStartCovMat_type
70 :
71 : private :: constructProposalStartCovMat, setProposalStartCoVMat, checkForSanity, nullifyNameListVar
72 :
73 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
74 :
75 : contains
76 :
77 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
78 :
79 349 : function constructProposalStartCovMat(nd,methodName) result(self)
80 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
81 : !DEC$ ATTRIBUTES DLLEXPORT :: constructProposalStartCovMat
82 : #endif
83 : use Constants_mod, only: IK, NULL_RK
84 : use String_mod, only: num2str
85 : implicit none
86 : integer(IK), intent(in) :: nd
87 : character(*), intent(in) :: methodName
88 : type(ProposalStartCovMat_type) :: self
89 : integer(IK) :: i
90 349 : self%isPresent = .false.
91 349 : allocate( self%Def(nd,nd) )
92 1659 : self%Def = 0._RK
93 851 : do i = 1,nd
94 851 : self%Def(i,i) = 1._RK
95 : end do
96 349 : self%null = NULL_RK
97 : self%desc = &
98 : "proposalStartCovMat is a real-valued positive-definite matrix of size (ndim,ndim), where ndim is the dimension of the &
99 : &sampling space. It serves as the best-guess starting covariance matrix of the proposal distribution. &
100 : &To bring the sampling efficiency of " // methodName // " to within the desired requested range, the covariance matrix will &
101 : &be adaptively updated throughout the simulation, according to the user's requested schedule. If proposalStartCovMat &
102 : &is not provided by the user or it is completely missing from the input file, its value will be automatically computed &
103 : &via the input variables proposalStartCorMat and proposalStartStdVec (or via their default values, if not provided). &
104 349 : &The default value of proposalStartCovMat is an ndim-by-ndim Identity matrix."
105 349 : end function constructProposalStartCovMat
106 :
107 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
108 :
109 349 : subroutine nullifyNameListVar(self,nd)
110 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
111 : !DEC$ ATTRIBUTES DLLEXPORT :: nullifyNameListVar
112 : #endif
113 349 : use Constants_mod, only: IK
114 : implicit none
115 : class(ProposalStartCovMat_type), intent(in) :: self
116 : integer(IK), intent(in) :: nd
117 348 : if (allocated(proposalStartCovMat)) deallocate(proposalStartCovMat)
118 349 : allocate(proposalStartCovMat(nd,nd))
119 1659 : proposalStartCovMat = self%null
120 349 : end subroutine nullifyNameListVar
121 :
122 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
123 :
124 718 : subroutine setProposalStartCoVMat(self, proposalStartStdVec, proposalStartCorMat, proposalStartCovMat)
125 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
126 : !DEC$ ATTRIBUTES DLLEXPORT :: setProposalStartCoVMat
127 : #endif
128 349 : use Statistics_mod, only: getCovMatFromCorMatUpper
129 : use Constants_mod, only: RK, IK
130 : implicit none
131 : class(ProposalStartCovMat_type), intent(inout) :: self
132 : real(RK), intent(in) :: proposalStartCorMat(:,:), proposalStartStdVec(:)
133 : real(RK), intent(in), optional :: proposalStartCovMat(:,:)
134 : integer(IK) :: i, j, nd
135 :
136 359 : if (present(proposalStartCovMat)) then
137 1683 : self%val = proposalStartCovMat
138 : else
139 26 : self%val = self%null
140 : end if
141 :
142 359 : self%isPresent = .false.
143 359 : nd = size(proposalStartCorMat(:,1))
144 875 : do i = 1, nd
145 1705 : do j = 1, nd
146 1346 : if (self%val(j,i)==self%null) then
147 808 : self%val(j,i) = self%Def(j,i)
148 : else
149 22 : self%isPresent = .true.
150 : end if
151 : end do
152 : end do
153 :
154 359 : if (self%isPresent) return
155 :
156 : self%val = getCovMatFromCorMatUpper ( nd = nd & ! LCOV_EXCL_LINE
157 : , StdVec = proposalStartStdVec & ! LCOV_EXCL_LINE
158 : , CorMatUpper = proposalStartCorMat & ! LCOV_EXCL_LINE
159 2008 : )
160 :
161 359 : end subroutine setProposalStartCoVMat
162 :
163 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
164 :
165 345 : subroutine checkForSanity(self,Err,methodName,nd)
166 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
167 : !DEC$ ATTRIBUTES DLLEXPORT :: checkForSanity
168 : #endif
169 359 : use Constants_mod, only: IK, RK
170 : use Matrix_mod, only: isPosDef
171 : use String_mod, only: num2str
172 : use Err_mod, only: Err_type
173 : implicit none
174 : class(ProposalStartCovMat_type), intent(in) :: self
175 : integer(IK), intent(in) :: nd
176 : character(*), intent(in) :: methodName
177 : type(Err_type), intent(inout) :: Err
178 : character(*), parameter :: PROCEDURE_NAME = "@checkForSanity()"
179 345 : if (.not.isPosDef(nd,self%val)) then
180 4 : Err%occurred = .true.
181 : Err%msg = Err%msg // &
182 : MODULE_NAME // PROCEDURE_NAME // ": Error occurred. &
183 : &The input requested proposalStartCovMat for the proposal of " // methodName // &
184 4 : " is not a positive-definite matrix.\n\n"
185 : end if
186 690 : end subroutine checkForSanity
187 :
188 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
189 :
190 : end module SpecMCMC_ProposalStartCovMat_mod ! LCOV_EXCL_LINE
|