The ParaMonte Documentation Website
Current view: top level - kernel - SpecMCMC_mod.f90 (source / functions) Hit Total Coverage
Test: ParaMonte 1.5.1 :: Coarray Parallel Kernel - Code Coverage Report Lines: 155 155 100.0 %
Date: 2021-01-08 12:59:07 Functions: 6 6 100.0 %
Legend: Lines: hit not hit

          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 attributes of samplers of class [ParaMCMC_type](@ref paramcmc_mod::paramcmc_type).
      45             : !> For more information, see the description of this attributes in the body of the corresponding modules.
      46             : !> \author Amir Shahmoradi
      47             : 
      48             : module SpecMCMC_mod
      49             : 
      50             :     ! ParaMCMC Spec variable types
      51             :     use SpecMCMC_ChainSize_mod                          , only: ChainSize_type
      52             :     use SpecMCMC_ScaleFactor_mod                        , only: ScaleFactor_type
      53             :     use SpecMCMC_StartPointVec_mod                      , only: StartPointVec_type
      54             :     use SpecMCMC_ProposalModel_mod                      , only: ProposalModel_type
      55             :     use SpecMCMC_ProposalStartStdVec_mod                , only: ProposalStartStdVec_type
      56             :     use SpecMCMC_ProposalStartCorMat_mod                , only: ProposalStartCorMat_type
      57             :     use SpecMCMC_ProposalStartCovMat_mod                , only: ProposalStartCovMat_type
      58             :     use SpecMCMC_SampleRefinementCount_mod              , only: SampleRefinementCount_type
      59             :     use SpecMCMC_SampleRefinementMethod_mod             , only: SampleRefinementMethod_type
      60             :     use SpecMCMC_RandomStartPointRequested_mod          , only: RandomStartPointRequested_type
      61             :     use SpecMCMC_RandomStartPointDomainLowerLimitVec_mod, only: RandomStartPointDomainLowerLimitVec_type
      62             :     use SpecMCMC_RandomStartPointDomainUpperLimitVec_mod, only: RandomStartPointDomainUpperLimitVec_type
      63             : 
      64             :     ! ParaMCMC namelist variables
      65             :     use SpecMCMC_ChainSize_mod                          , only: ChainSize
      66             :     use SpecMCMC_ScaleFactor_mod                        , only: scaleFactor
      67             :     use SpecMCMC_StartPointVec_mod                      , only: startPointVec
      68             :     use SpecMCMC_ProposalModel_mod                      , only: proposalModel
      69             :     use SpecMCMC_ProposalStartStdVec_mod                , only: proposalStartStdVec
      70             :     use SpecMCMC_ProposalStartCorMat_mod                , only: proposalStartCorMat
      71             :     use SpecMCMC_ProposalStartCovMat_mod                , only: proposalStartCovMat
      72             :     use SpecMCMC_SampleRefinementCount_mod              , only: SampleRefinementCount
      73             :     use SpecMCMC_SampleRefinementMethod_mod             , only: sampleRefinementMethod
      74             :     use SpecMCMC_RandomStartPointRequested_mod          , only: randomStartPointRequested
      75             :     use SpecMCMC_RandomStartPointDomainLowerLimitVec_mod, only: randomStartPointDomainLowerLimitVec
      76             :     use SpecMCMC_RandomStartPointDomainUpperLimitVec_mod, only: randomStartPointDomainUpperLimitVec
      77             : 
      78             :     implicit none
      79             : 
      80             :     type                                                :: SpecMCMC_type
      81             :         type(ChainSize_type)                            :: ChainSize
      82             :         type(ScaleFactor_type)                          :: ScaleFactor
      83             :         type(StartPointVec_type)                        :: startPointVec
      84             :         type(ProposalModel_type)                        :: ProposalModel
      85             :         type(ProposalStartStdVec_type)                  :: proposalStartStdVec
      86             :         type(ProposalStartCorMat_type)                  :: proposalStartCorMat
      87             :         type(ProposalStartCovMat_type)                  :: proposalStartCovMat
      88             :         type(SampleRefinementCount_type)                :: SampleRefinementCount
      89             :         type(SampleRefinementMethod_type)               :: SampleRefinementMethod
      90             :         type(RandomStartPointRequested_type)            :: randomStartPointRequested
      91             :         type(RandomStartPointDomainLowerLimitVec_type)  :: RandomStartPointDomainLowerLimitVec
      92             :         type(RandomStartPointDomainUpperLimitVec_type)  :: RandomStartPointDomainUpperLimitVec
      93             :     contains
      94             :         procedure, pass                                 :: nullifyNameListVar
      95             :         procedure, pass                                 :: setFromInputFile
      96             :         procedure, pass                                 :: setFromInputArgs
      97             :         procedure, pass                                 :: checkForSanity
      98             :         procedure, pass                                 :: reportValues
      99             :     end type SpecMCMC_type
     100             : 
     101             :     interface SpecMCMC_type
     102             :         module procedure                                :: constructSpecMCMC
     103             :     end interface SpecMCMC_type
     104             : 
     105             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     106             : 
     107             : contains
     108             : 
     109             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     110             : 
     111        1047 :     function constructSpecMCMC  ( nd &
     112             :                                 , methodName &
     113             :                                 ) result(SpecMCMC)
     114             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     115             :         !DEC$ ATTRIBUTES DLLEXPORT :: constructSpecMCMC
     116             : #endif
     117             :         use Constants_mod, only: IK, RK
     118             :         implicit none
     119             :         integer(IK) , intent(in)    :: nd
     120             :         character(*), intent(in)    :: methodName
     121             :         type(SpecMCMC_type)         :: SpecMCMC
     122        1047 :         SpecMCMC%ChainSize                              = ChainSize_type                            (methodName)
     123        1047 :         SpecMCMC%ScaleFactor                            = ScaleFactor_type                          (nd,methodName)
     124        1047 :         SpecMCMC%startPointVec                          = StartPointVec_type                        ()
     125        1047 :         SpecMCMC%ProposalModel                          = ProposalModel_type                        ()
     126        1047 :         SpecMCMC%proposalStartStdVec                    = ProposalStartStdVec_type                  (nd,methodName)
     127        1047 :         SpecMCMC%proposalStartCorMat                    = ProposalStartCorMat_type                  (nd,methodName)
     128        1047 :         SpecMCMC%proposalStartCovMat                    = ProposalStartCovMat_type                  (nd,methodName)
     129        1047 :         SpecMCMC%SampleRefinementCount                  = SampleRefinementCount_type                (methodName)
     130        1047 :         SpecMCMC%SampleRefinementMethod                 = SampleRefinementMethod_type               (methodName)
     131        1047 :         SpecMCMC%RandomStartPointRequested              = RandomStartPointRequested_type            (methodName)
     132        1047 :         SpecMCMC%RandomStartPointDomainLowerLimitVec    = RandomStartPointDomainLowerLimitVec_type  (methodName)
     133        1047 :         SpecMCMC%RandomStartPointDomainUpperLimitVec    = RandomStartPointDomainUpperLimitVec_type  (methodName)
     134        1047 :     end function constructSpecMCMC
     135             : 
     136             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     137             : 
     138        1047 :     subroutine nullifyNameListVar( SpecMCMC, nd )
     139             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     140             :         !DEC$ ATTRIBUTES DLLEXPORT :: nullifyNameListVar
     141             : #endif
     142        1047 :         use Constants_mod, only: IK, RK
     143             :         implicit none
     144             :         class(SpecMCMC_type), intent(in)    :: SpecMCMC
     145             :         integer(IK), intent(in)             :: nd
     146        1047 :         call SpecMCMC%ChainSize                             %nullifyNameListVar()
     147        1047 :         call SpecMCMC%ScaleFactor                           %nullifyNameListVar()
     148        1047 :         call SpecMCMC%startPointVec                         %nullifyNameListVar(nd)
     149        1047 :         call SpecMCMC%ProposalModel                         %nullifyNameListVar()
     150        1047 :         call SpecMCMC%proposalStartStdVec                   %nullifyNameListVar(nd)
     151        1047 :         call SpecMCMC%proposalStartCorMat                   %nullifyNameListVar(nd)
     152        1047 :         call SpecMCMC%proposalStartCovMat                   %nullifyNameListVar(nd)
     153        1047 :         call SpecMCMC%SampleRefinementCount                 %nullifyNameListVar()
     154        1047 :         call SpecMCMC%SampleRefinementMethod                %nullifyNameListVar()
     155        1047 :         call SpecMCMC%RandomStartPointRequested             %nullifyNameListVar()
     156        1047 :         call SpecMCMC%RandomStartPointDomainLowerLimitVec   %nullifyNameListVar(nd)
     157        1047 :         call SpecMCMC%RandomStartPointDomainUpperLimitVec   %nullifyNameListVar(nd)
     158        1047 :     end subroutine nullifyNameListVar
     159             : 
     160             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     161             : 
     162        1047 :     subroutine setFromInputFile(SpecMCMC, Err) ! domainLowerLimitVec, domainUpperLimitVec )
     163             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     164             :         !DEC$ ATTRIBUTES DLLEXPORT :: setFromInputFile
     165             : #endif
     166        1047 :         use SpecBase_mod, only: SpecBase_type
     167             :         use Constants_mod, only: IK, RK
     168             :         use Err_mod, only: Err_type
     169             : 
     170             :         implicit none
     171             : 
     172             :         class(SpecMCMC_type), intent(inout)     :: SpecMCMC
     173             :         type(Err_type), intent(out)             :: Err
     174             : 
     175        1047 :         Err%occurred = .false.
     176        1047 :         Err%msg = ""
     177             : 
     178        1047 :         call SpecMCMC%ChainSize                             %set(chainSize)
     179        1047 :         call SpecMCMC%ScaleFactor                           %set(scaleFactor)
     180        1047 :         call SpecMCMC%ProposalModel                         %set(trim(adjustl(proposalModel)))
     181        1047 :         call SpecMCMC%proposalStartStdVec                   %set(proposalStartStdVec)
     182        1047 :         call SpecMCMC%proposalStartCorMat                   %set(proposalStartCorMat)
     183        1047 :         call SpecMCMC%proposalStartCovMat                   %set(SpecMCMC%proposalStartStdVec%val, SpecMCMC%proposalStartCorMat%val, proposalStartCovMat)
     184        1047 :         call SpecMCMC%SampleRefinementCount                 %set(sampleRefinementCount)
     185        1047 :         call SpecMCMC%SampleRefinementMethod                %set(sampleRefinementMethod)
     186        1047 :         call SpecMCMC%RandomStartPointRequested             %set(randomStartPointRequested)
     187        1047 :         call SpecMCMC%RandomStartPointDomainLowerLimitVec   %set(randomStartPointDomainLowerLimitVec)
     188        1047 :         call SpecMCMC%RandomStartPointDomainUpperLimitVec   %set(randomStartPointDomainUpperLimitVec)
     189        1047 :         call SpecMCMC%startPointVec                         %set(startPointVec)
     190             : 
     191        1047 :     end subroutine setFromInputFile
     192             : 
     193             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     194             : 
     195        1041 :     subroutine setFromInputArgs ( SpecMCMC &
     196             :                                 ! ParaMCMC variables
     197             :                                 , chainSize                             &
     198             :                                 , scaleFactor                           &
     199        1041 :                                 , startPointVec                         &
     200             :                                 , proposalModel                         &
     201          18 :                                 , proposalStartStdVec                   &
     202        1041 :                                 , proposalStartCorMat                   &
     203        1041 :                                 , proposalStartCovMat                   &
     204             :                                 , sampleRefinementCount                 &
     205             :                                 , sampleRefinementMethod                &
     206             :                                 , randomStartPointRequested             &
     207        1041 :                                 , randomStartPointDomainLowerLimitVec   &
     208        1041 :                                 , randomStartPointDomainUpperLimitVec   &
     209             :                                 )
     210             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     211             :         !DEC$ ATTRIBUTES DLLEXPORT :: setFromInputArgs
     212             : #endif
     213             : 
     214        1047 :         use SpecBase_mod, only: SpecBase_type
     215             :         use Constants_mod, only: IK, RK
     216             :         implicit none
     217             :         class(SpecMCMC_type), intent(inout) :: SpecMCMC
     218             : 
     219             :         ! ParaMCMC variables
     220             :         integer(IK) , intent(in), optional  :: chainSize
     221             :         character(*), intent(in), optional  :: scaleFactor
     222             :         real(RK)    , intent(in), optional  :: startPointVec(:)
     223             :         character(*), intent(in), optional  :: proposalModel
     224             :         real(RK)    , intent(in), optional  :: proposalStartStdVec(:)
     225             :         real(RK)    , intent(in), optional  :: proposalStartCorMat(:,:)
     226             :         real(RK)    , intent(in), optional  :: proposalStartCovMat(:,:)
     227             :         integer(IK) , intent(in), optional  :: sampleRefinementCount
     228             :         character(*), intent(in), optional  :: sampleRefinementMethod
     229             :         logical     , intent(in), optional  :: randomStartPointRequested
     230             :         real(RK)    , intent(in), optional  :: randomStartPointDomainLowerLimitVec(:)
     231             :         real(RK)    , intent(in), optional  :: randomStartPointDomainUpperLimitVec(:)
     232             : 
     233             :         logical                             :: proposalStartStdVecIsPresent
     234             :         logical                             :: proposalStartCorMatIsPresent
     235             :         logical                             :: proposalStartCovMatIsPresent
     236             : 
     237        1041 :         proposalStartStdVecIsPresent = present(proposalStartStdVec)
     238        1041 :         proposalStartCorMatIsPresent = present(proposalStartCorMat)
     239        1041 :         proposalStartCovMatIsPresent = present(proposalStartCovMat) .or. proposalStartCorMatIsPresent .or. proposalStartStdVecIsPresent
     240             : 
     241             : 
     242        1041 :         if (present(chainSize))                             call SpecMCMC%ChainSize                             %set(chainSize)
     243        1041 :         if (present(scaleFactor))                           call SpecMCMC%ScaleFactor                           %set(scaleFactor)
     244        1041 :         if (present(proposalModel))                         call SpecMCMC%ProposalModel                         %set(trim(adjustl(proposalModel)))
     245        1041 :         if (proposalStartStdVecIsPresent)                   call SpecMCMC%proposalStartStdVec                   %set(proposalStartStdVec)
     246        1041 :         if (proposalStartCorMatIsPresent)                   call SpecMCMC%proposalStartCorMat                   %set(proposalStartCorMat)
     247        1041 :         if (proposalStartCovMatIsPresent)                   call SpecMCMC%proposalStartCovMat                   %set(SpecMCMC%proposalStartStdVec%val, SpecMCMC%proposalStartCorMat%val, proposalStartCovMat)
     248        1041 :         if (present(sampleRefinementCount))                 call SpecMCMC%SampleRefinementCount                 %set(sampleRefinementCount)
     249        1041 :         if (present(sampleRefinementMethod))                call SpecMCMC%SampleRefinementMethod                %set(sampleRefinementMethod)
     250        1041 :         if (present(randomStartPointRequested))             call SpecMCMC%RandomStartPointRequested             %set(randomStartPointRequested)
     251             : 
     252        1041 :         call SpecMCMC%RandomStartPointDomainLowerLimitVec   %set(randomStartPointDomainLowerLimitVec)
     253        1041 :         call SpecMCMC%RandomStartPointDomainUpperLimitVec   %set(randomStartPointDomainUpperLimitVec)
     254        1041 :         call SpecMCMC%startPointVec                         %set(startPointVec)
     255             : 
     256        2082 :     end subroutine setFromInputArgs
     257             : 
     258             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     259             : 
     260         969 :     subroutine reportValues ( SpecMCMC              &
     261             :                             , prefix                &
     262             :                             , methodName            &
     263             :                             , outputUnit            &
     264             :                             , isLeaderImage         &
     265             :                             , splashModeRequested   &
     266             :                             )
     267             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     268             :         !DEC$ ATTRIBUTES DLLEXPORT :: reportValues
     269             : #endif
     270        1041 :         use Decoration_mod, only: GENERIC_OUTPUT_FORMAT
     271             :         use Decoration_mod, only: GENERIC_TABBED_FORMAT
     272             :         use Decoration_mod, only: TAB
     273             :         use Constants_mod, only: IK, RK
     274             :         use Err_mod, only: note
     275             :         implicit none
     276             :         class(SpecMCMC_type), intent(in)    :: SpecMCMC
     277             :         character(*), intent(in)            :: prefix, methodName
     278             :         integer(IK), intent(in)             :: outputUnit
     279             :         logical, intent(in)                 :: isLeaderImage, splashModeRequested
     280             :         integer(IK)                         :: ndim, i
     281             : 
     282         969 :         if (isLeaderImage) then
     283             : 
     284         359 :             ndim = size(SpecMCMC%proposalStartCovMat%val(:,1))
     285             : 
     286         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     287         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT) "chainSize"
     288         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     289         359 :             write(outputUnit,GENERIC_TABBED_FORMAT) SpecMCMC%ChainSize%val
     290         359 :             if (splashModeRequested) call note( prefix = prefix, outputUnit = outputUnit, newline = "\n", msg = SpecMCMC%ChainSize%desc )
     291             : 
     292             : 
     293         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     294         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT) "randomStartPointDomainLowerLimitVec"
     295         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     296         871 :             do i = 1, size(SpecMCMC%RandomStartPointDomainLowerLimitVec%val(:))
     297         871 :                 write(outputUnit,GENERIC_TABBED_FORMAT) SpecMCMC%RandomStartPointDomainLowerLimitVec%val(i)
     298             :             end do
     299         359 :             if (splashModeRequested) call note( prefix = prefix, outputUnit = outputUnit, newline = "\n", msg = SpecMCMC%RandomStartPointDomainLowerLimitVec%desc )
     300             : 
     301             : 
     302         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     303         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT) "randomStartPointDomainUpperLimitVec"
     304         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     305         871 :             do i = 1, size(SpecMCMC%RandomStartPointDomainUpperLimitVec%val(:))
     306         871 :                 write(outputUnit,GENERIC_TABBED_FORMAT) SpecMCMC%RandomStartPointDomainUpperLimitVec%val(i)
     307             :             end do
     308         359 :             if (splashModeRequested) call note( prefix = prefix, outputUnit = outputUnit, newline = "\n", msg = SpecMCMC%RandomStartPointDomainUpperLimitVec%desc )
     309             : 
     310             : 
     311         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     312         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT) "startPointVec"
     313         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     314         871 :             do i = 1, size(SpecMCMC%startPointVec%val(:))
     315         871 :                 write(outputUnit,GENERIC_TABBED_FORMAT) SpecMCMC%startPointVec%val(i)
     316             :             end do
     317         359 :             if (splashModeRequested) call note( prefix = prefix, outputUnit = outputUnit, newline = "\n", msg = SpecMCMC%startPointVec%desc )
     318             : 
     319             : 
     320         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     321         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT) "randomStartPointRequested"
     322         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     323         359 :             write(outputUnit,GENERIC_TABBED_FORMAT) SpecMCMC%RandomStartPointRequested%val
     324         359 :             if (splashModeRequested) call note( prefix = prefix, outputUnit = outputUnit, newline = "\n", msg = SpecMCMC%RandomStartPointRequested%desc )
     325             : 
     326             : 
     327         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     328         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT) "sampleRefinementCount"
     329         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     330         359 :             write(outputUnit,GENERIC_TABBED_FORMAT) SpecMCMC%SampleRefinementCount%val
     331         359 :             if (splashModeRequested) call note( prefix = prefix, outputUnit = outputUnit, newline = "\n", msg = SpecMCMC%SampleRefinementCount%desc )
     332             : 
     333             : 
     334         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     335         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT) "sampleRefinementMethod"
     336         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     337         359 :             write(outputUnit,GENERIC_TABBED_FORMAT) SpecMCMC%SampleRefinementMethod%val
     338         359 :             if (splashModeRequested) call note( prefix = prefix, outputUnit = outputUnit, newline = "\n", msg = SpecMCMC%SampleRefinementMethod%desc )
     339             : 
     340             : 
     341         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     342         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT) "scaleFactor"
     343         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     344         359 :             write(outputUnit,GENERIC_TABBED_FORMAT) SpecMCMC%ScaleFactor%str
     345         359 :             if (splashModeRequested) call note( prefix = prefix, outputUnit = outputUnit, newline = "\n", msg = SpecMCMC%ScaleFactor%desc )
     346             : 
     347             : 
     348             :             !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     349             :             ! proposal distribution
     350             :             !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     351             : 
     352             :             !block
     353             :             !    use Decoration_mod, only: writeDecoratedText
     354             :             !    call writeDecoratedText ( text = "\n" // methodName // " proposal specifications\n" &
     355             :             !                            , marginTop = 1     &
     356             :             !                            , marginBot = 1     &
     357             :             !                            , newline = "\n"    &
     358             :             !                            , outputUnit = outputUnit )
     359             :             !end block
     360             : 
     361             : 
     362         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     363         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT) "proposalModel"
     364         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     365         359 :             write(outputUnit,GENERIC_TABBED_FORMAT) SpecMCMC%ProposalModel%val
     366         359 :             if (splashModeRequested) call note( prefix = prefix, outputUnit = outputUnit, newline = "\n", msg = SpecMCMC%ProposalModel%desc )
     367             : 
     368             : 
     369         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     370         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT) "proposalStartStdVec"
     371         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     372         871 :             do i = 1, ndim
     373         871 :                 write(outputUnit,GENERIC_TABBED_FORMAT) SpecMCMC%proposalStartStdVec%val(i)
     374             :             end do
     375         359 :             if (splashModeRequested) call note( prefix = prefix, outputUnit = outputUnit, newline = "\n", msg = SpecMCMC%proposalStartStdVec%desc )
     376             : 
     377             : 
     378         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     379         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT) "proposalStartCorMat"
     380         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     381         871 :             do i = 1, ndim
     382         871 :                 write(outputUnit,GENERIC_TABBED_FORMAT) SpecMCMC%proposalStartCorMat%val(:,i)
     383             :             end do
     384         359 :             if (splashModeRequested) call note( prefix = prefix, outputUnit = outputUnit, newline = "\n", msg = SpecMCMC%proposalStartCorMat%desc )
     385             : 
     386             : 
     387         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     388         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT) "proposalStartCovMat"
     389         359 :             write(outputUnit,GENERIC_OUTPUT_FORMAT)
     390         871 :             do i = 1, ndim
     391         871 :                 write(outputUnit,GENERIC_TABBED_FORMAT) SpecMCMC%proposalStartCovMat%val(:,i)
     392             :             end do
     393         359 :             if (splashModeRequested) call note( prefix = prefix, outputUnit = outputUnit, newline = "\n", msg = SpecMCMC%proposalStartCovMat%desc )
     394             : 
     395             :         end if
     396             : 
     397             : 
     398        1938 :     end subroutine reportValues
     399             : 
     400             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     401             : 
     402        1035 :     subroutine checkForSanity(SpecMCMC, SpecBase, methodName, nd, Err) ! ,domainLowerLimitVec,domainUpperLimitVec)
     403             : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
     404             :         !DEC$ ATTRIBUTES DLLEXPORT :: checkForSanity
     405             : #endif
     406         969 :         use SpecBase_mod, only: SpecBase_type
     407             :         use Constants_mod, only: IK, RK
     408             :         use Err_mod, only: Err_type
     409             :         implicit none
     410             :         class(SpecMCMC_type), intent(inout) :: SpecMCMC
     411             :         type(SpecBase_type) , intent(in)    :: SpecBase
     412             :         character(*), intent(in)            :: methodName
     413             :         integer(IK), intent(in)             :: nd
     414             :         type(Err_type), intent(inout)       :: Err
     415             :         !real(RK), intent(in)                :: domainLowerLimitVec(:), domainUpperLimitVec(:)
     416        1035 :         call SpecMCMC%ChainSize                             %checkForSanity(Err,methodName,nd)
     417        1035 :         call SpecMCMC%ScaleFactor                           %checkForSanity(Err,methodName)
     418        1035 :         call SpecMCMC%ProposalModel                         %checkForSanity(Err,methodName)
     419        1035 :         call SpecMCMC%proposalStartCovMat                   %checkForSanity(Err,methodName,nd)
     420        1035 :         call SpecMCMC%proposalStartCorMat                   %checkForSanity(Err,methodName,nd)
     421        1035 :         call SpecMCMC%proposalStartStdVec                   %checkForSanity(Err,methodName,nd)
     422        1035 :         call SpecMCMC%SampleRefinementCount                 %checkForSanity(Err,methodName)
     423        1035 :         call SpecMCMC%SampleRefinementMethod                %checkForSanity(Err,methodName)
     424        1035 :         call SpecMCMC%RandomStartPointDomainLowerLimitVec   %checkForSanity(Err,methodName, SpecBase, randomStartPointRequested = SpecMCMC%RandomStartPointRequested%val )
     425             :         call SpecMCMC%RandomStartPointDomainUpperLimitVec   %checkForSanity(Err,methodName, SpecBase, randomStartPointRequested = SpecMCMC%RandomStartPointRequested%val &
     426        1035 :                                                                                                     , randomStartPointDomainLowerLimitVec = SpecMCMC%RandomStartPointDomainLowerLimitVec%val )
     427             :         call SpecMCMC%startPointVec                         %checkForSanity(Err,methodName, SpecBase, randomStartPointRequested = SpecMCMC%RandomStartPointRequested%val &
     428             :                                                                                                     , randomStartPointDomainLowerLimitVec = SpecMCMC%RandomStartPointDomainLowerLimitVec%Val & ! LCOV_EXCL_LINE
     429        1035 :                                                                                                     , randomStartPointDomainUpperLimitVec = SpecMCMC%RandomStartPointDomainUpperLimitVec%val )
     430        2070 :     end subroutine checkForSanity
     431             : 
     432             : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
     433             : 
     434             : end module SpecMCMC_mod ! LCOV_EXCL_LINE

ParaMonte: Plain Powerful Parallel Monte Carlo Library 
The Computational Data Science Lab
© Copyright 2012 - 2021