MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
DefinitionSelect.f90
Go to the documentation of this file.
1 !> @brief This module contains the DefinitionSelectModule
2 !!
3 !! This module contains the routines for getting parameter
4 !! definitions, aggregate definitions, and block definitions
5 !! for the different package types.
6 !!
7 !<
9 
10  use kindmodule, only: i4b
11  use simvariablesmodule, only: errmsg
15 
16  implicit none
17  private
20  public :: split_record_definition
21  public :: idt_parse_rectype
22  public :: idt_datatype
23 
24 contains
25 
26  !> @brief allocate and set RECARRAY, KEYSTRING or RECORD param list
27  !<
28  subroutine idt_parse_rectype(idt, cols, ncol)
29  ! -- modules
30  use constantsmodule, only: linelength
31  use inputoutputmodule, only: parseline
32  ! -- dummy
33  type(inputparamdefinitiontype), pointer, intent(in) :: idt
34  character(len=LINELENGTH), dimension(:), allocatable, &
35  intent(inout) :: cols
36  integer(I4B), intent(inout) :: ncol
37  ! -- local
38  character(len=:), allocatable :: parse_str
39  character(len=LINELENGTH), dimension(:), allocatable :: param_cols
40  integer(I4B) :: param_ncol, n
41  !
42  ! -- initialize
43  if (allocated(cols)) deallocate (cols)
44  ncol = 0
45  !
46  ! -- split definition
47  parse_str = trim(idt%datatype)//' '
48  call parseline(parse_str, param_ncol, param_cols)
49  !
50  if (param_ncol > 1) then
51  if (param_cols(1) == 'RECARRAY' .or. &
52  param_cols(1) == 'KEYSTRING' .or. &
53  param_cols(1) == 'RECORD') then
54  ! -- exclude 1st column
55  allocate (cols(param_ncol - 1))
56  do n = 2, param_ncol
57  cols(n - 1) = param_cols(n)
58  end do
59  !
60  ! -- set ncol
61  ncol = param_ncol - 1
62  end if
63  end if
64  !
65  ! -- cleanup
66  if (allocated(param_cols)) deallocate (param_cols)
67  if (allocated(parse_str)) deallocate (parse_str)
68  end subroutine idt_parse_rectype
69 
70  !> @brief return input definition type datatype
71  !<
72  function idt_datatype(idt) result(datatype)
73  ! -- modules
74  use constantsmodule, only: linelength
75  ! -- dummy
76  type(inputparamdefinitiontype), pointer, intent(in) :: idt
77  ! -- result
78  character(len=LINELENGTH) :: datatype
79  !
80  if (idt%datatype(1:9) == 'KEYSTRING') then
81  datatype = 'KEYSTRING'
82  else if (idt%datatype(1:8) == 'RECARRAY') then
83  datatype = 'RECARRAY'
84  else if (idt%datatype(1:6) == 'RECORD') then
85  datatype = 'RECORD'
86  else
87  datatype = idt%datatype
88  end if
89  end function idt_datatype
90 
91  !> @brief Return parameter definition
92  !<
93  function get_param_definition_type(input_definition_types, &
94  component_type, subcomponent_type, &
95  blockname, tagname, filename) &
96  result(idt)
97  type(inputparamdefinitiontype), dimension(:), intent(in), target :: &
98  input_definition_types
99  character(len=*), intent(in) :: component_type !< component type, such as GWF or GWT
100  character(len=*), intent(in) :: subcomponent_type !< subcomponent type, such as DIS or NPF
101  character(len=*), intent(in) :: blockname !< name of the block
102  character(len=*), intent(in) :: tagname !< name of the input tag
103  character(len=*), intent(in) :: filename !< input filename
104  type(inputparamdefinitiontype), pointer :: idt !< corresponding InputParameterDefinitionType for this tag
105  type(inputparamdefinitiontype), pointer :: tmp_ptr
106  integer(I4B) :: i
107  !
108  nullify (idt)
109  do i = 1, size(input_definition_types)
110  tmp_ptr => input_definition_types(i)
111  if (tmp_ptr%component_type == component_type .and. &
112  tmp_ptr%subcomponent_type == subcomponent_type .and. &
113  tmp_ptr%blockname == blockname .and. &
114  tmp_ptr%tagname == tagname) then
115  idt => input_definition_types(i)
116  exit
117  end if
118  end do
119  !
120  if (.not. associated(idt)) then
121  write (errmsg, '(a,a,a,a,a)') &
122  'Input file tag not found: "', trim(tagname), &
123  '" in block "', trim(blockname), &
124  '".'
125  call store_error(errmsg)
126  call store_error_filename(filename)
127  end if
128  end function get_param_definition_type
129 
130  !> @brief Return aggregate definition
131  !<
132  function get_aggregate_definition_type(input_definition_types, component_type, &
133  subcomponent_type, blockname) result(idt)
134  type(inputparamdefinitiontype), dimension(:), intent(in), target :: &
135  input_definition_types
136  character(len=*), intent(in) :: component_type !< component type, such as GWF or GWT
137  character(len=*), intent(in) :: subcomponent_type !< subcomponent type, such as DIS or NPF
138  character(len=*), intent(in) :: blockname !< name of the block
139  type(inputparamdefinitiontype), pointer :: idt !< corresponding InputParameterDefinitionType for this block
140  type(inputparamdefinitiontype), pointer :: tmp_ptr
141  integer(I4B) :: i
142  !
143  nullify (idt)
144  do i = 1, size(input_definition_types)
145  tmp_ptr => input_definition_types(i)
146  if (tmp_ptr%component_type == component_type .and. &
147  tmp_ptr%subcomponent_type == subcomponent_type .and. &
148  tmp_ptr%blockname == blockname) then
149  idt => input_definition_types(i)
150  exit
151  end if
152  end do
153  !
154  if (.not. associated(idt)) then
155  write (errmsg, '(a,a,a,a,a,a,a)') &
156  'Idm aggregate definition not found: ', trim(blockname), &
157  '. Component="', trim(component_type), &
158  '", subcomponent="', trim(subcomponent_type), '".'
159  call store_error(errmsg, .true.)
160  end if
161  end function get_aggregate_definition_type
162 
163  !> @brief Return aggregate definition
164  !!
165  !! Split a component RECORD datatype definition whose second element matches
166  !! tagname into an array of character tokens
167  !<
168  subroutine split_record_definition(input_definition_types, component_type, &
169  subcomponent_type, tagname, nwords, words)
170  use inputoutputmodule, only: parseline
171  type(inputparamdefinitiontype), dimension(:), intent(in), target :: &
172  input_definition_types
173  character(len=*), intent(in) :: component_type !< component type, such as GWF or GWT
174  character(len=*), intent(in) :: subcomponent_type !< subcomponent type, such as DIS or NPF
175  character(len=*), intent(in) :: tagname !< name of the input tag
176  integer(I4B), intent(inout) :: nwords
177  character(len=40), dimension(:), allocatable, intent(inout) :: words
178  type(inputparamdefinitiontype), pointer :: tmp_ptr
179  integer(I4B) :: i
180  character(len=:), allocatable :: parse_str
181  !
182  ! -- initialize to deallocated
183  if (allocated(words)) deallocate (words)
184  !
185  ! -- return all tokens of multi-record type that matches the first
186  ! -- tag following the expected first token "RECORD"
187  do i = 1, size(input_definition_types)
188  !
189  ! -- initialize
190  nwords = 0
191  !
192  ! -- set ptr to current definition
193  tmp_ptr => input_definition_types(i)
194  !
195  ! -- match for definition to split
196  if (tmp_ptr%component_type == component_type .and. &
197  tmp_ptr%subcomponent_type == subcomponent_type .and. &
198  idt_datatype(tmp_ptr) == 'RECORD') then
199  !
200  ! -- set split string
201  parse_str = trim(input_definition_types(i)%datatype)//' '
202  !
203  ! -- split
204  call parseline(parse_str, nwords, words)
205  !
206  ! -- check for match and manage memory
207  if (nwords >= 2) then
208  if (words(1) == 'RECORD' .and. words(2) == tagname) then
209  exit
210  end if
211  end if
212  !
213  ! -- deallocate
214  if (allocated(parse_str)) deallocate (parse_str)
215  if (allocated(words)) deallocate (words)
216  !
217  end if
218  end do
219  end subroutine split_record_definition
220 
221 end module definitionselectmodule
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
This module contains the DefinitionSelectModule.
type(inputparamdefinitiontype) function, pointer, public get_param_definition_type(input_definition_types, component_type, subcomponent_type, blockname, tagname, filename)
Return parameter definition.
subroutine, public split_record_definition(input_definition_types, component_type, subcomponent_type, tagname, nwords, words)
Return aggregate definition.
type(inputparamdefinitiontype) function, pointer, public get_aggregate_definition_type(input_definition_types, component_type, subcomponent_type, blockname)
Return aggregate definition.
subroutine, public idt_parse_rectype(idt, cols, ncol)
allocate and set RECARRAY, KEYSTRING or RECORD param list
character(len=linelength) function, public idt_datatype(idt)
return input definition type datatype
This module contains the InputDefinitionModule.
subroutine, public parseline(line, nwords, words, inunit, filename)
Parse a line into words.
This module defines variable data types.
Definition: kind.f90:8
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
subroutine, public store_error_filename(filename, terminate)
Store the erroring file name.
Definition: Sim.f90:203
This module contains simulation variables.
Definition: SimVariables.f90:9
character(len=maxcharlen) errmsg
error message string