MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
ModelPackageInputs.f90
Go to the documentation of this file.
1 !> @brief This module contains the ModelPackageInputsModule
2 !!
3 !! This module contains the high-level routines for assembling
4 !! model package information and loading to the input context
5 !!
6 !<
8 
9  use kindmodule, only: dp, i4b, lgp
10  use simvariablesmodule, only: errmsg
14  use simvariablesmodule, only: iout
17 
18  implicit none
19  private
20  public :: modelpackageinputstype
21 
22  !> @brief derived type for loadable package type
23  !!
24  !! This derived type is used to store package instance
25  !! descriptions for a supported package type.
26  !!
27  !<
29  ! -- package type, e.g. 'DIS6' or 'CHD6'
30  character(len=LENPACKAGETYPE) :: pkgtype
31  ! -- component type, e.g. 'DIS' or 'CHD'
32  character(len=LENCOMPONENTNAME) :: subcomponent_type
33  ! -- package instance attribute arrays
34  character(len=LINELENGTH), dimension(:), allocatable :: filenames
35  character(len=LENPACKAGENAME), dimension(:), allocatable :: pkgnames
36  character(len=LENMEMPATH), dimension(:), allocatable :: mempaths
37  integer(I4B), dimension(:), allocatable :: inunits
38  ! -- number of package instances
39  integer(I4B) :: pnum
40  contains
41  procedure :: create => pkgtype_create
42  procedure :: add => pkgtype_add
43  procedure :: destroy => pkgtype_destroy
44  end type loadablepackagetype
45 
46  !> @brief derived type for model package inputs type
47  !!
48  !! This derived type is used to define input package
49  !! descriptors for a model and load to managed memory.
50  !!
51  !<
53  ! -- model attributes
54  character(len=LENPACKAGETYPE) :: modeltype ! -- model type, e.g. 'GWF6'
55  character(len=LINELENGTH) :: modelfname
56  character(len=LENMODELNAME) :: modelname
57  ! -- component type
58  character(len=LENCOMPONENTNAME) :: component_type ! -- e.g. 'GWF'
59  ! -- mempaths
60  character(len=LENMEMPATH) :: input_mempath
61  character(len=LENMEMPATH) :: model_mempath
62  ! -- pointers to created managed memory
63  type(characterstringtype), dimension(:), contiguous, &
64  pointer :: pkgtypes => null()
65  type(characterstringtype), dimension(:), contiguous, &
66  pointer :: pkgnames => null()
67  type(characterstringtype), dimension(:), contiguous, &
68  pointer :: mempaths => null()
69  integer(I4B), dimension(:), contiguous, &
70  pointer :: inunits => null()
71  ! -- loadable package type array
72  type(loadablepackagetype), dimension(:), allocatable :: pkglist
73  ! -- pkgtype definitions
74  integer(I4B) :: niunit
75  character(len=LENPACKAGETYPE), dimension(:), allocatable :: cunit
76  ! -- out handle
77  integer(I4B) :: iout
78  contains
79  procedure :: init => modelpkgs_init
80  procedure :: memload => modelpkgs_memload
81  procedure :: destroy => modelpkgs_destroy
82  procedure, private :: create => modelpkgs_create
83  procedure, private :: addpkgs => modelpkgs_addpkgs
84  procedure, private :: add => modelpkgs_add
85  procedure, private :: pkgcount => modelpkgs_pkgcount
86  end type modelpackageinputstype
87 
88 contains
89 
90  !> @brief does model support multiple instances of this package type
91  !<
92  function multi_pkg_type(mtype_component, ptype_component, pkgtype) &
93  result(multi_pkg)
94  ! -- modules
97  ! -- dummy
98  character(len=LENCOMPONENTNAME), intent(in) :: mtype_component
99  character(len=LENCOMPONENTNAME), intent(in) :: ptype_component
100  character(len=LENFTYPE), intent(in) :: pkgtype
101  ! -- return
102  logical(LGP) :: multi_pkg
103  ! -- local
104  !
105  multi_pkg = .false.
106  !
107  if (idm_integrated(mtype_component, ptype_component)) then
108  multi_pkg = idm_multi_package(mtype_component, ptype_component)
109  !
110  else
111  multi_pkg = multi_package_type(mtype_component, ptype_component, pkgtype)
112  !
113  end if
114  !
115  ! -- return
116  return
117  end function multi_pkg_type
118 
119  !> @brief create a new package type
120  !<
121  subroutine pkgtype_create(this, modeltype, modelname, pkgtype)
122  ! -- modules
124  ! -- dummy
125  class(loadablepackagetype) :: this
126  character(len=*), intent(in) :: modeltype
127  character(len=*), intent(in) :: modelname
128  character(len=*), intent(in) :: pkgtype
129  ! -- local
130  !
131  ! -- initialize
132  this%pkgtype = pkgtype
133  this%subcomponent_type = idm_subcomponent_type(modeltype, pkgtype)
134  this%pnum = 0
135  !
136  ! -- allocate arrays
137  allocate (this%filenames(0))
138  allocate (this%pkgnames(0))
139  allocate (this%mempaths(0))
140  allocate (this%inunits(0))
141  !
142  ! -- return
143  return
144  end subroutine pkgtype_create
145 
146  !> @brief add a new package instance to this package type
147  !<
148  subroutine pkgtype_add(this, modelname, mtype_component, filetype, &
149  filename, pkgname, iout)
150  ! -- modules
157  ! -- dummy
158  class(loadablepackagetype) :: this
159  character(len=*), intent(in) :: modelname
160  character(len=*), intent(in) :: mtype_component
161  character(len=*), intent(in) :: filetype
162  character(len=*), intent(in) :: filename
163  character(len=*), intent(in) :: pkgname
164  integer(I4B), intent(in) :: iout
165  ! -- local
166  character(len=LENPACKAGENAME) :: sc_name, pname
167  character(len=LENMEMPATH) :: mempath
168  character(len=LINELENGTH), pointer :: cstr
169  !
170  ! -- reallocate
171  call expandarray(this%filenames)
172  call expandarray(this%pkgnames)
173  call expandarray(this%inunits)
174  call expandarray(this%mempaths)
175  !
176  ! -- add new package instance
177  this%pnum = this%pnum + 1
178  this%filenames(this%pnum) = filename
179  this%pkgnames(this%pnum) = pkgname
180  this%inunits(this%pnum) = 0
181  !
182  ! -- set pkgname if empty
183  if (this%pkgnames(this%pnum) == '') then
184  if (multi_pkg_type(mtype_component, &
185  this%subcomponent_type, &
186  filetype)) then
187  write (pname, '(a,i0)') trim(this%subcomponent_type)//'-', this%pnum
188  else
189  write (pname, '(a,i0)') trim(this%subcomponent_type)
190  end if
191  this%pkgnames(this%pnum) = pname
192  end if
193  !
194  ! -- set up input context for model
195  if (idm_integrated(mtype_component, this%subcomponent_type)) then
196  !
197  ! -- set subcomponent name
198  sc_name = idm_subcomponent_name(mtype_component, this%subcomponent_type, &
199  this%pkgnames(this%pnum))
200  !
201  ! -- create and store the mempath
202  this%mempaths(this%pnum) = &
203  create_mem_path(modelname, sc_name, idm_context)
204  !
205  ! -- allocate and initialize filename for package
206  mempath = create_mem_path(modelname, sc_name, idm_context)
207  call mem_allocate(cstr, linelength, 'INPUT_FNAME', mempath)
208  cstr = filename
209  !
210  else
211  !
212  ! -- set mempath empty
213  this%mempaths(this%pnum) = ''
214  end if
215  !
216  ! -- return
217  return
218  end subroutine pkgtype_add
219 
220  !> @brief deallocate object
221  !<
222  subroutine pkgtype_destroy(this)
223  ! -- modules
224  ! -- dummy
225  class(loadablepackagetype) :: this
226  ! -- local
227  !
228  ! -- deallocate dynamic arrays
229  deallocate (this%filenames)
230  deallocate (this%pkgnames)
231  deallocate (this%inunits)
232  deallocate (this%mempaths)
233  !
234  ! -- return
235  return
236  end subroutine pkgtype_destroy
237 
238  !> @brief initialize model package inputs object
239  !<
240  subroutine modelpkgs_init(this, modeltype, modelfname, modelname, iout)
241  ! -- modules
247  ! -- dummy
248  class(modelpackageinputstype) :: this
249  character(len=*), intent(in) :: modeltype
250  character(len=*), intent(in) :: modelfname
251  character(len=*), intent(in) :: modelname
252  integer(I4B), intent(in) :: iout
253  ! -- local
254  !
255  ! -- initialize object
256  this%modeltype = modeltype
257  this%modelfname = modelfname
258  this%modelname = modelname
259  this%component_type = idm_component_type(modeltype)
260  this%iout = iout
261  !
262  ! -- allocate and set model supported package types
263  call supported_model_packages(modeltype, this%cunit, this%niunit)
264  !
265  ! -- set memory paths
266  this%input_mempath = create_mem_path(this%modelname, 'NAM', idm_context)
267  this%model_mempath = create_mem_path(component=this%modelname, &
268  context=idm_context)
269  !
270  ! -- allocate managed memory
271  call mem_allocate(this%pkgtypes, lenpackagetype, 0, 'PKGTYPES', &
272  this%model_mempath)
273  call mem_allocate(this%pkgnames, lenpackagename, 0, 'PKGNAMES', &
274  this%model_mempath)
275  call mem_allocate(this%mempaths, lenmempath, 0, 'MEMPATHS', &
276  this%model_mempath)
277  call mem_allocate(this%inunits, 0, 'INUNITS', this%model_mempath)
278  !
279  ! build descriptions of packages
280  call this%addpkgs()
281  !
282  ! -- return
283  return
284  end subroutine modelpkgs_init
285 
286  !> @brief create the package type list
287  !<
288  subroutine modelpkgs_create(this, ftypes)
289  ! -- modules
290  use sortmodule, only: qsort
291  ! -- dummy
292  class(modelpackageinputstype) :: this
293  type(characterstringtype), dimension(:), contiguous, &
294  pointer :: ftypes
295  ! -- local
296  integer(I4B), dimension(:), allocatable :: cunit_idxs, indx
297  character(len=LENPACKAGETYPE) :: ftype
298  integer(I4B) :: n, m
299  logical(LGP) :: found
300  !
301  ! -- allocate
302  allocate (cunit_idxs(0))
303  !
304  ! -- identify input packages and check that each is supported
305  do n = 1, size(ftypes)
306  !
307  ! -- type from model nam file packages block
308  ftype = ftypes(n)
309  found = .false.
310  !
311  ! -- search supported types for this filetype
312  do m = 1, this%niunit
313  if (this%cunit(m) == ftype) then
314  ! -- set found
315  found = .true.
316  !
317  ! -- add to cunit list if first instance of this type
318  if (any(cunit_idxs == m)) then
319  ! no-op
320  else
321  call expandarray(cunit_idxs)
322  cunit_idxs(size(cunit_idxs)) = m
323  end if
324  !
325  ! -- exit search
326  exit
327  end if
328  end do
329  !
330  ! -- set error if namfile pkg filetype is not supported
331  if (.not. found) then
332  write (errmsg, '(a,a,a,a,a)') 'Model package type not supported &
333  &[model=', trim(this%modelname), ', type=', &
334  trim(ftype), '].'
335  call store_error(errmsg)
336  call store_error_filename(this%modelfname)
337  end if
338  end do
339  !
340  ! -- allocate the pkglist
341  allocate (this%pkglist(size(cunit_idxs)))
342  !
343  ! -- sort cunit indexes
344  allocate (indx(size(cunit_idxs)))
345  call qsort(indx, cunit_idxs)
346  !
347  ! -- create sorted LoadablePackageType object list
348  do n = 1, size(cunit_idxs)
349  call this%pkglist(n)%create(this%modeltype, this%modelname, &
350  this%cunit(cunit_idxs(n)))
351  end do
352  !
353  ! -- cleanup
354  deallocate (cunit_idxs)
355  deallocate (indx)
356  !
357  ! -- return
358  return
359  end subroutine modelpkgs_create
360 
361  !> @brief add a model package instance to package type list
362  !<
363  subroutine modelpkgs_add(this, pkgtype, filename, pkgname)
364  ! -- modules
365  ! -- dummy
366  class(modelpackageinputstype) :: this
367  character(len=*), intent(in) :: pkgtype
368  character(len=*), intent(in) :: filename
369  character(len=*), intent(in) :: pkgname
370  ! -- local
371  type(loadablepackagetype) :: pkg
372  integer(I4B) :: n
373  !
374  ! -- locate index of pkgtype in pkglist
375  do n = 1, size(this%pkglist)
376  pkg = this%pkglist(n)
377  if (pkg%pkgtype == pkgtype) then
378  call this%pkglist(n)%add(this%modelname, this%component_type, &
379  pkgtype, filename, pkgname, this%iout)
380  exit
381  end if
382  end do
383  !
384  ! -- return
385  return
386  end subroutine modelpkgs_add
387 
388  !> @brief build the type list with all model package instances
389  !<
390  subroutine modelpkgs_addpkgs(this)
391  ! -- modules
394  ! -- dummy
395  class(modelpackageinputstype) :: this
396  ! -- local
397  type(characterstringtype), dimension(:), contiguous, &
398  pointer :: ftypes !< file types
399  type(characterstringtype), dimension(:), contiguous, &
400  pointer :: fnames !< file names
401  type(characterstringtype), dimension(:), contiguous, &
402  pointer :: pnames !< package names
403  character(len=LINELENGTH) :: ftype, fname, pname
404  integer(I4B) :: n
405  !
406  ! -- set pointers to input context model package attribute arrays
407  call mem_setptr(ftypes, 'FTYPE', this%input_mempath)
408  call mem_setptr(fnames, 'FNAME', this%input_mempath)
409  call mem_setptr(pnames, 'PNAME', this%input_mempath)
410  !
411  ! -- create the package list
412  call this%create(ftypes)
413  !
414  ! -- load model packages
415  do n = 1, size(ftypes)
416  !
417  ! -- attributes for this package
418  ftype = ftypes(n)
419  fname = fnames(n)
420  call inlen_check(pnames(n), pname, lenpackagename, 'PACKAGENAME')
421  !
422  ! -- add this instance to package list
423  call this%add(ftype, fname, pname)
424  end do
425  !
426  ! -- terminate if errors were detected
427  if (count_errors() > 0) then
428  call store_error_filename(this%modelfname)
429  end if
430  !
431  ! --
432  return
433  end subroutine modelpkgs_addpkgs
434 
435  !> @brief get package instance count and verify base or multi of each
436  !<
437  function modelpkgs_pkgcount(this) result(pnum)
438  ! -- modules
439  ! -- dummy
440  class(modelpackageinputstype) :: this
441  !
442  ! -- return
443  integer(I4B) :: pnum
444  ! -- local
445  integer(I4B) :: n
446  !
447  ! -- initialize
448  pnum = 0
449  !
450  ! -- count model package instances
451  do n = 1, size(this%pkglist)
452  !
453  if (multi_pkg_type(this%component_type, &
454  this%pkglist(n)%subcomponent_type, &
455  this%pkglist(n)%pkgtype)) then
456  ! multiple instances ok
457  else
458  ! -- set error for unexpected extra packages
459  if (this%pkglist(n)%pnum > 1) then
460  write (errmsg, '(a,a,a,a,a)') &
461  'Multiple instances specified for model base package type &
462  &[model=', trim(this%modelname), ', type=', &
463  trim(this%pkglist(n)%pkgtype), '].'
464  call store_error(errmsg)
465  call store_error_filename(this%modelfname)
466  end if
467  end if
468  !
469  ! -- add to package count
470  pnum = pnum + this%pkglist(n)%pnum
471  end do
472  !
473  ! -- return
474  return
475  end function modelpkgs_pkgcount
476 
477  !> @brief load package descriptors to managed memory
478  !<
479  subroutine modelpkgs_memload(this)
480  ! -- modules
482  ! -- dummy
483  class(modelpackageinputstype) :: this
484  ! -- local
485  integer(I4B) :: n, m, idx
486  integer(I4B) :: pnum
487  !
488  ! -- initialize load index
489  idx = 0
490  !
491  ! -- set total number of package instances
492  pnum = this%pkgcount()
493  !
494  ! -- reallocate model input package attribute arrays
495  call mem_reallocate(this%pkgtypes, lenpackagetype, pnum, 'PKGTYPES', &
496  this%model_mempath)
497  call mem_reallocate(this%pkgnames, lenpackagename, pnum, 'PKGNAMES', &
498  this%model_mempath)
499  call mem_reallocate(this%mempaths, lenmempath, pnum, 'MEMPATHS', &
500  this%model_mempath)
501  call mem_reallocate(this%inunits, pnum, 'INUNITS', this%model_mempath)
502  !
503  ! -- load pkinfo
504  do n = 1, size(this%pkglist)
505  !
506  do m = 1, this%pkglist(n)%pnum
507  ! -- increment index
508  idx = idx + 1
509  ! -- package type like 'CHD6'
510  this%pkgtypes(idx) = trim(this%pkglist(n)%pkgtype)
511  ! -- package name like 'CHD-2'
512  this%pkgnames(idx) = trim(this%pkglist(n)%pkgnames(m))
513  ! -- memory path like '__INPUT__/MYMODEL/CHD-2'
514  this%mempaths(idx) = trim(this%pkglist(n)%mempaths(m))
515  ! -- input file unit number
516  this%inunits(idx) = this%pkglist(n)%inunits(m)
517  end do
518  end do
519  !
520  ! -- return
521  return
522  end subroutine modelpkgs_memload
523 
524  !> @brief deallocate object
525  !<
526  subroutine modelpkgs_destroy(this)
527  ! -- modules
528  ! -- dummy
529  class(modelpackageinputstype) :: this
530  ! -- local
531  integer(I4B) :: n
532  !
533  ! --
534  do n = 1, size(this%pkglist)
535  call this%pkglist(n)%destroy()
536  end do
537  !
538  deallocate (this%pkglist)
539  deallocate (this%cunit)
540  !
541  ! -- return
542  return
543  end subroutine modelpkgs_destroy
544 
545 end module modelpackageinputsmodule
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 lencomponentname
maximum length of a component name
Definition: Constants.f90:18
integer(i4b), parameter lenmodelname
maximum length of the model name
Definition: Constants.f90:22
integer(i4b), parameter lenpackagename
maximum length of the package name
Definition: Constants.f90:23
integer(i4b), parameter lenpackagetype
maximum length of a package type (DIS6, SFR6, CSUB6, etc.)
Definition: Constants.f90:38
integer(i4b), parameter lenftype
maximum length of a package type (DIS, WEL, OC, etc.)
Definition: Constants.f90:39
integer(i4b), parameter lenmempath
maximum length of the memory path
Definition: Constants.f90:27
logical function, public idm_integrated(component, subcomponent)
logical function, public idm_multi_package(component, subcomponent)
This module defines variable data types.
Definition: kind.f90:8
character(len=lenmempath) function create_mem_path(component, subcomponent, context)
returns the path to the memory object
This module contains the ModelPackageInputModule.
logical(lgp) function, public multi_package_type(mtype_component, ptype_component, pkgtype)
Is the package multi-instance.
subroutine, public supported_model_packages(mtype, pkgtypes, numpkgs)
set supported package types for model
This module contains the ModelPackageInputsModule.
subroutine modelpkgs_add(this, pkgtype, filename, pkgname)
add a model package instance to package type list
subroutine modelpkgs_init(this, modeltype, modelfname, modelname, iout)
initialize model package inputs object
subroutine pkgtype_destroy(this)
deallocate object
subroutine pkgtype_create(this, modeltype, modelname, pkgtype)
create a new package type
logical(lgp) function multi_pkg_type(mtype_component, ptype_component, pkgtype)
does model support multiple instances of this package type
subroutine modelpkgs_destroy(this)
deallocate object
subroutine modelpkgs_addpkgs(this)
build the type list with all model package instances
subroutine modelpkgs_memload(this)
load package descriptors to managed memory
subroutine modelpkgs_create(this, ftypes)
create the package type list
subroutine pkgtype_add(this, modelname, mtype_component, filetype, filename, pkgname, iout)
add a new package instance to this package type
integer(i4b) function modelpkgs_pkgcount(this)
get package instance count and verify base or multi of each
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
integer(i4b) function, public count_errors()
Return number of errors.
Definition: Sim.f90:59
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
character(len=linelength) idm_context
integer(i4b) iout
file unit number for simulation output
This module contains the SourceCommonModule.
Definition: SourceCommon.f90:7
character(len=lencomponentname) function, public idm_subcomponent_type(component, subcomponent)
component from package or model type
subroutine, public inlen_check(input_name, mf6_name, maxlen, name_type)
store an error for input exceeding internal name length
character(len=lencomponentname) function, public idm_component_type(component)
component from package or model type
character(len=lenpackagename) function, public idm_subcomponent_name(component_type, subcomponent_type, sc_name)
model package subcomponent name
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 loadable package type
derived type for model package inputs type