31 character(len=LENPACKAGETYPE) :: pkgtype
33 character(len=LENCOMPONENTNAME) :: subcomponent_type
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
55 character(len=LENPACKAGETYPE) :: modeltype
56 character(len=LINELENGTH) :: modelfname
57 character(len=LENMODELNAME) :: modelname
59 character(len=LENCOMPONENTNAME) :: component_type
61 character(len=LENMEMPATH) :: input_mempath
62 character(len=LENMEMPATH) :: model_mempath
65 pointer :: pkgtypes => null()
67 pointer :: pkgnames => null()
69 pointer :: mempaths => null()
70 integer(I4B),
dimension(:),
contiguous, &
71 pointer :: inunits => null()
75 integer(I4B) :: niunit
76 character(len=LENPACKAGETYPE),
dimension(:),
allocatable :: cunit
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
113 character(len=*),
intent(in) :: ctype
130 character(len=*),
intent(in) :: modeltype
131 character(len=*),
intent(in) :: modelname
132 character(len=*),
intent(in) :: pkgtype
135 this%pkgtype = pkgtype
140 allocate (this%filenames(0))
141 allocate (this%pkgnames(0))
142 allocate (this%mempaths(0))
143 allocate (this%inunits(0))
148 subroutine pkgtype_add(this, modelname, mtype_component, filetype, &
149 filename, pkgname, iout)
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
173 this%pnum = this%pnum + 1
174 this%filenames(this%pnum) = filename
175 this%pkgnames(this%pnum) = pkgname
176 this%inunits(this%pnum) = 0
179 if (this%pkgnames(this%pnum) ==
'')
then
181 this%subcomponent_type, &
183 write (pname,
'(a,i0)') trim(this%subcomponent_type)//
'-', this%pnum
185 write (pname,
'(a,i0)') trim(this%subcomponent_type)
187 this%pkgnames(this%pnum) = pname
194 this%pkgnames(this%pnum))
196 this%mempaths(this%pnum) = &
204 this%mempaths(this%pnum) =
''
213 deallocate (this%filenames)
214 deallocate (this%pkgnames)
215 deallocate (this%inunits)
216 deallocate (this%mempaths)
228 character(len=*),
intent(in) :: modeltype
229 character(len=*),
intent(in) :: modelfname
230 character(len=*),
intent(in) :: modelname
231 integer(I4B),
intent(in) :: iout
234 this%modeltype = modeltype
235 this%modelfname = modelfname
236 this%modelname = modelname
243 write (errmsg,
'(3a)')
'Models block model type "', trim(modeltype), &
263 call mem_allocate(this%inunits, 0,
'INUNITS', this%model_mempath)
276 integer(I4B),
dimension(:),
allocatable :: cunit_idxs, indx
277 character(len=LENPACKAGETYPE) :: ftype
279 logical(LGP) :: found
282 allocate (cunit_idxs(0))
285 do n = 1,
size(ftypes)
291 do m = 1, this%niunit
292 if (this%cunit(m) == ftype)
then
297 if (any(cunit_idxs == m))
then
301 cunit_idxs(
size(cunit_idxs)) = m
310 if (.not. found)
then
311 write (errmsg,
'(a,a,a,a,a)')
'Model package type not supported &
312 &[model=', trim(this%modelname),
', type=', &
320 allocate (this%pkglist(
size(cunit_idxs)))
323 allocate (indx(
size(cunit_idxs)))
324 call qsort(indx, cunit_idxs)
327 do n = 1,
size(cunit_idxs)
328 call this%pkglist(n)%create(this%modeltype, this%modelname, &
329 this%cunit(cunit_idxs(n)))
333 deallocate (cunit_idxs)
341 character(len=*),
intent(in) :: pkgtype
342 character(len=*),
intent(in) :: filename
343 character(len=*),
intent(in) :: pkgname
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)
369 character(len=LINELENGTH) :: ftype, fname, pname
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)
378 call this%create(ftypes)
381 do n = 1,
size(ftypes)
388 call this%add(ftype, fname, pname)
408 do n = 1,
size(this%pkglist)
410 this%pkglist(n)%subcomponent_type, &
411 this%pkglist(n)%pkgtype))
then
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),
'].'
426 pnum = pnum + this%pkglist(n)%pnum
435 integer(I4B) :: n, m, idx
442 pnum = this%pkgcount()
451 call mem_reallocate(this%inunits, pnum,
'INUNITS', this%model_mempath)
454 do n = 1,
size(this%pkglist)
455 do m = 1, this%pkglist(n)%pnum
459 this%pkgtypes(idx) = trim(this%pkglist(n)%pkgtype)
461 this%pkgnames(idx) = trim(this%pkglist(n)%pkgnames(m))
463 this%mempaths(idx) = trim(this%pkglist(n)%mempaths(m))
465 this%inunits(idx) = this%pkglist(n)%inunits(m)
475 do n = 1,
size(this%pkglist)
476 call this%pkglist(n)%destroy()
478 deallocate (this%pkglist)
479 deallocate (this%cunit)
This module contains simulation constants.
integer(i4b), parameter linelength
maximum length of a standard line
integer(i4b), parameter lencomponentname
maximum length of a component name
integer(i4b), parameter lenmodelname
maximum length of the model name
integer(i4b), parameter lenpackagename
maximum length of the package name
integer(i4b), parameter lenpackagetype
maximum length of a package type (DIS6, SFR6, CSUB6, etc.)
integer(i4b), parameter lenftype
maximum length of a package type (DIS, WEL, OC, etc.)
integer(i4b), parameter lenmempath
maximum length of the memory path
logical function, public idm_integrated(component, subcomponent)
logical function, public idm_multi_package(component, subcomponent)
This module defines variable data types.
character(len=lenmempath) function create_mem_path(component, subcomponent, context)
returns the path to the memory object
This module contains simulation methods.
subroutine, public store_error(msg, terminate)
Store an error message.
integer(i4b) function, public count_errors()
Return number of errors.
subroutine, public store_error_filename(filename, terminate)
Store the erroring file name.
This module contains simulation variables.
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.
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 ...