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  use constantsmodule, only: linelength
30  use inputoutputmodule, only: parseline
31  type(inputparamdefinitiontype), pointer, intent(in) :: idt
32  character(len=LINELENGTH), dimension(:), allocatable, &
33  intent(inout) :: cols
34  integer(I4B), intent(inout) :: ncol
35  character(len=:), allocatable :: parse_str
36  character(len=LINELENGTH), dimension(:), allocatable :: param_cols
37  integer(I4B) :: param_ncol, n
38 
39  ! initialize
40  if (allocated(cols)) deallocate (cols)
41  ncol = 0
42 
43  ! split definition
44  parse_str = trim(idt%datatype)//' '
45  call parseline(parse_str, param_ncol, param_cols)
46 
47  if (param_ncol > 1) then
48  if (param_cols(1) == 'RECARRAY' .or. &
49  param_cols(1) == 'KEYSTRING' .or. &
50  param_cols(1) == 'RECORD') then
51  ! exclude 1st column
52  allocate (cols(param_ncol - 1))
53  do n = 2, param_ncol
54  cols(n - 1) = param_cols(n)
55  end do
56  ! set ncol
57  ncol = param_ncol - 1
58  end if
59  end if
60 
61  ! cleanup
62  if (allocated(param_cols)) deallocate (param_cols)
63  if (allocated(parse_str)) deallocate (parse_str)
64  end subroutine idt_parse_rectype
65 
66  !> @brief return input definition type datatype
67  !<
68  function idt_datatype(idt) result(datatype)
69  use constantsmodule, only: linelength
70  type(inputparamdefinitiontype), pointer, intent(in) :: idt
71  character(len=LINELENGTH) :: datatype
72  if (idt%datatype(1:9) == 'KEYSTRING') then
73  datatype = 'KEYSTRING'
74  else if (idt%datatype(1:8) == 'RECARRAY') then
75  datatype = 'RECARRAY'
76  else if (idt%datatype(1:6) == 'RECORD') then
77  datatype = 'RECORD'
78  else
79  datatype = idt%datatype
80  end if
81  end function idt_datatype
82 
83  !> @brief Return parameter definition
84  !<
85  function get_param_definition_type(input_definition_types, &
86  component_type, subcomponent_type, &
87  blockname, tagname, filename) &
88  result(idt)
89  type(inputparamdefinitiontype), dimension(:), intent(in), target :: &
90  input_definition_types
91  character(len=*), intent(in) :: component_type !< component type, such as GWF or GWT
92  character(len=*), intent(in) :: subcomponent_type !< subcomponent type, such as DIS or NPF
93  character(len=*), intent(in) :: blockname !< name of the block
94  character(len=*), intent(in) :: tagname !< name of the input tag
95  character(len=*), intent(in) :: filename !< input filename
96  type(inputparamdefinitiontype), pointer :: idt !< corresponding InputParameterDefinitionType for this tag
97  type(inputparamdefinitiontype), pointer :: tmp_ptr
98  integer(I4B) :: i
99 
100  nullify (idt)
101  do i = 1, size(input_definition_types)
102  tmp_ptr => input_definition_types(i)
103  if (tmp_ptr%component_type == component_type .and. &
104  tmp_ptr%subcomponent_type == subcomponent_type .and. &
105  tmp_ptr%blockname == blockname .and. &
106  tmp_ptr%tagname == tagname) then
107  idt => input_definition_types(i)
108  exit
109  end if
110  end do
111 
112  if (.not. associated(idt)) then
113  write (errmsg, '(a,a,a,a,a)') &
114  'Input file tag not found: "', trim(tagname), &
115  '" in block "', trim(blockname), &
116  '".'
117  call store_error(errmsg)
118  call store_error_filename(filename)
119  end if
120  end function get_param_definition_type
121 
122  !> @brief Return aggregate definition
123  !<
124  function get_aggregate_definition_type(input_definition_types, component_type, &
125  subcomponent_type, blockname) result(idt)
126  type(inputparamdefinitiontype), dimension(:), intent(in), target :: &
127  input_definition_types
128  character(len=*), intent(in) :: component_type !< component type, such as GWF or GWT
129  character(len=*), intent(in) :: subcomponent_type !< subcomponent type, such as DIS or NPF
130  character(len=*), intent(in) :: blockname !< name of the block
131  type(inputparamdefinitiontype), pointer :: idt !< corresponding InputParameterDefinitionType for this block
132  type(inputparamdefinitiontype), pointer :: tmp_ptr
133  integer(I4B) :: i
134 
135  nullify (idt)
136  do i = 1, size(input_definition_types)
137  tmp_ptr => input_definition_types(i)
138  if (tmp_ptr%component_type == component_type .and. &
139  tmp_ptr%subcomponent_type == subcomponent_type .and. &
140  tmp_ptr%blockname == blockname) then
141  idt => input_definition_types(i)
142  exit
143  end if
144  end do
145 
146  if (.not. associated(idt)) then
147  write (errmsg, '(a,a,a,a,a,a,a)') &
148  'Idm aggregate definition not found: ', trim(blockname), &
149  '. Component="', trim(component_type), &
150  '", subcomponent="', trim(subcomponent_type), '".'
151  call store_error(errmsg, .true.)
152  end if
153  end function get_aggregate_definition_type
154 
155  !> @brief Return aggregate definition
156  !!
157  !! Split a component RECORD datatype definition whose second element matches
158  !! tagname into an array of character tokens
159  !<
160  subroutine split_record_definition(input_definition_types, component_type, &
161  subcomponent_type, tagname, nwords, words)
162  use inputoutputmodule, only: parseline
163  type(inputparamdefinitiontype), dimension(:), intent(in), target :: &
164  input_definition_types
165  character(len=*), intent(in) :: component_type !< component type, such as GWF or GWT
166  character(len=*), intent(in) :: subcomponent_type !< subcomponent type, such as DIS or NPF
167  character(len=*), intent(in) :: tagname !< name of the input tag
168  integer(I4B), intent(inout) :: nwords
169  character(len=40), dimension(:), allocatable, intent(inout) :: words
170  type(inputparamdefinitiontype), pointer :: tmp_ptr
171  integer(I4B) :: i
172  character(len=:), allocatable :: parse_str
173 
174  ! initialize to deallocated
175  if (allocated(words)) deallocate (words)
176 
177  ! return all tokens of multi-record type that matches the first
178  ! tag following the expected first token "RECORD"
179  do i = 1, size(input_definition_types)
180 
181  ! initialize
182  nwords = 0
183 
184  ! set ptr to current definition
185  tmp_ptr => input_definition_types(i)
186 
187  ! match for definition to split
188  if (tmp_ptr%component_type == component_type .and. &
189  tmp_ptr%subcomponent_type == subcomponent_type .and. &
190  idt_datatype(tmp_ptr) == 'RECORD') then
191 
192  ! set split string
193  parse_str = trim(input_definition_types(i)%datatype)//' '
194 
195  ! split
196  call parseline(parse_str, nwords, words)
197 
198  ! check for match and manage memory
199  if (nwords >= 2) then
200  if (words(1) == 'RECORD' .and. words(2) == tagname) then
201  exit
202  end if
203  end if
204 
205  ! deallocate
206  if (allocated(parse_str)) deallocate (parse_str)
207  if (allocated(words)) deallocate (words)
208  end if
209  end do
210  end subroutine split_record_definition
211 
212 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