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 `variableNameList` 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_VariableNameList_mod
49 :
50 : use Constants_mod, only: IK
51 : implicit none
52 :
53 : character(*), parameter :: MODULE_NAME = "@SpecBase_VariableNameList_mod"
54 :
55 : integer(IK), parameter :: MAX_VARIABLE_NAME_LEN = 63_IK
56 :
57 : character(MAX_VARIABLE_NAME_LEN), allocatable :: variableNameList(:) ! namelist input
58 :
59 : type, private :: MaxLen_type
60 : integer(IK) :: val
61 : character(:), allocatable :: str
62 : end type MaxLen_type
63 :
64 : type :: VariableNameList_type
65 : character(MAX_VARIABLE_NAME_LEN), allocatable :: Val(:)
66 : character(MAX_VARIABLE_NAME_LEN), allocatable :: Def(:)
67 : character(MAX_VARIABLE_NAME_LEN) :: null
68 : character(:), allocatable :: desc
69 : character(:), allocatable :: prefix
70 : type(MaxLen_type) :: MaxLen
71 : contains
72 : procedure, pass :: set => setVariableNameList, nullifyNameListVar
73 : end type VariableNameList_type
74 :
75 : interface VariableNameList_type
76 : module procedure :: constructVariableNameList
77 : end interface VariableNameList_type
78 :
79 : private :: constructVariableNameList, setVariableNameList, nullifyNameListVar
80 :
81 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
82 :
83 : contains
84 :
85 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
86 :
87 349 : function constructVariableNameList(nd,methodName) result(VariableNameListObj)
88 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
89 : !DEC$ ATTRIBUTES DLLEXPORT :: constructVariableNameList
90 : #endif
91 : use Constants_mod, only: IK, NULL_SK
92 : use String_mod, only: num2str
93 : implicit none
94 : integer(IK), intent(in) :: nd
95 : character(*), intent(in) :: methodName
96 : type(VariableNameList_type) :: VariableNameListObj
97 : integer :: i
98 :
99 349 : VariableNameListObj%null = repeat(NULL_SK, MAX_VARIABLE_NAME_LEN)
100 :
101 349 : VariableNameListObj%prefix = "SampleVariable"
102 349 : if ( allocated(VariableNameListObj%Def) ) deallocate(VariableNameListObj%Def)
103 349 : allocate( VariableNameListObj%Def(nd) )
104 851 : do i = 1,nd
105 851 : VariableNameListObj%Def(i) = adjustl( VariableNameListObj%prefix//num2str(i) )
106 : end do
107 :
108 : VariableNameListObj%desc = &
109 : "variableNameList contains the names of the variables to be sampled by " // methodName // ". &
110 : &It is used to construct the header of the output sample file. &
111 : &Any element of variableNameList that is not set by the user will be automatically assigned a default name. &
112 349 : &The default value is '" // VariableNameListObj%prefix // "i' where integer 'i' is the index of the variable."
113 349 : end function constructVariableNameList
114 :
115 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
116 :
117 349 : subroutine nullifyNameListVar(VariableNameListObj,nd)
118 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
119 : !DEC$ ATTRIBUTES DLLEXPORT :: nullifyNameListVar
120 : #endif
121 349 : use Constants_mod, only: IK
122 : implicit none
123 : class(VariableNameList_type), intent(in) :: VariableNameListObj
124 : integer(IK), intent(in) :: nd
125 348 : if (allocated(variableNameList)) deallocate(variableNameList)
126 349 : allocate(variableNameList(nd))
127 851 : variableNameList = VariableNameListObj%null
128 349 : end subroutine nullifyNameListVar
129 :
130 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
131 :
132 698 : subroutine setVariableNameList(VariableNameListObj,variableNameList)
133 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
134 : !DEC$ ATTRIBUTES DLLEXPORT :: setVariableNameList
135 : #endif
136 349 : use String_mod, only: num2str
137 : implicit none
138 : class(VariableNameList_type), intent(inout) :: VariableNameListObj
139 : character(*), intent(in) :: variableNameList(:)
140 : integer :: i, lentrim
141 349 : VariableNameListObj%MaxLen%val = -1
142 349 : if ( allocated(VariableNameListObj%Val) ) deallocate(VariableNameListObj%Val)
143 851 : allocate( VariableNameListObj%Val, source=VariableNameListObj%Def )
144 851 : do i = 1, size(VariableNameListObj%Val)
145 502 : if (trim(adjustl(variableNameList(i)))/=trim(adjustl(VariableNameListObj%null))) VariableNameListObj%Val(i) = variableNameList(i)
146 502 : lentrim = len_trim(adjustl(VariableNameListObj%Val(i)))
147 851 : if (lentrim>VariableNameListObj%MaxLen%val) VariableNameListObj%MaxLen%val = lentrim
148 : end do
149 349 : VariableNameListObj%MaxLen%str = num2str(VariableNameListObj%MaxLen%val)
150 349 : end subroutine setVariableNameList
151 :
152 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
153 :
154 : end module SpecBase_VariableNameList_mod ! LCOV_EXCL_LINE
|