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  ! -- modules
54  ! -- dummy
55  class(dynamicpackageparamstype) :: this
56  type(modflowinputtype), intent(in) :: mf6_input
57  character(len=*) :: blockname
58  logical(LGP), intent(in) :: readasarrays
59  integer(I4B), intent(in) :: iauxiliary
60  integer(I4B), intent(in) :: inamedbound
61  !integer(I4B) :: iparam
62  ! -- local
63  !
64  this%mf6_input = mf6_input
65  this%blockname = blockname
66  this%nparam = 0
67  this%iauxiliary = iauxiliary
68  this%inamedbound = inamedbound
69  !
70  ! -- determine in scope input params
71  if (readasarrays) then
72  call this%set_filtered_grid()
73  else
74  call this%set_filtered_list()
75  end if
76  end subroutine init
77 
78  !> @brief destroy
79  !!
80  !<
81  subroutine destroy(this)
82  ! -- modules
83  ! -- dummy
84  class(dynamicpackageparamstype) :: this
85  !
86  ! -- deallocate
87  if (allocated(this%params)) deallocate (this%params)
88  end subroutine destroy
89 
90  !> @brief array based input dynamic param filter
91  !!
92  !<
93  subroutine set_filtered_grid(this)
94  ! -- modules
95  ! -- dummy
96  class(dynamicpackageparamstype) :: this
97  ! -- local
98  type(inputparamdefinitiontype), pointer :: idt
99  integer(I4B), dimension(:), allocatable :: idt_idxs
100  type(characterstringtype), dimension(:), pointer, contiguous :: boundname
101  real(DP), dimension(:, :), pointer, contiguous :: auxvar
102  integer(I4B) :: keepcnt, iparam
103  logical(LGP) :: keep
104  !
105  ! -- initialize
106  keepcnt = 0
107  !
108  ! -- allocate dfn input params
109  do iparam = 1, size(this%mf6_input%param_dfns)
110  !
111  keep = .true.
112  !
113  ! -- assign param definition pointer
114  idt => this%mf6_input%param_dfns(iparam)
115  !
116  if (idt%blockname /= this%blockname) then
117  keep = .false.
118  end if
119  !
120  if (idt%tagname == 'AUX') then
121  if (this%iauxiliary == 0) then
122  keep = .false.
123  call mem_allocate(auxvar, 0, 0, 'AUXVAR', this%mf6_input%mempath)
124  end if
125  if (this%inamedbound == 0) then
126  call mem_allocate(boundname, lenboundname, 0, 'BOUNDNAME', &
127  this%mf6_input%mempath)
128  end if
129  end if
130  !
131  if (keep) then
132  keepcnt = keepcnt + 1
133  call expandarray(idt_idxs)
134  idt_idxs(keepcnt) = iparam
135  end if
136  end do
137  !
138  ! -- update nparam
139  this%nparam = keepcnt
140  !
141  ! -- allocate filtcols
142  allocate (this%params(this%nparam))
143  !
144  ! -- set filtcols
145  do iparam = 1, this%nparam
146  idt => this%mf6_input%param_dfns(idt_idxs(iparam))
147  this%params(iparam) = trim(idt%tagname)
148  end do
149  !
150  ! -- cleanup
151  deallocate (idt_idxs)
152  end subroutine set_filtered_grid
153 
154  !> @brief create array of in scope list input columns
155  !!
156  !! Filter the recarray description of list input parameters
157  !! to determine which columns are to be read in this run.
158  !<
159  subroutine set_filtered_list(this)
160  ! -- modules
161  ! -- dummy
162  class(dynamicpackageparamstype) :: this
163  ! -- local
164  type(inputparamdefinitiontype), pointer :: ra_idt, idt
165  character(len=LINELENGTH), dimension(:), allocatable :: ra_cols
166  type(characterstringtype), dimension(:), pointer, contiguous :: boundname
167  real(DP), dimension(:, :), pointer, contiguous :: auxvar
168  integer(I4B) :: ra_ncol, icol, keepcnt
169  logical(LGP) :: keep
170  !
171  ! -- initialize
172  keepcnt = 0
173  !
174  ! -- get aggregate param definition for period block
175  ra_idt => &
176  get_aggregate_definition_type(this%mf6_input%aggregate_dfns, &
177  this%mf6_input%component_type, &
178  this%mf6_input%subcomponent_type, &
179  this%blockname)
180  !
181  ! -- split recarray definition
182  call idt_parse_rectype(ra_idt, ra_cols, ra_ncol)
183  !
184  ! -- determine which columns are in scope
185  do icol = 1, ra_ncol
186  !
187  keep = .false.
188  !
189  ! -- set dfn pointer to recarray parameter
190  idt => get_param_definition_type(this%mf6_input%param_dfns, &
191  this%mf6_input%component_type, &
192  this%mf6_input%subcomponent_type, &
193  this%blockname, ra_cols(icol), '')
194  !
195  if (ra_cols(icol) == 'RECARRAY') then
196  ! no-op
197  else if (ra_cols(icol) == 'AUX') then
198  if (this%iauxiliary > 0) then
199  keep = .true.
200  else
201  call mem_allocate(auxvar, 0, 0, 'AUXVAR', this%mf6_input%mempath)
202  end if
203  else if (ra_cols(icol) == 'BOUNDNAME') then
204  if (this%inamedbound /= 0) then
205  keep = .true.
206  else
207  call mem_allocate(boundname, lenboundname, 0, 'BOUNDNAME', &
208  this%mf6_input%mempath)
209  end if
210  else
211  ! -- determine if the param is scope
212  keep = pkg_param_in_scope(this%mf6_input, this%blockname, ra_cols(icol))
213  end if
214  !
215  if (keep) then
216  keepcnt = keepcnt + 1
217  call expandarray(this%params)
218  this%params(keepcnt) = trim(ra_cols(icol))
219  end if
220  end do
221  !
222  ! -- update nparam
223  this%nparam = keepcnt
224  !
225  ! -- cleanup
226  deallocate (ra_cols)
227  end subroutine set_filtered_list
228 
229  !> @brief allocate and set input array to filtered param set
230  !!
231  !<
232  subroutine package_params(this, params, nparam)
233  ! -- modules
234  ! -- dummy
235  class(dynamicpackageparamstype) :: this
236  character(len=LINELENGTH), dimension(:), allocatable, &
237  intent(inout) :: params
238  integer(I4B), intent(inout) :: nparam
239  integer(I4B) :: n
240  !
241  if (allocated(params)) deallocate (params)
242  !
243  nparam = this%nparam
244  !
245  allocate (params(nparam))
246  !
247  do n = 1, nparam
248  params(n) = this%params(n)
249  end do
250  end subroutine package_params
251 
252  !> @brief allocate character string type array
253  !<
254  subroutine allocate_param_charstr(strlen, nrow, varname, mempath)
255  integer(I4B), intent(in) :: strlen !< string number of characters
256  integer(I4B), intent(in) :: nrow !< integer array number of rows
257  character(len=*), intent(in) :: varname !< variable name
258  character(len=*), intent(in) :: mempath !< variable mempath
259  type(characterstringtype), dimension(:), pointer, &
260  contiguous :: charstr1d
261  integer(I4B) :: n
262  !
263  call mem_allocate(charstr1d, strlen, nrow, varname, mempath)
264  do n = 1, nrow
265  charstr1d(n) = ''
266  end do
267  end subroutine allocate_param_charstr
268 
269  !> @brief allocate int1d
270  !<
271  subroutine allocate_param_int1d(nrow, varname, mempath)
272  integer(I4B), intent(in) :: nrow !< integer array number of rows
273  character(len=*), intent(in) :: varname !< variable name
274  character(len=*), intent(in) :: mempath !< variable mempath
275  integer(I4B), dimension(:), pointer, contiguous :: int1d
276  integer(I4B) :: n
277  !
278  call mem_allocate(int1d, nrow, varname, mempath)
279  do n = 1, nrow
280  int1d(n) = izero
281  end do
282  end subroutine allocate_param_int1d
283 
284  !> @brief allocate int2d
285  !<
286  subroutine allocate_param_int2d(ncol, nrow, varname, mempath)
287  integer(I4B), intent(in) :: ncol !< integer array number of cols
288  integer(I4B), intent(in) :: nrow !< integer array number of rows
289  character(len=*), intent(in) :: varname !< variable name
290  character(len=*), intent(in) :: mempath !< variable mempath
291  integer(I4B), dimension(:, :), pointer, contiguous :: int2d
292  integer(I4B) :: n, m
293  !
294  call mem_allocate(int2d, ncol, nrow, varname, mempath)
295  do m = 1, nrow
296  do n = 1, ncol
297  int2d(n, m) = izero
298  end do
299  end do
300  end subroutine allocate_param_int2d
301 
302  !> @brief allocate dbl1d
303  !<
304  subroutine allocate_param_dbl1d(nrow, varname, mempath)
305  integer(I4B), intent(in) :: nrow !< integer array number of rows
306  character(len=*), intent(in) :: varname !< variable name
307  character(len=*), intent(in) :: mempath !< variable mempath
308  real(dp), dimension(:), pointer, contiguous :: dbl1d
309  integer(I4B) :: n
310  !
311  call mem_allocate(dbl1d, nrow, varname, mempath)
312  do n = 1, nrow
313  dbl1d(n) = dzero
314  end do
315  end subroutine allocate_param_dbl1d
316 
317  !> @brief allocate dbl2d
318  !<
319  subroutine allocate_param_dbl2d(ncol, nrow, varname, mempath)
320  integer(I4B), intent(in) :: ncol !< integer array number of cols
321  integer(I4B), intent(in) :: nrow !< integer array number of rows
322  character(len=*), intent(in) :: varname !< variable name
323  character(len=*), intent(in) :: mempath !< variable mempath
324  real(dp), dimension(:, :), pointer, contiguous :: dbl2d
325  integer(I4B) :: n, m
326  !
327  call mem_allocate(dbl2d, ncol, nrow, varname, mempath)
328  do m = 1, nrow
329  do n = 1, ncol
330  dbl2d(n, m) = dzero
331  end do
332  end do
333  end subroutine allocate_param_dbl2d
334 
335  !> @brief determine if input param is in scope for a package
336  !!
337  !<
338  function pkg_param_in_scope(mf6_input, blockname, tagname) result(in_scope)
339  ! -- modules
341  ! -- dummy
342  type(modflowinputtype), intent(in) :: mf6_input
343  character(len=*), intent(in) :: blockname
344  character(len=*), intent(in) :: tagname
345  ! -- return
346  logical(LGP) :: in_scope
347  ! -- local
348  type(inputparamdefinitiontype), pointer :: idt
349  integer(I4B) :: pdim_isize, popt_isize
350  integer(I4B), pointer :: pdim
351  !
352  ! -- initialize
353  in_scope = .false.
354  !
355  idt => get_param_definition_type(mf6_input%param_dfns, &
356  mf6_input%component_type, &
357  mf6_input%subcomponent_type, &
358  blockname, tagname, '')
359  !
360  if (idt%required) then
361  ! -- required params always included
362  in_scope = .true.
363  else
364  !
365  ! -- package specific logic to determine if input params to be read
366  select case (mf6_input%subcomponent_type)
367  case ('EVT')
368  !
369  if (tagname == 'PXDP' .or. tagname == 'PETM') then
370  call get_isize('NSEG', mf6_input%mempath, pdim_isize)
371  if (pdim_isize > 0) then
372  call mem_setptr(pdim, 'NSEG', mf6_input%mempath)
373  if (pdim > 1) then
374  in_scope = .true.
375  end if
376  end if
377  else if (tagname == 'PETM0') then
378  call get_isize('SURFRATESPEC', mf6_input%mempath, popt_isize)
379  if (popt_isize > 0) then
380  in_scope = .true.
381  end if
382  end if
383  !
384  case ('NAM')
385  in_scope = .true.
386  case default
387  errmsg = 'IDM unimplemented. DynamicPackageParamsType::pkg_param_in_scope &
388  &add case tagname='//trim(idt%tagname)
389  call store_error(errmsg, .true.)
390  !call store_error_filename(sourcename)
391  end select
392  end if
393  end function pkg_param_in_scope
394 
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