MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
DynamicPackageParams.f90
Go to the documentation of this file.
1 !> @brief This module contains the DynamicPackageParamsModule
2 !!
3 !!
4 !<
6 
7  use kindmodule, only: dp, i4b, lgp
9  use simvariablesmodule, only: errmsg
19 
20  implicit none
21  private
22  public :: dynamicpackageparamstype
23  public :: allocate_param_charstr
26 
27  !> @brief dynamic parameter filter type
28  !!
29  !!
30  !<
32  character(len=LINELENGTH), dimension(:), allocatable :: params !< in scope param tags
33  character(len=LINELENGTH) :: blockname !< name of block
34  integer(I4B) :: iauxiliary !< package auxiliary active, 0=inactive, active for values > 0
35  integer(I4B) :: inamedbound !< package inamedbound setting
36  integer(I4B) :: nparam !< number of in scope params
37  type(modflowinputtype) :: mf6_input !< description of input
38  contains
39  procedure :: init
40  procedure :: destroy
41  procedure :: set_filtered_list
42  procedure :: set_filtered_grid
43  procedure :: package_params
45 
46 contains
47 
48  !> @brief initialize dynamic param filter
49  !!
50  !<
51  subroutine init(this, mf6_input, blockname, readasarrays, iauxiliary, &
52  inamedbound)
53  class(dynamicpackageparamstype) :: this
54  type(modflowinputtype), intent(in) :: mf6_input
55  character(len=*) :: blockname
56  logical(LGP), intent(in) :: readasarrays
57  integer(I4B), intent(in) :: iauxiliary
58  integer(I4B), intent(in) :: inamedbound
59 
60  this%mf6_input = mf6_input
61  this%blockname = blockname
62  this%nparam = 0
63  this%iauxiliary = iauxiliary
64  this%inamedbound = inamedbound
65 
66  ! determine in scope input params
67  if (readasarrays) then
68  call this%set_filtered_grid()
69  else
70  call this%set_filtered_list()
71  end if
72  end subroutine init
73 
74  !> @brief destroy
75  !!
76  !<
77  subroutine destroy(this)
78  class(dynamicpackageparamstype) :: this
79  if (allocated(this%params)) deallocate (this%params)
80  end subroutine destroy
81 
82  !> @brief array based input dynamic param filter
83  !!
84  !<
85  subroutine set_filtered_grid(this)
86  class(dynamicpackageparamstype) :: this
87  type(inputparamdefinitiontype), pointer :: idt
88  integer(I4B), dimension(:), allocatable :: idt_idxs
89  type(characterstringtype), dimension(:), pointer, contiguous :: boundname
90  real(DP), dimension(:, :), pointer, contiguous :: auxvar
91  integer(I4B) :: keepcnt, iparam
92  logical(LGP) :: keep
93 
94  ! initialize
95  keepcnt = 0
96 
97  ! allocate dfn input params
98  do iparam = 1, size(this%mf6_input%param_dfns)
99  keep = .true.
100 
101  ! assign param definition pointer
102  idt => this%mf6_input%param_dfns(iparam)
103 
104  if (idt%blockname /= this%blockname) then
105  keep = .false.
106  end if
107 
108  if (idt%tagname == 'AUX') then
109  if (this%iauxiliary == 0) then
110  keep = .false.
111  call mem_allocate(auxvar, 0, 0, 'AUXVAR', this%mf6_input%mempath)
112  end if
113  if (this%inamedbound == 0) then
114  call mem_allocate(boundname, lenboundname, 0, 'BOUNDNAME', &
115  this%mf6_input%mempath)
116  end if
117  end if
118 
119  if (keep) then
120  keepcnt = keepcnt + 1
121  call expandarray(idt_idxs)
122  idt_idxs(keepcnt) = iparam
123  end if
124  end do
125 
126  ! update nparam
127  this%nparam = keepcnt
128 
129  ! allocate filtcols
130  allocate (this%params(this%nparam))
131 
132  ! set filtcols
133  do iparam = 1, this%nparam
134  idt => this%mf6_input%param_dfns(idt_idxs(iparam))
135  this%params(iparam) = trim(idt%tagname)
136  end do
137 
138  ! cleanup
139  deallocate (idt_idxs)
140  end subroutine set_filtered_grid
141 
142  !> @brief create array of in scope list input columns
143  !!
144  !! Filter the recarray description of list input parameters
145  !! to determine which columns are to be read in this run.
146  !<
147  subroutine set_filtered_list(this)
148  class(dynamicpackageparamstype) :: this
149  type(inputparamdefinitiontype), pointer :: ra_idt, idt
150  character(len=LINELENGTH), dimension(:), allocatable :: ra_cols
151  type(characterstringtype), dimension(:), pointer, contiguous :: boundname
152  real(DP), dimension(:, :), pointer, contiguous :: auxvar
153  integer(I4B) :: ra_ncol, icol, keepcnt
154  logical(LGP) :: keep
155 
156  ! initialize
157  keepcnt = 0
158 
159  ! get aggregate param definition for period block
160  ra_idt => &
161  get_aggregate_definition_type(this%mf6_input%aggregate_dfns, &
162  this%mf6_input%component_type, &
163  this%mf6_input%subcomponent_type, &
164  this%blockname)
165  ! split recarray definition
166  call idt_parse_rectype(ra_idt, ra_cols, ra_ncol)
167 
168  ! determine which columns are in scope
169  do icol = 1, ra_ncol
170  keep = .false.
171 
172  ! set dfn pointer to recarray parameter
173  idt => get_param_definition_type(this%mf6_input%param_dfns, &
174  this%mf6_input%component_type, &
175  this%mf6_input%subcomponent_type, &
176  this%blockname, ra_cols(icol), '')
177  if (ra_cols(icol) == 'RECARRAY') then
178  ! no-op
179  else if (ra_cols(icol) == 'AUX') then
180  if (this%iauxiliary > 0) then
181  keep = .true.
182  else
183  call mem_allocate(auxvar, 0, 0, 'AUXVAR', this%mf6_input%mempath)
184  end if
185  else if (ra_cols(icol) == 'BOUNDNAME') then
186  if (this%inamedbound /= 0) then
187  keep = .true.
188  else
189  call mem_allocate(boundname, lenboundname, 0, 'BOUNDNAME', &
190  this%mf6_input%mempath)
191  end if
192  else
193  ! determine if the param is scope
194  keep = pkg_param_in_scope(this%mf6_input, this%blockname, ra_cols(icol))
195  end if
196 
197  if (keep) then
198  keepcnt = keepcnt + 1
199  call expandarray(this%params)
200  this%params(keepcnt) = trim(ra_cols(icol))
201  end if
202  end do
203 
204  ! update nparam
205  this%nparam = keepcnt
206 
207  ! cleanup
208  deallocate (ra_cols)
209  end subroutine set_filtered_list
210 
211  !> @brief allocate and set input array to filtered param set
212  !!
213  !<
214  subroutine package_params(this, params, nparam)
215  class(dynamicpackageparamstype) :: this
216  character(len=LINELENGTH), dimension(:), allocatable, &
217  intent(inout) :: params
218  integer(I4B), intent(inout) :: nparam
219  integer(I4B) :: n
220  if (allocated(params)) deallocate (params)
221  nparam = this%nparam
222  allocate (params(nparam))
223  do n = 1, nparam
224  params(n) = this%params(n)
225  end do
226  end subroutine package_params
227 
228  !> @brief allocate character string type array
229  !<
230  subroutine allocate_param_charstr(strlen, nrow, varname, mempath)
231  integer(I4B), intent(in) :: strlen !< string number of characters
232  integer(I4B), intent(in) :: nrow !< integer array number of rows
233  character(len=*), intent(in) :: varname !< variable name
234  character(len=*), intent(in) :: mempath !< variable mempath
235  type(characterstringtype), dimension(:), pointer, &
236  contiguous :: charstr1d
237  integer(I4B) :: n
238  call mem_allocate(charstr1d, strlen, nrow, varname, mempath)
239  do n = 1, nrow
240  charstr1d(n) = ''
241  end do
242  end subroutine allocate_param_charstr
243 
244  !> @brief allocate int1d
245  !<
246  subroutine allocate_param_int1d(nrow, varname, mempath)
247  integer(I4B), intent(in) :: nrow !< integer array number of rows
248  character(len=*), intent(in) :: varname !< variable name
249  character(len=*), intent(in) :: mempath !< variable mempath
250  integer(I4B), dimension(:), pointer, contiguous :: int1d
251  integer(I4B) :: n
252  call mem_allocate(int1d, nrow, varname, mempath)
253  do n = 1, nrow
254  int1d(n) = izero
255  end do
256  end subroutine allocate_param_int1d
257 
258  !> @brief allocate int2d
259  !<
260  subroutine allocate_param_int2d(ncol, nrow, varname, mempath)
261  integer(I4B), intent(in) :: ncol !< integer array number of cols
262  integer(I4B), intent(in) :: nrow !< integer array number of rows
263  character(len=*), intent(in) :: varname !< variable name
264  character(len=*), intent(in) :: mempath !< variable mempath
265  integer(I4B), dimension(:, :), pointer, contiguous :: int2d
266  integer(I4B) :: n, m
267  call mem_allocate(int2d, ncol, nrow, varname, mempath)
268  do m = 1, nrow
269  do n = 1, ncol
270  int2d(n, m) = izero
271  end do
272  end do
273  end subroutine allocate_param_int2d
274 
275  !> @brief allocate dbl1d
276  !<
277  subroutine allocate_param_dbl1d(nrow, varname, mempath)
278  integer(I4B), intent(in) :: nrow !< integer array number of rows
279  character(len=*), intent(in) :: varname !< variable name
280  character(len=*), intent(in) :: mempath !< variable mempath
281  real(dp), dimension(:), pointer, contiguous :: dbl1d
282  integer(I4B) :: n
283  call mem_allocate(dbl1d, nrow, varname, mempath)
284  do n = 1, nrow
285  dbl1d(n) = dzero
286  end do
287  end subroutine allocate_param_dbl1d
288 
289  !> @brief allocate dbl2d
290  !<
291  subroutine allocate_param_dbl2d(ncol, nrow, varname, mempath)
292  integer(I4B), intent(in) :: ncol !< integer array number of cols
293  integer(I4B), intent(in) :: nrow !< integer array number of rows
294  character(len=*), intent(in) :: varname !< variable name
295  character(len=*), intent(in) :: mempath !< variable mempath
296  real(dp), dimension(:, :), pointer, contiguous :: dbl2d
297  integer(I4B) :: n, m
298  call mem_allocate(dbl2d, ncol, nrow, varname, mempath)
299  do m = 1, nrow
300  do n = 1, ncol
301  dbl2d(n, m) = dzero
302  end do
303  end do
304  end subroutine allocate_param_dbl2d
305 
306  !> @brief determine if input param is in scope for a package
307  !!
308  !<
309  function pkg_param_in_scope(mf6_input, blockname, tagname) result(in_scope)
311  type(modflowinputtype), intent(in) :: mf6_input
312  character(len=*), intent(in) :: blockname
313  character(len=*), intent(in) :: tagname
314  logical(LGP) :: in_scope
315  type(inputparamdefinitiontype), pointer :: idt
316  integer(I4B) :: pdim_isize, popt_isize
317  integer(I4B), pointer :: pdim
318 
319  ! initialize
320  in_scope = .false.
321 
322  idt => get_param_definition_type(mf6_input%param_dfns, &
323  mf6_input%component_type, &
324  mf6_input%subcomponent_type, &
325  blockname, tagname, '')
326  if (idt%required) then
327  ! required params always included
328  in_scope = .true.
329  else
330  ! package specific logic to determine if input params to be read
331  select case (mf6_input%subcomponent_type)
332  case ('EVT')
333  if (tagname == 'PXDP' .or. tagname == 'PETM') then
334  call get_isize('NSEG', mf6_input%mempath, pdim_isize)
335  if (pdim_isize > 0) then
336  call mem_setptr(pdim, 'NSEG', mf6_input%mempath)
337  if (pdim > 1) then
338  in_scope = .true.
339  end if
340  end if
341  else if (tagname == 'PETM0') then
342  call get_isize('SURFRATESPEC', mf6_input%mempath, popt_isize)
343  if (popt_isize > 0) then
344  in_scope = .true.
345  end if
346  end if
347  case ('NAM')
348  in_scope = .true.
349  case default
350  errmsg = 'IDM unimplemented. DynamicPackageParamsType::pkg_param_in_scope &
351  &add case tagname='//trim(idt%tagname)
352  call store_error(errmsg, .true.)
353  !call store_error_filename(sourcename)
354  end select
355  end if
356  end function pkg_param_in_scope
357 
subroutine init()
Definition: GridSorting.f90:24
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
integer(i4b), parameter lenboundname
maximum length of a bound name
Definition: Constants.f90:36
integer(i4b), parameter izero
integer constant zero
Definition: Constants.f90:51
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
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.
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
This module contains the DynamicPackageParamsModule.
subroutine set_filtered_list(this)
create array of in scope list input columns
subroutine, public allocate_param_int2d(ncol, nrow, varname, mempath)
allocate int2d
subroutine, public allocate_param_int1d(nrow, varname, mempath)
allocate int1d
subroutine set_filtered_grid(this)
array based input dynamic param filter
subroutine destroy(this)
destroy
subroutine package_params(this, params, nparam)
allocate and set input array to filtered param set
logical(lgp) function pkg_param_in_scope(mf6_input, blockname, tagname)
determine if input param is in scope for a package
subroutine, public allocate_param_dbl1d(nrow, varname, mempath)
allocate dbl1d
subroutine, public allocate_param_charstr(strlen, nrow, varname, mempath)
allocate character string type array
subroutine, public allocate_param_dbl2d(ncol, nrow, varname, mempath)
allocate dbl2d
This module contains the InputDefinitionModule.
This module defines variable data types.
Definition: kind.f90:8
subroutine, public get_isize(name, mem_path, isize)
@ brief Get the number of elements for this variable
This module contains the ModflowInputModule.
Definition: ModflowInput.f90:9
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
This class is used to store a single deferred-length character string. It was designed to work in an ...
Definition: CharString.f90:23
derived type for storing input definition for a file