28 character(len=LENVARNAME),
parameter ::
dvt =
'TEMPERATURE '
29 character(len=LENVARNAME),
parameter ::
dvu =
'ENERGY '
30 character(len=LENVARNAME),
parameter ::
dvua =
'E '
37 integer(I4B),
pointer :: inest => null()
38 integer(I4B),
pointer :: incnd => null()
70 character(len=LENPACKAGETYPE),
dimension(GWE_NBASEPKG) ::
gwe_basepkg
71 data gwe_basepkg/
'DIS6 ',
'DISV6',
'DISU6',
' ',
' ', &
72 &
'IC6 ',
'FMI6 ',
'EST6 ',
'ADV6 ',
' ', &
73 &
'CND6 ',
'SSM6 ',
'MVE6 ',
'OC6 ',
' ', &
74 &
'OBS6 ',
' ',
' ',
' ',
' ', &
83 character(len=LENPACKAGETYPE),
dimension(GWE_NMULTIPKG) ::
gwe_multipkg
84 data gwe_multipkg/
'CTP6 ',
'ESL6 ',
'LKE6 ',
'SFE6 ',
' ', &
85 &
'MWE6 ',
'UZE6 ',
'API6 ',
' ',
' ', &
95 subroutine gwe_cr(filename, id, modelname)
106 character(len=*),
intent(in) :: filename
107 integer(I4B),
intent(in) :: id
108 character(len=*),
intent(in) :: modelname
110 integer(I4B) :: indis
121 call this%allocate_scalars(modelname)
124 call this%set_tsp_labels(this%macronym,
dvt,
dvu,
dvua)
133 call this%tsp_cr(filename, id, modelname,
'GWE', indis)
136 call this%create_packages(indis)
152 class(
bndtype),
pointer :: packobj
155 call this%dis%dis_df()
156 call this%fmi%fmi_df(this%dis, 0)
157 if (this%inmvt > 0)
call this%mvt%mvt_df(this%dis)
158 if (this%inadv > 0)
call this%adv%adv_df()
159 if (this%incnd > 0)
call this%cnd%cnd_df(this%dis)
160 if (this%inssm > 0)
call this%ssm%ssm_df()
162 call this%budget%budget_df(
niunit_gwe, this%depvarunit, &
163 this%depvarunitabbrev)
166 if (this%inssm == 0)
then
167 if (this%fmi%nflowpack > 0)
then
168 call store_error(
'Flow model has boundary packages, but there &
169 &is no SSM package. The SSM package must be activated.', &
175 this%neq = this%dis%nodes
176 this%nja = this%dis%nja
177 this%ia => this%dis%con%ia
178 this%ja => this%dis%con%ja
181 call this%allocate_arrays()
184 do ip = 1, this%bndlist%Count()
186 call packobj%bnd_df(this%neq, this%dis)
187 packobj%TsManager%iout = this%iout
188 packobj%TasManager%iout = this%iout
192 call this%obs%obs_df(this%iout, this%name,
'GWE', this%dis)
204 class(
bndtype),
pointer :: packobj
208 call this%dis%dis_ac(this%moffset, sparse)
209 if (this%incnd > 0) &
210 call this%cnd%cnd_ac(this%moffset, sparse)
213 do ip = 1, this%bndlist%Count()
215 call packobj%bnd_ac(this%moffset, sparse)
227 class(
bndtype),
pointer :: packobj
232 call this%dis%dis_mc(this%moffset, this%idxglo, matrix_sln)
234 if (this%incnd > 0)
call this%cnd%cnd_mc(this%moffset, matrix_sln)
237 do ip = 1, this%bndlist%Count()
239 call packobj%bnd_mc(this%moffset, matrix_sln)
256 class(
bndtype),
pointer :: packobj
259 call this%fmi%fmi_ar(this%ibound)
260 if (this%inmvt > 0)
call this%mvt%mvt_ar()
261 if (this%inic > 0)
call this%ic%ic_ar(this%x)
262 if (this%inest > 0)
call this%est%est_ar(this%dis, this%ibound)
263 if (this%inadv > 0)
call this%adv%adv_ar(this%dis, this%ibound)
264 if (this%incnd > 0)
call this%cnd%cnd_ar(this%ibound, this%est%porosity)
265 if (this%inssm > 0)
call this%ssm%ssm_ar(this%dis, this%ibound, this%x)
266 if (this%inobs > 0)
call this%obs%tsp_obs_ar(this%ic, this%x, this%flowja)
269 this%eqnsclfac = this%gwecommon%gwerhow * this%gwecommon%gwecpw
275 call this%oc%oc_ar(this%x, this%dis,
dhnoflo, this%depvartype)
276 call this%budget%set_ibudcsv(this%oc%ibudcsv)
279 do ip = 1, this%bndlist%Count()
281 call packobj%set_pointers(this%dis%nodes, this%ibound, this%x, &
282 this%xold, this%flowja)
284 call packobj%bnd_ar()
298 class(
bndtype),
pointer :: packobj
302 call this%fmi%fmi_rp(this%inmvt)
303 if (this%inmvt > 0)
call this%mvt%mvt_rp()
309 if (this%inoc > 0)
call this%oc%oc_rp()
310 if (this%inssm > 0)
call this%ssm%ssm_rp()
311 do ip = 1, this%bndlist%Count()
313 call packobj%bnd_rp()
314 call packobj%bnd_rp_obs()
327 class(
bndtype),
pointer :: packobj
329 integer(I4B) :: irestore
330 integer(I4B) :: ip, n
335 if (irestore == 0)
then
338 do n = 1, this%dis%nodes
339 if (this%ibound(n) == 0)
then
342 this%xold(n) = this%x(n)
348 do n = 1, this%dis%nodes
349 this%x(n) = this%xold(n)
354 call this%fmi%fmi_ad(this%x)
357 if (this%incnd > 0)
call this%cnd%cnd_ad()
358 if (this%inssm > 0)
call this%ssm%ssm_ad()
359 do ip = 1, this%bndlist%Count()
361 call packobj%bnd_ad()
363 call packobj%bnd_ck()
368 call this%obs%obs_ad()
379 integer(I4B),
intent(in) :: kiter
381 class(
bndtype),
pointer :: packobj
385 do ip = 1, this%bndlist%Count()
387 call packobj%bnd_cf()
396 subroutine gwe_fc(this, kiter, matrix_sln, inwtflag)
399 integer(I4B),
intent(in) :: kiter
401 integer(I4B),
intent(in) :: inwtflag
403 class(
bndtype),
pointer :: packobj
407 call this%fmi%fmi_fc(this%dis%nodes, this%xold, this%nja, matrix_sln, &
408 this%idxglo, this%rhs)
409 if (this%inmvt > 0)
then
410 call this%mvt%mvt_fc(this%x, this%x)
412 if (this%inest > 0)
then
413 call this%est%est_fc(this%dis%nodes, this%xold, this%nja, matrix_sln, &
414 this%idxglo, this%x, this%rhs, kiter)
416 if (this%inadv > 0)
then
417 call this%adv%adv_fc(this%dis%nodes, matrix_sln, this%idxglo, this%x, &
420 if (this%incnd > 0)
then
421 call this%cnd%cnd_fc(kiter, this%dis%nodes, this%nja, matrix_sln, &
422 this%idxglo, this%rhs, this%x)
424 if (this%inssm > 0)
then
425 call this%ssm%ssm_fc(matrix_sln, this%idxglo, this%rhs)
429 do ip = 1, this%bndlist%Count()
431 call packobj%bnd_fc(this%rhs, this%ia, this%idxglo, matrix_sln)
440 subroutine gwe_cc(this, innertot, kiter, iend, icnvgmod, cpak, ipak, dpak)
443 integer(I4B),
intent(in) :: innertot
444 integer(I4B),
intent(in) :: kiter
445 integer(I4B),
intent(in) :: iend
446 integer(I4B),
intent(in) :: icnvgmod
447 character(len=LENPAKLOC),
intent(inout) :: cpak
448 integer(I4B),
intent(inout) :: ipak
449 real(DP),
intent(inout) :: dpak
452 if (this%inmvt > 0)
call this%mvt%mvt_cc(kiter, iend, icnvgmod, cpak, dpak)
459 subroutine gwe_cq(this, icnvg, isuppress_output)
464 integer(I4B),
intent(in) :: icnvg
465 integer(I4B),
intent(in) :: isuppress_output
469 class(
bndtype),
pointer :: packobj
477 this%flowja(i) =
dzero
479 if (this%inadv > 0)
call this%adv%adv_cq(this%x, this%flowja)
480 if (this%incnd > 0)
call this%cnd%cnd_cq(this%x, this%flowja)
481 if (this%inest > 0)
call this%est%est_cq(this%dis%nodes, this%x, this%xold, &
483 if (this%inssm > 0)
call this%ssm%ssm_cq(this%flowja)
484 if (this%infmi > 0)
call this%fmi%fmi_cq(this%x, this%flowja)
489 do ip = 1, this%bndlist%Count()
491 call packobj%bnd_cf()
492 call packobj%bnd_cq(this%x, this%flowja)
507 subroutine gwe_bd(this, icnvg, isuppress_output)
511 integer(I4B),
intent(in) :: icnvg
512 integer(I4B),
intent(in) :: isuppress_output
515 class(
bndtype),
pointer :: packobj
524 call this%budget%reset()
525 if (this%inest > 0)
call this%est%est_bd(isuppress_output, this%budget)
526 if (this%inssm > 0)
call this%ssm%ssm_bd(isuppress_output, this%budget)
527 if (this%infmi > 0)
call this%fmi%fmi_bd(isuppress_output, this%budget)
528 if (this%inmvt > 0)
call this%mvt%mvt_bd(this%x, this%x)
529 do ip = 1, this%bndlist%Count()
531 call packobj%bnd_bd(this%budget)
542 integer(I4B),
intent(in) :: icbcfl
543 integer(I4B),
intent(in) :: ibudfl
544 integer(I4B),
intent(in) :: icbcun
547 if (this%inest > 0)
call this%est%est_ot_flow(icbcfl, icbcun)
548 call this%TransportModelType%tsp_ot_flow(icbcfl, ibudfl, icbcun)
565 class(
bndtype),
pointer :: packobj
572 call this%dis%dis_da()
574 call this%fmi%fmi_da()
575 call this%adv%adv_da()
576 call this%cnd%cnd_da()
577 call this%ssm%ssm_da()
578 call this%est%est_da()
579 call this%mvt%mvt_da()
580 call this%budget%budget_da()
582 call this%obs%obs_da()
583 call this%gwecommon%gweshared_dat_da()
586 deallocate (this%dis)
588 deallocate (this%fmi)
589 deallocate (this%adv)
590 deallocate (this%cnd)
591 deallocate (this%ssm)
592 deallocate (this%est)
593 deallocate (this%mvt)
594 deallocate (this%budget)
596 deallocate (this%obs)
597 nullify (this%gwecommon)
600 do ip = 1, this%bndlist%Count()
602 call packobj%bnd_da()
611 call this%TransportModelType%tsp_da()
614 call this%NumericalModelType%model_da()
629 real(DP),
dimension(:, :),
intent(in) :: budterm
630 character(len=LENBUDTXT),
dimension(:),
intent(in) :: budtxt
631 character(len=*),
intent(in) :: rowlabel
633 call this%budget%addentry(budterm,
delt, budtxt, rowlabel=rowlabel)
642 integer(I4B) :: iasym
644 class(
bndtype),
pointer :: packobj
650 if (this%inadv > 0)
then
651 if (this%adv%iasym /= 0) iasym = 1
655 if (this%incnd > 0)
then
656 if (this%cnd%ixt3d /= 0) iasym = 1
660 do ip = 1, this%bndlist%Count()
662 if (packobj%iasym /= 0) iasym = 1
677 character(len=*),
intent(in) :: modelname
680 call this%allocate_tsp_scalars(modelname)
709 character(len=*),
intent(in) :: filtyp
710 character(len=LINELENGTH) :: errmsg
711 integer(I4B),
intent(in) :: ipakid
712 integer(I4B),
intent(in) :: ipaknum
713 character(len=*),
intent(in) :: pakname
714 character(len=*),
intent(in) :: mempath
715 integer(I4B),
intent(in) :: inunit
716 integer(I4B),
intent(in) :: iout
718 class(
bndtype),
pointer :: packobj
719 class(
bndtype),
pointer :: packobj2
725 call ctp_create(packobj, ipakid, ipaknum, inunit, iout, this%name, &
726 pakname, this%depvartype, mempath)
728 call esl_create(packobj, ipakid, ipaknum, inunit, iout, this%name, &
729 pakname, this%gwecommon)
731 call lke_create(packobj, ipakid, ipaknum, inunit, iout, this%name, &
732 pakname, this%fmi, this%eqnsclfac, this%gwecommon, &
733 this%depvartype, this%depvarunit, this%depvarunitabbrev)
735 call sfe_create(packobj, ipakid, ipaknum, inunit, iout, this%name, &
736 pakname, this%fmi, this%eqnsclfac, this%gwecommon, &
737 this%depvartype, this%depvarunit, this%depvarunitabbrev)
739 call mwe_create(packobj, ipakid, ipaknum, inunit, iout, this%name, &
740 pakname, this%fmi, this%eqnsclfac, this%gwecommon, &
741 this%depvartype, this%depvarunit, this%depvarunitabbrev)
743 call uze_create(packobj, ipakid, ipaknum, inunit, iout, this%name, &
744 pakname, this%fmi, this%eqnsclfac, this%gwecommon, &
745 this%depvartype, this%depvarunit, this%depvarunitabbrev)
750 write (errmsg, *)
'Invalid package type: ', filtyp
757 do ip = 1, this%bndlist%Count()
759 if (packobj2%packName == pakname)
then
760 write (errmsg,
'(a,a)')
'Cannot create package. Package name '// &
761 'already exists: ', trim(pakname)
772 class(*),
pointer :: model
777 if (.not.
associated(model))
return
793 integer(I4B),
dimension(:),
allocatable,
intent(inout) :: bndpkgs
795 pointer,
intent(inout) :: pkgtypes
797 pointer,
intent(inout) :: pkgnames
799 pointer,
intent(inout) :: mempaths
800 integer(I4B),
dimension(:),
contiguous, &
801 pointer,
intent(inout) :: inunits
803 integer(I4B) :: ipakid, ipaknum
804 character(len=LENFTYPE) :: pkgtype, bndptype
805 character(len=LENPACKAGENAME) :: pkgname
806 character(len=LENMEMPATH) :: mempath
807 integer(I4B),
pointer :: inunit
810 if (
allocated(bndpkgs))
then
815 do n = 1,
size(bndpkgs)
817 pkgtype = pkgtypes(bndpkgs(n))
818 pkgname = pkgnames(bndpkgs(n))
819 mempath = mempaths(bndpkgs(n))
820 inunit => inunits(bndpkgs(n))
822 if (bndptype /= pkgtype)
then
827 call this%package_create(pkgtype, ipakid, ipaknum, pkgname, mempath, &
830 ipaknum = ipaknum + 1
852 integer(I4B),
intent(in) :: indis
855 pointer :: pkgtypes => null()
857 pointer :: pkgnames => null()
859 pointer :: mempaths => null()
860 integer(I4B),
dimension(:),
contiguous, &
861 pointer :: inunits => null()
862 character(len=LENMEMPATH) :: model_mempath
863 character(len=LENFTYPE) :: pkgtype
864 character(len=LENPACKAGENAME) :: pkgname
865 character(len=LENMEMPATH) :: mempath
866 integer(I4B),
pointer :: inunit
867 integer(I4B),
dimension(:),
allocatable :: bndpkgs
869 character(len=LENMEMPATH) :: mempathcnd =
''
875 call mem_setptr(pkgtypes,
'PKGTYPES', model_mempath)
876 call mem_setptr(pkgnames,
'PKGNAMES', model_mempath)
877 call mem_setptr(mempaths,
'MEMPATHS', model_mempath)
878 call mem_setptr(inunits,
'INUNITS', model_mempath)
880 do n = 1,
size(pkgtypes)
883 pkgtype = pkgtypes(n)
884 pkgname = pkgnames(n)
885 mempath = mempaths(n)
889 select case (pkgtype)
895 case (
'CTP6',
'ESL6',
'LKE6',
'SFE6', &
896 'MWE6',
'UZE6',
'API6')
898 bndpkgs(
size(bndpkgs)) = n
905 call est_cr(this%est, this%name, this%inest, this%iout, this%fmi, &
906 this%eqnsclfac, this%gwecommon)
907 call cnd_cr(this%cnd, this%name, mempathcnd, this%incnd, this%iout, &
908 this%fmi, this%eqnsclfac, this%gwecommon)
911 call this%ftype_check(indis, this%inest)
913 call this%create_bndpkgs(bndpkgs, pkgtypes, pkgnames, mempaths, inunits)
This module contains the API package methods.
subroutine, public api_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname)
@ brief Create a new package object
subroutine, public addbasemodeltolist(list, model)
This module contains the base boundary package.
subroutine, public addbndtolist(list, bnd)
Add boundary to package list.
class(bndtype) function, pointer, public getbndfromlist(list, idx)
Get boundary from package list.
This module contains the BudgetModule.
subroutine, public budget_cr(this, name_model)
@ brief Create a new budget object
This module contains simulation constants.
integer(i4b), parameter linelength
maximum length of a standard line
integer(i4b), parameter lenpackagename
maximum length of the package name
integer(i4b), parameter lenpackagetype
maximum length of a package type (DIS6, SFR6, CSUB6, etc.)
real(dp), parameter dhnoflo
real no flow constant
integer(i4b), parameter lenpakloc
maximum length of a package location
integer(i4b), parameter lenvarname
maximum length of a variable name
integer(i4b), parameter lenftype
maximum length of a package type (DIS, WEL, OC, etc.)
real(dp), parameter dzero
real constant zero
integer(i4b), parameter lenbudtxt
maximum length of a budget component names
integer(i4b), parameter lenmempath
maximum length of the memory path
subroutine, public cnd_cr(cndobj, name_model, input_mempath, inunit, iout, fmi, eqnsclfac, gwecommon)
Create a new CND object.
subroutine, public ctp_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, depvartype, mempath)
Create a new constant temperature package.
subroutine, public esl_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, gwecommon)
Create an energy source loading package.
– @ brief Energy Storage and Transfer (EST) Module
subroutine, public est_cr(estobj, name_model, inunit, iout, fmi, eqnsclfac, gwecommon)
@ brief Create a new EST package object
subroutine, public lke_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, fmi, eqnsclfac, gwecommon, dvt, dvu, dvua)
Create a new lke package.
subroutine create_bndpkgs(this, bndpkgs, pkgtypes, pkgnames, mempaths, inunits)
Source package info and begin to process.
character(len=lenpackagetype), dimension(gwe_nmultipkg), public gwe_multipkg
subroutine gwe_cf(this, kiter)
GWE Model calculate coefficients.
subroutine gwe_ot_flow(this, icbcfl, ibudfl, icbcun)
GWE model output routine.
subroutine gwe_bd(this, icnvg, isuppress_output)
GWE Model Budget.
subroutine gwe_bdentry(this, budterm, budtxt, rowlabel)
GroundWater Energy Transport Model Budget Entry.
integer(i4b), parameter, public gwe_nbasepkg
GWE base package array descriptors.
subroutine gwe_ad(this)
GWE Model Time Step Advance.
subroutine gwe_cq(this, icnvg, isuppress_output)
GWE Model calculate flow.
subroutine gwe_mc(this, matrix_sln)
Map the positions of the GWE model connections in the numerical solution coefficient matrix.
subroutine gwe_da(this)
Deallocate.
character(len=lenvarname), parameter dvt
dependent variable type, varies based on model type
subroutine gwe_df(this)
Define packages of the GWE model.
subroutine gwe_cc(this, innertot, kiter, iend, icnvgmod, cpak, ipak, dpak)
GWE Model Final Convergence Check.
subroutine allocate_scalars(this, modelname)
Allocate memory for non-allocatable members.
subroutine package_create(this, filtyp, ipakid, ipaknum, pakname, mempath, inunit, iout)
Create boundary condition packages for this model.
subroutine gwe_ac(this, sparse)
Add the internal connections of this model to the sparse matrix.
subroutine gwe_rp(this)
GWE Model Read and Prepare.
integer(i4b), parameter niunit_gwe
subroutine, public gwe_cr(filename, id, modelname)
Create a new groundwater energy transport model object.
subroutine gwe_fc(this, kiter, matrix_sln, inwtflag)
GWE Model fill coefficients.
integer(i4b) function gwe_get_iasym(this)
return 1 if any package causes the matrix to be asymmetric. Otherwise return 0.
character(len=lenvarname), parameter dvu
dependent variable unit of measure, either "mass" or "energy"
subroutine gwe_ar(this)
GWE Model Allocate and Read.
character(len=lenpackagetype), dimension(gwe_nbasepkg), public gwe_basepkg
integer(i4b), parameter, public gwe_nmultipkg
GWE multi package array descriptors.
subroutine create_gwe_packages(this, indis)
Source package info and begin to process.
class(gwemodeltype) function, pointer, public castasgwemodel(model)
Cast to GweModelType.
character(len=lenvarname), parameter dvua
abbreviation of the dependent variable unit of measure, either "M" or "E"
subroutine, public mwe_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, fmi, eqnsclfac, gwecommon, dvt, dvu, dvua)
Create new MWE package.
subroutine, public sfe_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, fmi, eqnsclfac, gwecommon, dvt, dvu, dvua)
Create a new sfe package.
subroutine, public uze_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, fmi, eqnsclfac, gwecommon, dvt, dvu, dvua)
Create a new UZE package.
This module defines variable data types.
type(listtype), public basemodellist
character(len=lenmempath) function create_mem_path(component, subcomponent, context)
returns the path to the memory object
subroutine, public memorystore_remove(component, subcomponent, context)
This module contains simulation methods.
subroutine, public store_error(msg, terminate)
Store an error message.
This module contains simulation variables.
character(len=linelength) idm_context
integer(i4b) isimcheck
simulation input check flag (1) to check input, (0) to ignore checks
integer(i4b) ifailedstepretry
current retry for this time step
subroutine csr_diagsum(ia, flowja)
logical(lgp), pointer, public readnewdata
flag indicating time to read new data
real(dp), pointer, public delt
length of the current time step
This module contains the base transport model type.
subroutine tsp_ot_flow(this, icbcfl, ibudfl, icbcun)
Generalized transport model output routine.
Highest level model type. All models extend this parent type.
Derived type for the Budget object.
This class is used to store a single deferred-length character string. It was designed to work in an ...
@ brief Energy storage and transfer