50 character(len=*),
parameter ::
ftype =
'SFT'
51 character(len=*),
parameter ::
flowtype =
'SFR'
52 character(len=16) ::
text =
' SFT'
56 integer(I4B),
pointer :: idxbudrain => null()
57 integer(I4B),
pointer :: idxbudevap => null()
58 integer(I4B),
pointer :: idxbudroff => null()
59 integer(I4B),
pointer :: idxbudiflw => null()
60 integer(I4B),
pointer :: idxbudoutf => null()
62 real(dp),
dimension(:),
pointer,
contiguous :: concrain => null()
63 real(dp),
dimension(:),
pointer,
contiguous :: concevap => null()
64 real(dp),
dimension(:),
pointer,
contiguous :: concroff => null()
65 real(dp),
dimension(:),
pointer,
contiguous :: conciflw => null()
94 subroutine sft_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, &
95 fmi, eqnsclfac, dvt, dvu, dvua)
97 class(
bndtype),
pointer :: packobj
98 integer(I4B),
intent(in) :: id
99 integer(I4B),
intent(in) :: ibcnum
100 integer(I4B),
intent(in) :: inunit
101 integer(I4B),
intent(in) :: iout
102 character(len=*),
intent(in) :: namemodel
103 character(len=*),
intent(in) :: pakname
105 real(dp),
intent(in),
pointer :: eqnsclfac
106 character(len=*),
intent(in) :: dvt
107 character(len=*),
intent(in) :: dvu
108 character(len=*),
intent(in) :: dvua
117 call packobj%set_names(ibcnum, namemodel, pakname,
ftype)
121 call sftobj%allocate_scalars()
124 call packobj%pack_initialize()
126 packobj%inunit = inunit
129 packobj%ibcnum = ibcnum
139 sftobj%eqnsclfac => eqnsclfac
142 sftobj%depvartype = dvt
143 sftobj%depvarunit = dvu
144 sftobj%depvarunitabbrev = dvua
155 character(len=LINELENGTH) :: errmsg
156 class(
bndtype),
pointer :: packobj
157 integer(I4B) :: ip, icount
158 integer(I4B) :: nbudterm
168 if (this%fmi%flows_from_file)
then
169 call this%fmi%set_aptbudobj_pointer(this%flowpackagename, this%flowbudptr)
170 if (
associated(this%flowbudptr)) found = .true.
173 if (
associated(this%fmi%gwfbndlist))
then
176 do ip = 1, this%fmi%gwfbndlist%Count()
178 if (packobj%packName == this%flowpackagename)
then
183 this%flowpackagebnd => packobj
184 select type (packobj)
186 this%flowbudptr => packobj%budobj
195 if (.not. found)
then
196 write (errmsg,
'(a)')
'Could not find flow package with name '&
197 &//trim(adjustl(this%flowpackagename))//
'.'
199 call this%parser%StoreErrorUnit()
204 nbudterm = this%flowbudptr%nbudterm
205 call mem_allocate(this%idxbudssm, nbudterm,
'IDXBUDSSM', this%memoryPath)
208 write (this%iout,
'(/, a, a)') &
209 'PROCESSING '//
ftype//
' INFORMATION FOR ', this%packName
210 write (this%iout,
'(a)')
' IDENTIFYING FLOW TERMS IN '//
flowtype//
' PACKAGE'
211 write (this%iout,
'(a, i0)') &
212 ' NUMBER OF '//
flowtype//
' = ', this%flowbudptr%ncv
214 do ip = 1, this%flowbudptr%nbudterm
215 select case (trim(adjustl(this%flowbudptr%budterm(ip)%flowtype)))
216 case (
'FLOW-JA-FACE')
218 this%idxbudssm(ip) = 0
221 this%idxbudssm(ip) = 0
224 this%idxbudssm(ip) = 0
227 this%idxbudssm(ip) = 0
230 this%idxbudssm(ip) = 0
233 this%idxbudssm(ip) = 0
236 this%idxbudssm(ip) = 0
239 this%idxbudssm(ip) = 0
242 this%idxbudssm(ip) = 0
245 this%idxbudssm(ip) = 0
248 this%idxbudssm(ip) = 0
253 this%idxbudssm(ip) = icount
256 write (this%iout,
'(a, i0, " = ", a,/, a, i0)') &
257 ' TERM ', ip, trim(adjustl(this%flowbudptr%budterm(ip)%flowtype)), &
258 ' MAX NO. OF ENTRIES = ', this%flowbudptr%budterm(ip)%maxlist
260 write (this%iout,
'(a, //)')
'DONE PROCESSING '//
ftype//
' INFORMATION'
272 real(DP),
dimension(:),
intent(inout) :: rhs
273 integer(I4B),
dimension(:),
intent(in) :: ia
274 integer(I4B),
dimension(:),
intent(in) :: idxglo
277 integer(I4B) :: j, n1, n2
279 integer(I4B) :: iposd
285 if (this%idxbudrain /= 0)
then
286 do j = 1, this%flowbudptr%budterm(this%idxbudrain)%nlist
287 call this%sft_rain_term(j, n1, n2, rrate, rhsval, hcofval)
288 iloc = this%idxlocnode(n1)
289 iposd = this%idxpakdiag(n1)
290 call matrix_sln%add_value_pos(iposd, hcofval)
291 rhs(iloc) = rhs(iloc) + rhsval
296 if (this%idxbudevap /= 0)
then
297 do j = 1, this%flowbudptr%budterm(this%idxbudevap)%nlist
298 call this%sft_evap_term(j, n1, n2, rrate, rhsval, hcofval)
299 iloc = this%idxlocnode(n1)
300 iposd = this%idxpakdiag(n1)
301 call matrix_sln%add_value_pos(iposd, hcofval)
302 rhs(iloc) = rhs(iloc) + rhsval
307 if (this%idxbudroff /= 0)
then
308 do j = 1, this%flowbudptr%budterm(this%idxbudroff)%nlist
309 call this%sft_roff_term(j, n1, n2, rrate, rhsval, hcofval)
310 iloc = this%idxlocnode(n1)
311 iposd = this%idxpakdiag(n1)
312 call matrix_sln%add_value_pos(iposd, hcofval)
313 rhs(iloc) = rhs(iloc) + rhsval
318 if (this%idxbudiflw /= 0)
then
319 do j = 1, this%flowbudptr%budterm(this%idxbudiflw)%nlist
320 call this%sft_iflw_term(j, n1, n2, rrate, rhsval, hcofval)
321 iloc = this%idxlocnode(n1)
322 iposd = this%idxpakdiag(n1)
323 call matrix_sln%add_value_pos(iposd, hcofval)
324 rhs(iloc) = rhs(iloc) + rhsval
329 if (this%idxbudoutf /= 0)
then
330 do j = 1, this%flowbudptr%budterm(this%idxbudoutf)%nlist
331 call this%sft_outf_term(j, n1, n2, rrate, rhsval, hcofval)
332 iloc = this%idxlocnode(n1)
333 iposd = this%idxpakdiag(n1)
334 call matrix_sln%add_value_pos(iposd, hcofval)
335 rhs(iloc) = rhs(iloc) + rhsval
347 integer(I4B) :: n1, n2
351 if (this%idxbudrain /= 0)
then
352 do j = 1, this%flowbudptr%budterm(this%idxbudrain)%nlist
353 call this%sft_rain_term(j, n1, n2, rrate)
354 this%dbuff(n1) = this%dbuff(n1) + rrate
359 if (this%idxbudevap /= 0)
then
360 do j = 1, this%flowbudptr%budterm(this%idxbudevap)%nlist
361 call this%sft_evap_term(j, n1, n2, rrate)
362 this%dbuff(n1) = this%dbuff(n1) + rrate
367 if (this%idxbudroff /= 0)
then
368 do j = 1, this%flowbudptr%budterm(this%idxbudroff)%nlist
369 call this%sft_roff_term(j, n1, n2, rrate)
370 this%dbuff(n1) = this%dbuff(n1) + rrate
375 if (this%idxbudiflw /= 0)
then
376 do j = 1, this%flowbudptr%budterm(this%idxbudiflw)%nlist
377 call this%sft_iflw_term(j, n1, n2, rrate)
378 this%dbuff(n1) = this%dbuff(n1) + rrate
383 if (this%idxbudoutf /= 0)
then
384 do j = 1, this%flowbudptr%budterm(this%idxbudoutf)%nlist
385 call this%sft_outf_term(j, n1, n2, rrate)
386 this%dbuff(n1) = this%dbuff(n1) + rrate
400 integer(I4B) :: nbudterms
414 integer(I4B),
intent(inout) :: idx
416 integer(I4B) :: maxlist, naux
417 character(len=LENBUDTXT) :: text
422 maxlist = this%flowbudptr%budterm(this%idxbudrain)%maxlist
424 call this%budobj%budterm(idx)%initialize(text, &
429 maxlist, .false., .false., &
433 text =
' EVAPORATION'
435 maxlist = this%flowbudptr%budterm(this%idxbudevap)%maxlist
437 call this%budobj%budterm(idx)%initialize(text, &
442 maxlist, .false., .false., &
448 maxlist = this%flowbudptr%budterm(this%idxbudroff)%maxlist
450 call this%budobj%budterm(idx)%initialize(text, &
455 maxlist, .false., .false., &
461 maxlist = this%flowbudptr%budterm(this%idxbudiflw)%maxlist
463 call this%budobj%budterm(idx)%initialize(text, &
468 maxlist, .false., .false., &
472 text =
' EXT-OUTFLOW'
474 maxlist = this%flowbudptr%budterm(this%idxbudoutf)%maxlist
476 call this%budobj%budterm(idx)%initialize(text, &
481 maxlist, .false., .false., &
491 integer(I4B),
intent(inout) :: idx
492 real(DP),
dimension(:),
intent(in) :: x
493 real(DP),
dimension(:),
contiguous,
intent(inout) :: flowja
494 real(DP),
intent(inout) :: ccratin
495 real(DP),
intent(inout) :: ccratout
497 integer(I4B) :: j, n1, n2
498 integer(I4B) :: nlist
504 nlist = this%flowbudptr%budterm(this%idxbudrain)%nlist
505 call this%budobj%budterm(idx)%reset(nlist)
507 call this%sft_rain_term(j, n1, n2, q)
508 call this%budobj%budterm(idx)%update_term(n1, n2, q)
509 call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
514 nlist = this%flowbudptr%budterm(this%idxbudevap)%nlist
515 call this%budobj%budterm(idx)%reset(nlist)
517 call this%sft_evap_term(j, n1, n2, q)
518 call this%budobj%budterm(idx)%update_term(n1, n2, q)
519 call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
524 nlist = this%flowbudptr%budterm(this%idxbudroff)%nlist
525 call this%budobj%budterm(idx)%reset(nlist)
527 call this%sft_roff_term(j, n1, n2, q)
528 call this%budobj%budterm(idx)%update_term(n1, n2, q)
529 call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
534 nlist = this%flowbudptr%budterm(this%idxbudiflw)%nlist
535 call this%budobj%budterm(idx)%reset(nlist)
537 call this%sft_iflw_term(j, n1, n2, q)
538 call this%budobj%budterm(idx)%update_term(n1, n2, q)
539 call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
544 nlist = this%flowbudptr%budterm(this%idxbudoutf)%nlist
545 call this%budobj%budterm(idx)%reset(nlist)
547 call this%sft_outf_term(j, n1, n2, q)
548 call this%budobj%budterm(idx)%update_term(n1, n2, q)
549 call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
564 call this%TspAptType%allocate_scalars()
567 call mem_allocate(this%idxbudrain,
'IDXBUDRAIN', this%memoryPath)
568 call mem_allocate(this%idxbudevap,
'IDXBUDEVAP', this%memoryPath)
569 call mem_allocate(this%idxbudroff,
'IDXBUDROFF', this%memoryPath)
570 call mem_allocate(this%idxbudiflw,
'IDXBUDIFLW', this%memoryPath)
571 call mem_allocate(this%idxbudoutf,
'IDXBUDOUTF', this%memoryPath)
593 call mem_allocate(this%concrain, this%ncv,
'CONCRAIN', this%memoryPath)
594 call mem_allocate(this%concevap, this%ncv,
'CONCEVAP', this%memoryPath)
595 call mem_allocate(this%concroff, this%ncv,
'CONCROFF', this%memoryPath)
596 call mem_allocate(this%conciflw, this%ncv,
'CONCIFLW', this%memoryPath)
599 call this%TspAptType%apt_allocate_arrays()
603 this%concrain(n) =
dzero
604 this%concevap(n) =
dzero
605 this%concroff(n) =
dzero
606 this%conciflw(n) =
dzero
633 call this%TspAptType%bnd_da()
642 integer(I4B),
intent(in) :: ientry
643 integer(I4B),
intent(inout) :: n1
644 integer(I4B),
intent(inout) :: n2
645 real(DP),
intent(inout),
optional :: rrate
646 real(DP),
intent(inout),
optional :: rhsval
647 real(DP),
intent(inout),
optional :: hcofval
652 n1 = this%flowbudptr%budterm(this%idxbudrain)%id1(ientry)
653 n2 = this%flowbudptr%budterm(this%idxbudrain)%id2(ientry)
654 qbnd = this%flowbudptr%budterm(this%idxbudrain)%flow(ientry)
655 ctmp = this%concrain(n1)
656 if (
present(rrate)) rrate = ctmp * qbnd
657 if (
present(rhsval)) rhsval = -rrate
658 if (
present(hcofval)) hcofval =
dzero
667 integer(I4B),
intent(in) :: ientry
668 integer(I4B),
intent(inout) :: n1
669 integer(I4B),
intent(inout) :: n2
670 real(DP),
intent(inout),
optional :: rrate
671 real(DP),
intent(inout),
optional :: rhsval
672 real(DP),
intent(inout),
optional :: hcofval
678 n1 = this%flowbudptr%budterm(this%idxbudevap)%id1(ientry)
679 n2 = this%flowbudptr%budterm(this%idxbudevap)%id2(ientry)
681 qbnd = this%flowbudptr%budterm(this%idxbudevap)%flow(ientry)
682 ctmp = this%concevap(n1)
683 if (this%xnewpak(n1) < ctmp)
then
688 if (
present(rrate)) &
689 rrate = omega * qbnd * this%xnewpak(n1) + &
690 (
done - omega) * qbnd * ctmp
691 if (
present(rhsval)) rhsval = -(
done - omega) * qbnd * ctmp
692 if (
present(hcofval)) hcofval = omega * qbnd
701 integer(I4B),
intent(in) :: ientry
702 integer(I4B),
intent(inout) :: n1
703 integer(I4B),
intent(inout) :: n2
704 real(DP),
intent(inout),
optional :: rrate
705 real(DP),
intent(inout),
optional :: rhsval
706 real(DP),
intent(inout),
optional :: hcofval
711 n1 = this%flowbudptr%budterm(this%idxbudroff)%id1(ientry)
712 n2 = this%flowbudptr%budterm(this%idxbudroff)%id2(ientry)
713 qbnd = this%flowbudptr%budterm(this%idxbudroff)%flow(ientry)
714 ctmp = this%concroff(n1)
715 if (
present(rrate)) rrate = ctmp * qbnd
716 if (
present(rhsval)) rhsval = -rrate
717 if (
present(hcofval)) hcofval =
dzero
730 integer(I4B),
intent(in) :: ientry
731 integer(I4B),
intent(inout) :: n1
732 integer(I4B),
intent(inout) :: n2
733 real(DP),
intent(inout),
optional :: rrate
734 real(DP),
intent(inout),
optional :: rhsval
735 real(DP),
intent(inout),
optional :: hcofval
740 n1 = this%flowbudptr%budterm(this%idxbudiflw)%id1(ientry)
741 n2 = this%flowbudptr%budterm(this%idxbudiflw)%id2(ientry)
742 qbnd = this%flowbudptr%budterm(this%idxbudiflw)%flow(ientry)
743 ctmp = this%conciflw(n1)
744 if (
present(rrate)) rrate = ctmp * qbnd
745 if (
present(rhsval)) rhsval = -rrate
746 if (
present(hcofval)) hcofval =
dzero
758 integer(I4B),
intent(in) :: ientry
759 integer(I4B),
intent(inout) :: n1
760 integer(I4B),
intent(inout) :: n2
761 real(DP),
intent(inout),
optional :: rrate
762 real(DP),
intent(inout),
optional :: rhsval
763 real(DP),
intent(inout),
optional :: hcofval
768 n1 = this%flowbudptr%budterm(this%idxbudoutf)%id1(ientry)
769 n2 = this%flowbudptr%budterm(this%idxbudoutf)%id2(ientry)
770 qbnd = this%flowbudptr%budterm(this%idxbudoutf)%flow(ientry)
771 ctmp = this%xnewpak(n1)
772 if (
present(rrate)) rrate = ctmp * qbnd
773 if (
present(rhsval)) rhsval =
dzero
774 if (
present(hcofval)) hcofval = qbnd
791 call this%obs%StoreObsType(
'concentration', .false., indx)
796 call this%obs%StoreObsType(
'flow-ja-face', .true., indx)
801 call this%obs%StoreObsType(
'from-mvr', .true., indx)
806 call this%obs%StoreObsType(
'to-mvr', .true., indx)
811 call this%obs%StoreObsType(
'storage', .true., indx)
816 call this%obs%StoreObsType(
'constant', .true., indx)
821 call this%obs%StoreObsType(
'sft', .true., indx)
826 call this%obs%StoreObsType(
'rainfall', .true., indx)
831 call this%obs%StoreObsType(
'evaporation', .true., indx)
836 call this%obs%StoreObsType(
'runoff', .true., indx)
841 call this%obs%StoreObsType(
'ext-inflow', .true., indx)
846 call this%obs%StoreObsType(
'ext-outflow', .true., indx)
858 logical,
intent(inout) :: found
862 select case (obsrv%ObsTypeId)
864 call this%rp_obs_byfeature(obsrv)
866 call this%rp_obs_byfeature(obsrv)
868 call this%rp_obs_byfeature(obsrv)
870 call this%rp_obs_byfeature(obsrv)
872 call this%rp_obs_byfeature(obsrv)
874 call this%rp_obs_byfeature(obsrv)
885 character(len=*),
intent(in) :: obstypeid
886 real(DP),
intent(inout) :: v
887 integer(I4B),
intent(in) :: jj
888 logical,
intent(inout) :: found
890 integer(I4B) :: n1, n2
893 select case (obstypeid)
895 if (this%iboundpak(jj) /= 0)
then
896 call this%sft_rain_term(jj, n1, n2, v)
899 if (this%iboundpak(jj) /= 0)
then
900 call this%sft_evap_term(jj, n1, n2, v)
903 if (this%iboundpak(jj) /= 0)
then
904 call this%sft_roff_term(jj, n1, n2, v)
907 if (this%iboundpak(jj) /= 0)
then
908 call this%sft_iflw_term(jj, n1, n2, v)
911 if (this%iboundpak(jj) /= 0)
then
912 call this%sft_outf_term(jj, n1, n2, v)
925 integer(I4B),
intent(in) :: itemno
926 character(len=*),
intent(in) :: keyword
927 logical,
intent(inout) :: found
929 character(len=LINELENGTH) :: text
932 real(DP),
pointer :: bndElem => null()
942 select case (keyword)
944 ierr = this%apt_check_valid(itemno)
948 call this%parser%GetString(text)
950 bndelem => this%concrain(itemno)
952 this%packName,
'BND', this%tsManager, &
953 this%iprpak,
'RAINFALL')
955 ierr = this%apt_check_valid(itemno)
959 call this%parser%GetString(text)
961 bndelem => this%concevap(itemno)
963 this%packName,
'BND', this%tsManager, &
964 this%iprpak,
'EVAPORATION')
966 ierr = this%apt_check_valid(itemno)
970 call this%parser%GetString(text)
972 bndelem => this%concroff(itemno)
974 this%packName,
'BND', this%tsManager, &
975 this%iprpak,
'RUNOFF')
977 ierr = this%apt_check_valid(itemno)
981 call this%parser%GetString(text)
983 bndelem => this%conciflw(itemno)
985 this%packName,
'BND', this%tsManager, &
986 this%iprpak,
'INFLOW')
This module contains the base boundary package.
class(bndtype) function, pointer, public getbndfromlist(list, idx)
Get boundary from package list.
This module contains simulation constants.
integer(i4b), parameter linelength
maximum length of a standard line
real(dp), parameter dzero
real constant zero
integer(i4b), parameter lenbudtxt
maximum length of a budget component names
real(dp), parameter done
real constant 1
subroutine sft_solve(this)
Add terms specific to sft to the explicit sft solve.
subroutine sft_iflw_term(this, ientry, n1, n2, rrate, rhsval, hcofval)
Inflow Term.
subroutine allocate_scalars(this)
Allocate scalars specific to the streamflow energy transport (SFE) package.
character(len= *), parameter flowtype
subroutine sft_outf_term(this, ientry, n1, n2, rrate, rhsval, hcofval)
Outflow term.
subroutine sft_roff_term(this, ientry, n1, n2, rrate, rhsval, hcofval)
Runoff term.
subroutine find_sft_package(this)
Find corresponding sft package.
subroutine sft_bd_obs(this, obstypeid, jj, v, found)
Calculate observation value and pass it back to APT.
subroutine sft_rp_obs(this, obsrv, found)
Process package specific obs.
subroutine sft_da(this)
Deallocate memory.
subroutine sft_fill_budobj(this, idx, x, flowja, ccratin, ccratout)
Copy flow terms into thisbudobj.
subroutine sft_set_stressperiod(this, itemno, keyword, found)
Sets the stress period attributes for keyword use.
subroutine sft_fc_expanded(this, rhs, ia, idxglo, matrix_sln)
Add matrix terms related to SFT.
subroutine, public sft_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, fmi, eqnsclfac, dvt, dvu, dvua)
Create a new sft package.
character(len= *), parameter ftype
subroutine sft_setup_budobj(this, idx)
Set up the budget object that stores all the sft flows.
integer(i4b) function sft_get_nbudterms(this)
Function to return the number of budget terms just for this package.
subroutine sft_evap_term(this, ientry, n1, n2, rrate, rhsval, hcofval)
Evaporative term.
subroutine sft_allocate_arrays(this)
Allocate arrays specific to the streamflow energy transport (SFE) package.
subroutine sft_df_obs(this)
Observations.
subroutine sft_rain_term(this, ientry, n1, n2, rrate, rhsval, hcofval)
Rain term.
This module defines variable data types.
This module contains the derived types ObserveType and ObsDataType.
This module contains the SFR package methods.
This module contains simulation methods.
subroutine, public store_error(msg, terminate)
Store an error message.
subroutine, public read_value_or_time_series_adv(textInput, ii, jj, bndElem, pkgName, auxOrBnd, tsManager, iprpak, varName)
Call this subroutine from advanced packages to define timeseries link for a variable (varName).
subroutine, public apt_process_obsid(obsrv, dis, inunitobs, iout)
Process observation IDs for an advanced package.
subroutine, public apt_process_obsid12(obsrv, dis, inunitobs, iout)
Process observation IDs for a package.