MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
definitionselectmodule Module Reference

This module contains the DefinitionSelectModule. More...

Functions/Subroutines

subroutine, public idt_parse_rectype (idt, cols, ncol)
 allocate and set RECARRAY, KEYSTRING or RECORD param list More...
 
character(len=linelength) function, public idt_datatype (idt)
 return input definition type datatype More...
 
type(inputparamdefinitiontype) function, pointer, public get_param_definition_type (input_definition_types, component_type, subcomponent_type, blockname, tagname, filename)
 Return parameter definition. More...
 
type(inputparamdefinitiontype) function, pointer, public get_aggregate_definition_type (input_definition_types, component_type, subcomponent_type, blockname)
 Return aggregate definition. More...
 
subroutine, public split_record_definition (input_definition_types, component_type, subcomponent_type, tagname, nwords, words)
 Return aggregate definition. More...
 

Detailed Description

This module contains the routines for getting parameter definitions, aggregate definitions, and block definitions for the different package types.

Function/Subroutine Documentation

◆ get_aggregate_definition_type()

type(inputparamdefinitiontype) function, pointer, public definitionselectmodule::get_aggregate_definition_type ( type(inputparamdefinitiontype), dimension(:), intent(in), target  input_definition_types,
character(len=*), intent(in)  component_type,
character(len=*), intent(in)  subcomponent_type,
character(len=*), intent(in)  blockname 
)
Parameters
[in]component_typecomponent type, such as GWF or GWT
[in]subcomponent_typesubcomponent type, such as DIS or NPF
[in]blocknamename of the block
Returns
corresponding InputParameterDefinitionType for this block

Definition at line 132 of file DefinitionSelect.f90.

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
Here is the call graph for this function:
Here is the caller graph for this function:

◆ get_param_definition_type()

type(inputparamdefinitiontype) function, pointer, public definitionselectmodule::get_param_definition_type ( type(inputparamdefinitiontype), dimension(:), intent(in), target  input_definition_types,
character(len=*), intent(in)  component_type,
character(len=*), intent(in)  subcomponent_type,
character(len=*), intent(in)  blockname,
character(len=*), intent(in)  tagname,
character(len=*), intent(in)  filename 
)
Parameters
[in]component_typecomponent type, such as GWF or GWT
[in]subcomponent_typesubcomponent type, such as DIS or NPF
[in]blocknamename of the block
[in]tagnamename of the input tag
[in]filenameinput filename
Returns
corresponding InputParameterDefinitionType for this tag

Definition at line 93 of file DefinitionSelect.f90.

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
Here is the call graph for this function:
Here is the caller graph for this function:

◆ idt_datatype()

character(len=linelength) function, public definitionselectmodule::idt_datatype ( type(inputparamdefinitiontype), intent(in), pointer  idt)

Definition at line 72 of file DefinitionSelect.f90.

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
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
Here is the caller graph for this function:

◆ idt_parse_rectype()

subroutine, public definitionselectmodule::idt_parse_rectype ( type(inputparamdefinitiontype), intent(in), pointer  idt,
character(len=linelength), dimension(:), intent(inout), allocatable  cols,
integer(i4b), intent(inout)  ncol 
)

Definition at line 28 of file DefinitionSelect.f90.

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)
subroutine, public parseline(line, nwords, words, inunit, filename)
Parse a line into words.
Here is the call graph for this function:
Here is the caller graph for this function:

◆ split_record_definition()

subroutine, public definitionselectmodule::split_record_definition ( type(inputparamdefinitiontype), dimension(:), intent(in), target  input_definition_types,
character(len=*), intent(in)  component_type,
character(len=*), intent(in)  subcomponent_type,
character(len=*), intent(in)  tagname,
integer(i4b), intent(inout)  nwords,
character(len=40), dimension(:), intent(inout), allocatable  words 
)

Split a component RECORD datatype definition whose second element matches tagname into an array of character tokens

Parameters
[in]component_typecomponent type, such as GWF or GWT
[in]subcomponent_typesubcomponent type, such as DIS or NPF
[in]tagnamename of the input tag

Definition at line 168 of file DefinitionSelect.f90.

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
Here is the call graph for this function:
Here is the caller graph for this function: