MODFLOW 6  version 6.7.0.dev2
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  public :: supported_model
22 
23  !> @brief derived type for loadable package type
24  !!
25  !! This derived type is used to store package instance
26  !! descriptions for a supported package type.
27  !!
28  !<
30  ! package type, e.g. 'DIS6' or 'CHD6'
31  character(len=LENPACKAGETYPE) :: pkgtype
32  ! component type, e.g. 'DIS' or 'CHD'
33  character(len=LENCOMPONENTNAME) :: subcomponent_type
34  ! package instance attribute arrays
35  character(len=LINELENGTH), dimension(:), allocatable :: filenames
36  character(len=LENPACKAGENAME), dimension(:), allocatable :: pkgnames
37  character(len=LENMEMPATH), dimension(:), allocatable :: mempaths
38  integer(I4B), dimension(:), allocatable :: inunits
39  ! number of package instances
40  integer(I4B) :: pnum
41  contains
42  procedure :: create => pkgtype_create
43  procedure :: add => pkgtype_add
44  procedure :: destroy => pkgtype_destroy
45  end type loadablepackagetype
46 
47  !> @brief derived type for model package inputs type
48  !!
49  !! This derived type is used to define input package
50  !! descriptors for a model and load to managed memory.
51  !!
52  !<
54  ! model attributes
55  character(len=LENPACKAGETYPE) :: modeltype ! model type, e.g. 'GWF6'
56  character(len=LINELENGTH) :: modelfname
57  character(len=LENMODELNAME) :: modelname
58  ! component type
59  character(len=LENCOMPONENTNAME) :: component_type ! e.g. 'GWF'
60  ! mempaths
61  character(len=LENMEMPATH) :: input_mempath
62  character(len=LENMEMPATH) :: model_mempath
63  ! pointers to created managed memory
64  type(characterstringtype), dimension(:), contiguous, &
65  pointer :: pkgtypes => null()
66  type(characterstringtype), dimension(:), contiguous, &
67  pointer :: pkgnames => null()
68  type(characterstringtype), dimension(:), contiguous, &
69  pointer :: mempaths => null()
70  integer(I4B), dimension(:), contiguous, &
71  pointer :: inunits => null()
72  ! loadable package type array
73  type(loadablepackagetype), dimension(:), allocatable :: pkglist
74  ! pkgtype definitions
75  integer(I4B) :: niunit
76  character(len=LENPACKAGETYPE), dimension(:), allocatable :: cunit
77  ! out handle
78  integer(I4B) :: iout
79  contains
80  procedure :: init => modelpkgs_init
81  procedure :: memload => modelpkgs_memload
82  procedure :: destroy => modelpkgs_destroy
83  procedure, private :: create => modelpkgs_create
84  procedure, private :: addpkgs => modelpkgs_addpkgs
85  procedure, private :: add => modelpkgs_add
86  procedure, private :: pkgcount => modelpkgs_pkgcount
87  end type modelpackageinputstype
88 
89 contains
90 
91  !> @brief does model support multiple instances of this package type
92  !<
93  function multi_pkg_type(mtype_component, ptype_component, pkgtype) &
94  result(multi_pkg)
97  character(len=LENCOMPONENTNAME), intent(in) :: mtype_component
98  character(len=LENCOMPONENTNAME), intent(in) :: ptype_component
99  character(len=LENFTYPE), intent(in) :: pkgtype
100  logical(LGP) :: multi_pkg
101  multi_pkg = .false.
102  if (idm_integrated(mtype_component, ptype_component)) then
103  multi_pkg = idm_multi_package(mtype_component, ptype_component)
104  else
105  multi_pkg = multi_package_type(mtype_component, ptype_component, pkgtype)
106  end if
107  end function multi_pkg_type
108 
109  !> @brief is this a supported MODFLOW 6 model type
110  !<
111  function supported_model(ctype)
113  character(len=*), intent(in) :: ctype
114  logical(LGP) :: supported_model
115  integer(I4B) :: n
116  supported_model = .false.
117  do n = 1, nmodel
118  if (ctype == modflow6models(n)) then
119  supported_model = .true.
120  exit
121  end if
122  end do
123  end function supported_model
124 
125  !> @brief create a new package type
126  !<
127  subroutine pkgtype_create(this, modeltype, modelname, pkgtype)
129  class(loadablepackagetype) :: this
130  character(len=*), intent(in) :: modeltype
131  character(len=*), intent(in) :: modelname
132  character(len=*), intent(in) :: pkgtype
133 
134  ! initialize
135  this%pkgtype = pkgtype
136  this%subcomponent_type = idm_subcomponent_type(modeltype, pkgtype)
137  this%pnum = 0
138 
139  ! allocate arrays
140  allocate (this%filenames(0))
141  allocate (this%pkgnames(0))
142  allocate (this%mempaths(0))
143  allocate (this%inunits(0))
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)
155  class(loadablepackagetype) :: this
156  character(len=*), intent(in) :: modelname
157  character(len=*), intent(in) :: mtype_component
158  character(len=*), intent(in) :: filetype
159  character(len=*), intent(in) :: filename
160  character(len=*), intent(in) :: pkgname
161  integer(I4B), intent(in) :: iout
162  character(len=LENPACKAGENAME) :: sc_name, pname
163  character(len=LENMEMPATH) :: mempath
164  character(len=LINELENGTH), pointer :: cstr
165 
166  ! reallocate
167  call expandarray(this%filenames)
168  call expandarray(this%pkgnames)
169  call expandarray(this%inunits)
170  call expandarray(this%mempaths)
171 
172  ! add new package instance
173  this%pnum = this%pnum + 1
174  this%filenames(this%pnum) = filename
175  this%pkgnames(this%pnum) = pkgname
176  this%inunits(this%pnum) = 0
177 
178  ! set pkgname if empty
179  if (this%pkgnames(this%pnum) == '') then
180  if (multi_pkg_type(mtype_component, &
181  this%subcomponent_type, &
182  filetype)) then
183  write (pname, '(a,i0)') trim(this%subcomponent_type)//'-', this%pnum
184  else
185  write (pname, '(a,i0)') trim(this%subcomponent_type)
186  end if
187  this%pkgnames(this%pnum) = pname
188  end if
189 
190  ! set up input context for model
191  if (idm_integrated(mtype_component, this%subcomponent_type)) then
192  ! set subcomponent name
193  sc_name = idm_subcomponent_name(mtype_component, this%subcomponent_type, &
194  this%pkgnames(this%pnum))
195  ! create and store the mempath
196  this%mempaths(this%pnum) = &
197  create_mem_path(modelname, sc_name, idm_context)
198  ! allocate and initialize filename for package
199  mempath = create_mem_path(modelname, sc_name, idm_context)
200  call mem_allocate(cstr, linelength, 'INPUT_FNAME', mempath)
201  cstr = filename
202  else
203  ! set mempath empty
204  this%mempaths(this%pnum) = ''
205  end if
206  end subroutine pkgtype_add
207 
208  !> @brief deallocate object
209  !<
210  subroutine pkgtype_destroy(this)
211  class(loadablepackagetype) :: this
212  ! deallocate dynamic arrays
213  deallocate (this%filenames)
214  deallocate (this%pkgnames)
215  deallocate (this%inunits)
216  deallocate (this%mempaths)
217  end subroutine pkgtype_destroy
218 
219  !> @brief initialize model package inputs object
220  !<
221  subroutine modelpkgs_init(this, modeltype, modelfname, modelname, iout)
227  class(modelpackageinputstype) :: this
228  character(len=*), intent(in) :: modeltype
229  character(len=*), intent(in) :: modelfname
230  character(len=*), intent(in) :: modelname
231  integer(I4B), intent(in) :: iout
232 
233  ! initialize object
234  this%modeltype = modeltype
235  this%modelfname = modelfname
236  this%modelname = modelname
237  this%component_type = idm_component_type(modeltype)
238  this%iout = iout
239 
240  ! verify user specified model type
241  if (.not. supported_model(modeltype)) then
242  ! -- error and exit for unsupported model type
243  write (errmsg, '(3a)') 'Models block model type "', trim(modeltype), &
244  '" is not valid.'
245  call store_error(errmsg)
247  end if
248 
249  ! allocate and set model supported package types
250  call supported_model_packages(modeltype, this%cunit, this%niunit)
251 
252  ! set memory paths
253  this%input_mempath = create_mem_path(this%modelname, 'NAM', idm_context)
254  this%model_mempath = create_mem_path(component=this%modelname, &
255  context=idm_context)
256  ! allocate managed memory
257  call mem_allocate(this%pkgtypes, lenpackagetype, 0, 'PKGTYPES', &
258  this%model_mempath)
259  call mem_allocate(this%pkgnames, lenpackagename, 0, 'PKGNAMES', &
260  this%model_mempath)
261  call mem_allocate(this%mempaths, lenmempath, 0, 'MEMPATHS', &
262  this%model_mempath)
263  call mem_allocate(this%inunits, 0, 'INUNITS', this%model_mempath)
264 
265  ! build descriptions of packages
266  call this%addpkgs()
267  end subroutine modelpkgs_init
268 
269  !> @brief create the package type list
270  !<
271  subroutine modelpkgs_create(this, ftypes)
272  use sortmodule, only: qsort
273  class(modelpackageinputstype) :: this
274  type(characterstringtype), dimension(:), contiguous, &
275  pointer :: ftypes
276  integer(I4B), dimension(:), allocatable :: cunit_idxs, indx
277  character(len=LENPACKAGETYPE) :: ftype
278  integer(I4B) :: n, m
279  logical(LGP) :: found
280 
281  ! allocate
282  allocate (cunit_idxs(0))
283 
284  ! identify input packages and check that each is supported
285  do n = 1, size(ftypes)
286  ! type from model nam file packages block
287  ftype = ftypes(n)
288  found = .false.
289 
290  ! search supported types for this filetype
291  do m = 1, this%niunit
292  if (this%cunit(m) == ftype) then
293  ! set found
294  found = .true.
295 
296  ! add to cunit list if first instance of this type
297  if (any(cunit_idxs == m)) then
298  ! no-op
299  else
300  call expandarray(cunit_idxs)
301  cunit_idxs(size(cunit_idxs)) = m
302  end if
303 
304  ! exit search
305  exit
306  end if
307  end do
308 
309  ! set error if namfile pkg filetype is not supported
310  if (.not. found) then
311  write (errmsg, '(a,a,a,a,a)') 'Model package type not supported &
312  &[model=', trim(this%modelname), ', type=', &
313  trim(ftype), '].'
314  call store_error(errmsg)
315  call store_error_filename(this%modelfname)
316  end if
317  end do
318 
319  ! allocate the pkglist
320  allocate (this%pkglist(size(cunit_idxs)))
321 
322  ! sort cunit indexes
323  allocate (indx(size(cunit_idxs)))
324  call qsort(indx, cunit_idxs)
325 
326  ! create sorted LoadablePackageType object list
327  do n = 1, size(cunit_idxs)
328  call this%pkglist(n)%create(this%modeltype, this%modelname, &
329  this%cunit(cunit_idxs(n)))
330  end do
331 
332  ! cleanup
333  deallocate (cunit_idxs)
334  deallocate (indx)
335  end subroutine modelpkgs_create
336 
337  !> @brief add a model package instance to package type list
338  !<
339  subroutine modelpkgs_add(this, pkgtype, filename, pkgname)
340  class(modelpackageinputstype) :: this
341  character(len=*), intent(in) :: pkgtype
342  character(len=*), intent(in) :: filename
343  character(len=*), intent(in) :: pkgname
344  type(loadablepackagetype) :: pkg
345  integer(I4B) :: n
346  ! locate index of pkgtype in pkglist
347  do n = 1, size(this%pkglist)
348  pkg = this%pkglist(n)
349  if (pkg%pkgtype == pkgtype) then
350  call this%pkglist(n)%add(this%modelname, this%component_type, &
351  pkgtype, filename, pkgname, this%iout)
352  exit
353  end if
354  end do
355  end subroutine modelpkgs_add
356 
357  !> @brief build the type list with all model package instances
358  !<
359  subroutine modelpkgs_addpkgs(this)
362  class(modelpackageinputstype) :: this
363  type(characterstringtype), dimension(:), contiguous, &
364  pointer :: ftypes !< file types
365  type(characterstringtype), dimension(:), contiguous, &
366  pointer :: fnames !< file names
367  type(characterstringtype), dimension(:), contiguous, &
368  pointer :: pnames !< package names
369  character(len=LINELENGTH) :: ftype, fname, pname
370  integer(I4B) :: n
371 
372  ! set pointers to input context model package attribute arrays
373  call mem_setptr(ftypes, 'FTYPE', this%input_mempath)
374  call mem_setptr(fnames, 'FNAME', this%input_mempath)
375  call mem_setptr(pnames, 'PNAME', this%input_mempath)
376 
377  ! create the package list
378  call this%create(ftypes)
379 
380  ! load model packages
381  do n = 1, size(ftypes)
382  ! attributes for this package
383  ftype = ftypes(n)
384  fname = fnames(n)
385  call inlen_check(pnames(n), pname, lenpackagename, 'PACKAGENAME')
386 
387  ! add this instance to package list
388  call this%add(ftype, fname, pname)
389  end do
390 
391  ! terminate if errors were detected
392  if (count_errors() > 0) then
393  call store_error_filename(this%modelfname)
394  end if
395  end subroutine modelpkgs_addpkgs
396 
397  !> @brief get package instance count and verify base or multi of each
398  !<
399  function modelpkgs_pkgcount(this) result(pnum)
400  class(modelpackageinputstype) :: this
401  integer(I4B) :: pnum
402  integer(I4B) :: n
403 
404  ! initialize
405  pnum = 0
406 
407  ! count model package instances
408  do n = 1, size(this%pkglist)
409  if (multi_pkg_type(this%component_type, &
410  this%pkglist(n)%subcomponent_type, &
411  this%pkglist(n)%pkgtype)) then
412  ! multiple instances ok
413  else
414  ! set error for unexpected extra packages
415  if (this%pkglist(n)%pnum > 1) then
416  write (errmsg, '(a,a,a,a,a)') &
417  'Multiple instances specified for model base package type &
418  &[model=', trim(this%modelname), ', type=', &
419  trim(this%pkglist(n)%pkgtype), '].'
420  call store_error(errmsg)
421  call store_error_filename(this%modelfname)
422  end if
423  end if
424 
425  ! add to package count
426  pnum = pnum + this%pkglist(n)%pnum
427  end do
428  end function modelpkgs_pkgcount
429 
430  !> @brief load package descriptors to managed memory
431  !<
432  subroutine modelpkgs_memload(this)
434  class(modelpackageinputstype) :: this
435  integer(I4B) :: n, m, idx
436  integer(I4B) :: pnum
437 
438  ! initialize load index
439  idx = 0
440 
441  ! set total number of package instances
442  pnum = this%pkgcount()
443 
444  ! reallocate model input package attribute arrays
445  call mem_reallocate(this%pkgtypes, lenpackagetype, pnum, 'PKGTYPES', &
446  this%model_mempath)
447  call mem_reallocate(this%pkgnames, lenpackagename, pnum, 'PKGNAMES', &
448  this%model_mempath)
449  call mem_reallocate(this%mempaths, lenmempath, pnum, 'MEMPATHS', &
450  this%model_mempath)
451  call mem_reallocate(this%inunits, pnum, 'INUNITS', this%model_mempath)
452 
453  ! load pkinfo
454  do n = 1, size(this%pkglist)
455  do m = 1, this%pkglist(n)%pnum
456  ! increment index
457  idx = idx + 1
458  ! package type like 'CHD6'
459  this%pkgtypes(idx) = trim(this%pkglist(n)%pkgtype)
460  ! package name like 'CHD-2'
461  this%pkgnames(idx) = trim(this%pkglist(n)%pkgnames(m))
462  ! memory path like '__INPUT__/MYMODEL/CHD-2'
463  this%mempaths(idx) = trim(this%pkglist(n)%mempaths(m))
464  ! input file unit number
465  this%inunits(idx) = this%pkglist(n)%inunits(m)
466  end do
467  end do
468  end subroutine modelpkgs_memload
469 
470  !> @brief deallocate object
471  !<
472  subroutine modelpkgs_destroy(this)
473  class(modelpackageinputstype) :: this
474  integer(I4B) :: n
475  do n = 1, size(this%pkglist)
476  call this%pkglist(n)%destroy()
477  end do
478  deallocate (this%pkglist)
479  deallocate (this%cunit)
480  end subroutine modelpkgs_destroy
481 
482 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.
integer(i4b), parameter, public nmodel
Valid simulation model types.
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
character(len=lenpackagetype), dimension(nmodel), public modflow6models
This module contains the ModelPackageInputsModule.
subroutine modelpkgs_add(this, pkgtype, filename, pkgname)
add a model package instance to package type list
logical(lgp) function, public supported_model(ctype)
is this a supported MODFLOW 6 model type
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
character(len=linelength) simfile
simulation name file
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