MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
gwtsftmodule Module Reference

Data Types

type  gwtsfttype
 

Functions/Subroutines

subroutine, public sft_create (packobj, id, ibcnum, inunit, iout, namemodel, pakname, fmi, eqnsclfac, dvt, dvu, dvua)
 Create a new sft package. More...
 
subroutine find_sft_package (this)
 Find corresponding sft package. More...
 
subroutine sft_fc_expanded (this, rhs, ia, idxglo, matrix_sln)
 Add matrix terms related to SFT. More...
 
subroutine sft_solve (this)
 Add terms specific to sft to the explicit sft solve. More...
 
integer(i4b) function sft_get_nbudterms (this)
 Function to return the number of budget terms just for this package. More...
 
subroutine sft_setup_budobj (this, idx)
 Set up the budget object that stores all the sft flows. More...
 
subroutine sft_fill_budobj (this, idx, x, flowja, ccratin, ccratout)
 Copy flow terms into thisbudobj. More...
 
subroutine allocate_scalars (this)
 Allocate scalars specific to the streamflow energy transport (SFE) package. More...
 
subroutine sft_allocate_arrays (this)
 Allocate arrays specific to the streamflow energy transport (SFE) package. More...
 
subroutine sft_da (this)
 Deallocate memory. More...
 
subroutine sft_rain_term (this, ientry, n1, n2, rrate, rhsval, hcofval)
 Rain term. More...
 
subroutine sft_evap_term (this, ientry, n1, n2, rrate, rhsval, hcofval)
 Evaporative term. More...
 
subroutine sft_roff_term (this, ientry, n1, n2, rrate, rhsval, hcofval)
 Runoff term. More...
 
subroutine sft_iflw_term (this, ientry, n1, n2, rrate, rhsval, hcofval)
 Inflow Term. More...
 
subroutine sft_outf_term (this, ientry, n1, n2, rrate, rhsval, hcofval)
 Outflow term. More...
 
subroutine sft_df_obs (this)
 Observations. More...
 
subroutine sft_rp_obs (this, obsrv, found)
 Process package specific obs. More...
 
subroutine sft_bd_obs (this, obstypeid, jj, v, found)
 Calculate observation value and pass it back to APT. More...
 
subroutine sft_set_stressperiod (this, itemno, keyword, found)
 Sets the stress period attributes for keyword use. More...
 

Variables

character(len= *), parameter ftype = 'SFT'
 
character(len= *), parameter flowtype = 'SFR'
 
character(len=16) text = ' SFT'
 

Function/Subroutine Documentation

◆ allocate_scalars()

subroutine gwtsftmodule::allocate_scalars ( class(gwtsfttype this)

Definition at line 577 of file gwt-sft.f90.

578  ! -- modules
580  ! -- dummy
581  class(GwtSftType) :: this
582  ! -- local
583  !
584  ! -- allocate scalars in TspAptType
585  call this%TspAptType%allocate_scalars()
586  !
587  ! -- Allocate
588  call mem_allocate(this%idxbudrain, 'IDXBUDRAIN', this%memoryPath)
589  call mem_allocate(this%idxbudevap, 'IDXBUDEVAP', this%memoryPath)
590  call mem_allocate(this%idxbudroff, 'IDXBUDROFF', this%memoryPath)
591  call mem_allocate(this%idxbudiflw, 'IDXBUDIFLW', this%memoryPath)
592  call mem_allocate(this%idxbudoutf, 'IDXBUDOUTF', this%memoryPath)
593  !
594  ! -- Initialize
595  this%idxbudrain = 0
596  this%idxbudevap = 0
597  this%idxbudroff = 0
598  this%idxbudiflw = 0
599  this%idxbudoutf = 0
600  !
601  ! -- Return
602  return

◆ find_sft_package()

subroutine gwtsftmodule::find_sft_package ( class(gwtsfttype this)

Definition at line 152 of file gwt-sft.f90.

153  ! -- modules
155  ! -- dummy
156  class(GwtSftType) :: this
157  ! -- local
158  character(len=LINELENGTH) :: errmsg
159  class(BndType), pointer :: packobj
160  integer(I4B) :: ip, icount
161  integer(I4B) :: nbudterm
162  logical :: found
163  !
164  ! -- Initialize found to false, and error later if flow package cannot
165  ! be found
166  found = .false.
167  !
168  ! -- If user is specifying flows in a binary budget file, then set up
169  ! the budget file reader, otherwise set a pointer to the flow package
170  ! budobj
171  if (this%fmi%flows_from_file) then
172  call this%fmi%set_aptbudobj_pointer(this%flowpackagename, this%flowbudptr)
173  if (associated(this%flowbudptr)) found = .true.
174  !
175  else
176  if (associated(this%fmi%gwfbndlist)) then
177  ! -- Look through gwfbndlist for a flow package with the same name as
178  ! this transport package name
179  do ip = 1, this%fmi%gwfbndlist%Count()
180  packobj => getbndfromlist(this%fmi%gwfbndlist, ip)
181  if (packobj%packName == this%flowpackagename) then
182  found = .true.
183  !
184  ! -- store BndType pointer to packobj, and then
185  ! use the select type to point to the budobj in flow package
186  this%flowpackagebnd => packobj
187  select type (packobj)
188  type is (sfrtype)
189  this%flowbudptr => packobj%budobj
190  end select
191  end if
192  if (found) exit
193  end do
194  end if
195  end if
196  !
197  ! -- error if flow package not found
198  if (.not. found) then
199  write (errmsg, '(a)') 'Could not find flow package with name '&
200  &//trim(adjustl(this%flowpackagename))//'.'
201  call store_error(errmsg)
202  call this%parser%StoreErrorUnit()
203  end if
204  !
205  ! -- allocate space for idxbudssm, which indicates whether this is a
206  ! special budget term or one that is a general source and sink
207  nbudterm = this%flowbudptr%nbudterm
208  call mem_allocate(this%idxbudssm, nbudterm, 'IDXBUDSSM', this%memoryPath)
209  !
210  ! -- Process budget terms and identify special budget terms
211  write (this%iout, '(/, a, a)') &
212  'PROCESSING '//ftype//' INFORMATION FOR ', this%packName
213  write (this%iout, '(a)') ' IDENTIFYING FLOW TERMS IN '//flowtype//' PACKAGE'
214  write (this%iout, '(a, i0)') &
215  ' NUMBER OF '//flowtype//' = ', this%flowbudptr%ncv
216  icount = 1
217  do ip = 1, this%flowbudptr%nbudterm
218  select case (trim(adjustl(this%flowbudptr%budterm(ip)%flowtype)))
219  case ('FLOW-JA-FACE')
220  this%idxbudfjf = ip
221  this%idxbudssm(ip) = 0
222  case ('GWF')
223  this%idxbudgwf = ip
224  this%idxbudssm(ip) = 0
225  case ('STORAGE')
226  this%idxbudsto = ip
227  this%idxbudssm(ip) = 0
228  case ('RAINFALL')
229  this%idxbudrain = ip
230  this%idxbudssm(ip) = 0
231  case ('EVAPORATION')
232  this%idxbudevap = ip
233  this%idxbudssm(ip) = 0
234  case ('RUNOFF')
235  this%idxbudroff = ip
236  this%idxbudssm(ip) = 0
237  case ('EXT-INFLOW')
238  this%idxbudiflw = ip
239  this%idxbudssm(ip) = 0
240  case ('EXT-OUTFLOW')
241  this%idxbudoutf = ip
242  this%idxbudssm(ip) = 0
243  case ('TO-MVR')
244  this%idxbudtmvr = ip
245  this%idxbudssm(ip) = 0
246  case ('FROM-MVR')
247  this%idxbudfmvr = ip
248  this%idxbudssm(ip) = 0
249  case ('AUXILIARY')
250  this%idxbudaux = ip
251  this%idxbudssm(ip) = 0
252  case default
253  !
254  ! -- set idxbudssm equal to a column index for where the concentrations
255  ! are stored in the concbud(nbudssm, ncv) array
256  this%idxbudssm(ip) = icount
257  icount = icount + 1
258  end select
259  write (this%iout, '(a, i0, " = ", a,/, a, i0)') &
260  ' TERM ', ip, trim(adjustl(this%flowbudptr%budterm(ip)%flowtype)), &
261  ' MAX NO. OF ENTRIES = ', this%flowbudptr%budterm(ip)%maxlist
262  end do
263  write (this%iout, '(a, //)') 'DONE PROCESSING '//ftype//' INFORMATION'
264  !
265  ! -- Return
266  return
Here is the call graph for this function:

◆ sft_allocate_arrays()

subroutine gwtsftmodule::sft_allocate_arrays ( class(gwtsfttype), intent(inout)  this)

Definition at line 608 of file gwt-sft.f90.

609  ! -- modules
611  ! -- dummy
612  class(GwtSftType), intent(inout) :: this
613  ! -- local
614  integer(I4B) :: n
615  !
616  ! -- time series
617  call mem_allocate(this%concrain, this%ncv, 'CONCRAIN', this%memoryPath)
618  call mem_allocate(this%concevap, this%ncv, 'CONCEVAP', this%memoryPath)
619  call mem_allocate(this%concroff, this%ncv, 'CONCROFF', this%memoryPath)
620  call mem_allocate(this%conciflw, this%ncv, 'CONCIFLW', this%memoryPath)
621  !
622  ! -- call standard TspAptType allocate arrays
623  call this%TspAptType%apt_allocate_arrays()
624  !
625  ! -- Initialize
626  do n = 1, this%ncv
627  this%concrain(n) = dzero
628  this%concevap(n) = dzero
629  this%concroff(n) = dzero
630  this%conciflw(n) = dzero
631  end do
632  !
633  ! -- Return
634  return

◆ sft_bd_obs()

subroutine gwtsftmodule::sft_bd_obs ( class(gwtsfttype), intent(inout)  this,
character(len=*), intent(in)  obstypeid,
integer(i4b), intent(in)  jj,
real(dp), intent(inout)  v,
logical, intent(inout)  found 
)

Definition at line 933 of file gwt-sft.f90.

934  ! -- dummy
935  class(GwtSftType), intent(inout) :: this
936  character(len=*), intent(in) :: obstypeid
937  real(DP), intent(inout) :: v
938  integer(I4B), intent(in) :: jj
939  logical, intent(inout) :: found
940  ! -- local
941  integer(I4B) :: n1, n2
942  !
943  found = .true.
944  select case (obstypeid)
945  case ('RAINFALL')
946  if (this%iboundpak(jj) /= 0) then
947  call this%sft_rain_term(jj, n1, n2, v)
948  end if
949  case ('EVAPORATION')
950  if (this%iboundpak(jj) /= 0) then
951  call this%sft_evap_term(jj, n1, n2, v)
952  end if
953  case ('RUNOFF')
954  if (this%iboundpak(jj) /= 0) then
955  call this%sft_roff_term(jj, n1, n2, v)
956  end if
957  case ('EXT-INFLOW')
958  if (this%iboundpak(jj) /= 0) then
959  call this%sft_iflw_term(jj, n1, n2, v)
960  end if
961  case ('EXT-OUTFLOW')
962  if (this%iboundpak(jj) /= 0) then
963  call this%sft_outf_term(jj, n1, n2, v)
964  end if
965  case default
966  found = .false.
967  end select
968  !
969  ! -- Return
970  return

◆ sft_create()

subroutine, public gwtsftmodule::sft_create ( class(bndtype), pointer  packobj,
integer(i4b), intent(in)  id,
integer(i4b), intent(in)  ibcnum,
integer(i4b), intent(in)  inunit,
integer(i4b), intent(in)  iout,
character(len=*), intent(in)  namemodel,
character(len=*), intent(in)  pakname,
type(tspfmitype), pointer  fmi,
real(dp), intent(in), pointer  eqnsclfac,
character(len=*), intent(in)  dvt,
character(len=*), intent(in)  dvu,
character(len=*), intent(in)  dvua 
)
Parameters
[in]eqnsclfacgoverning equation scale factor
[in]dvtFor GWT, set to "CONCENTRATION" in TspAptType
[in]dvuFor GWT, set to "mass" in TspAptType
[in]dvuaFor GWT, set to "M" in TspAptType

Definition at line 94 of file gwt-sft.f90.

96  ! -- dummy
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
104  type(TspFmiType), pointer :: fmi
105  real(DP), intent(in), pointer :: eqnsclfac !< governing equation scale factor
106  character(len=*), intent(in) :: dvt !< For GWT, set to "CONCENTRATION" in TspAptType
107  character(len=*), intent(in) :: dvu !< For GWT, set to "mass" in TspAptType
108  character(len=*), intent(in) :: dvua !< For GWT, set to "M" in TspAptType
109  ! -- local
110  type(GwtSftType), pointer :: sftobj
111  !
112  ! -- allocate the object and assign values to object variables
113  allocate (sftobj)
114  packobj => sftobj
115  !
116  ! -- create name and memory path
117  call packobj%set_names(ibcnum, namemodel, pakname, ftype)
118  packobj%text = text
119  !
120  ! -- allocate scalars
121  call sftobj%allocate_scalars()
122  !
123  ! -- initialize package
124  call packobj%pack_initialize()
125  !
126  packobj%inunit = inunit
127  packobj%iout = iout
128  packobj%id = id
129  packobj%ibcnum = ibcnum
130  packobj%ncolbnd = 1
131  packobj%iscloc = 1
132  !
133  ! -- Store pointer to flow model interface. When the GwfGwt exchange is
134  ! created, it sets fmi%bndlist so that the GWT model has access to all
135  ! the flow packages
136  sftobj%fmi => fmi
137  !
138  ! -- Store pointer to governing equation scale factor
139  sftobj%eqnsclfac => eqnsclfac
140  !
141  ! -- Set labels that will be used in generalized APT class
142  sftobj%depvartype = dvt
143  sftobj%depvarunit = dvu
144  sftobj%depvarunitabbrev = dvua
145  !
146  ! -- Return
147  return
Here is the caller graph for this function:

◆ sft_da()

subroutine gwtsftmodule::sft_da ( class(gwtsfttype this)

Definition at line 639 of file gwt-sft.f90.

640  ! -- modules
642  ! -- dummy
643  class(GwtSftType) :: this
644  ! -- local
645  !
646  ! -- deallocate scalars
647  call mem_deallocate(this%idxbudrain)
648  call mem_deallocate(this%idxbudevap)
649  call mem_deallocate(this%idxbudroff)
650  call mem_deallocate(this%idxbudiflw)
651  call mem_deallocate(this%idxbudoutf)
652  !
653  ! -- deallocate time series
654  call mem_deallocate(this%concrain)
655  call mem_deallocate(this%concevap)
656  call mem_deallocate(this%concroff)
657  call mem_deallocate(this%conciflw)
658  !
659  ! -- deallocate scalars in TspAptType
660  call this%TspAptType%bnd_da()
661  !
662  ! -- Return
663  return

◆ sft_df_obs()

subroutine gwtsftmodule::sft_df_obs ( class(gwtsfttype this)

Store the observation type supported by the APT package and override BndTypebnd_df_obs

Definition at line 827 of file gwt-sft.f90.

828  ! -- modules
829  ! -- dummy
830  class(GwtSftType) :: this
831  ! -- local
832  integer(I4B) :: indx
833  !
834  ! -- Store obs type and assign procedure pointer
835  ! for concentration observation type.
836  call this%obs%StoreObsType('concentration', .false., indx)
837  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
838  !
839  ! -- Store obs type and assign procedure pointer
840  ! for flow between reaches.
841  call this%obs%StoreObsType('flow-ja-face', .true., indx)
842  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid12
843  !
844  ! -- Store obs type and assign procedure pointer
845  ! for from-mvr observation type.
846  call this%obs%StoreObsType('from-mvr', .true., indx)
847  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
848  !
849  ! -- Store obs type and assign procedure pointer
850  ! for to-mvr observation type.
851  call this%obs%StoreObsType('to-mvr', .true., indx)
852  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
853  !
854  ! -- Store obs type and assign procedure pointer
855  ! for storage observation type.
856  call this%obs%StoreObsType('storage', .true., indx)
857  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
858  !
859  ! -- Store obs type and assign procedure pointer
860  ! for constant observation type.
861  call this%obs%StoreObsType('constant', .true., indx)
862  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
863  !
864  ! -- Store obs type and assign procedure pointer
865  ! for observation type: sft
866  call this%obs%StoreObsType('sft', .true., indx)
867  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
868  !
869  ! -- Store obs type and assign procedure pointer
870  ! for rainfall observation type.
871  call this%obs%StoreObsType('rainfall', .true., indx)
872  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
873  !
874  ! -- Store obs type and assign procedure pointer
875  ! for evaporation observation type.
876  call this%obs%StoreObsType('evaporation', .true., indx)
877  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
878  !
879  ! -- Store obs type and assign procedure pointer
880  ! for runoff observation type.
881  call this%obs%StoreObsType('runoff', .true., indx)
882  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
883  !
884  ! -- Store obs type and assign procedure pointer
885  ! for inflow observation type.
886  call this%obs%StoreObsType('ext-inflow', .true., indx)
887  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
888  !
889  ! -- Store obs type and assign procedure pointer
890  ! for ext-outflow observation type.
891  call this%obs%StoreObsType('ext-outflow', .true., indx)
892  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
893  !
894  ! -- Return
895  return
Here is the call graph for this function:

◆ sft_evap_term()

subroutine gwtsftmodule::sft_evap_term ( class(gwtsfttype this,
integer(i4b), intent(in)  ientry,
integer(i4b), intent(inout)  n1,
integer(i4b), intent(inout)  n2,
real(dp), intent(inout), optional  rrate,
real(dp), intent(inout), optional  rhsval,
real(dp), intent(inout), optional  hcofval 
)

Definition at line 696 of file gwt-sft.f90.

698  ! -- dummy
699  class(GwtSftType) :: this
700  integer(I4B), intent(in) :: ientry
701  integer(I4B), intent(inout) :: n1
702  integer(I4B), intent(inout) :: n2
703  real(DP), intent(inout), optional :: rrate
704  real(DP), intent(inout), optional :: rhsval
705  real(DP), intent(inout), optional :: hcofval
706  ! -- local
707  real(DP) :: qbnd
708  real(DP) :: ctmp
709  real(DP) :: omega
710  !
711  n1 = this%flowbudptr%budterm(this%idxbudevap)%id1(ientry)
712  n2 = this%flowbudptr%budterm(this%idxbudevap)%id2(ientry)
713  ! -- note that qbnd is negative for evap
714  qbnd = this%flowbudptr%budterm(this%idxbudevap)%flow(ientry)
715  ctmp = this%concevap(n1)
716  if (this%xnewpak(n1) < ctmp) then
717  omega = done
718  else
719  omega = dzero
720  end if
721  if (present(rrate)) &
722  rrate = omega * qbnd * this%xnewpak(n1) + &
723  (done - omega) * qbnd * ctmp
724  if (present(rhsval)) rhsval = -(done - omega) * qbnd * ctmp
725  if (present(hcofval)) hcofval = omega * qbnd
726  !
727  ! -- Return
728  return

◆ sft_fc_expanded()

subroutine gwtsftmodule::sft_fc_expanded ( class(gwtsfttype this,
real(dp), dimension(:), intent(inout)  rhs,
integer(i4b), dimension(:), intent(in)  ia,
integer(i4b), dimension(:), intent(in)  idxglo,
class(matrixbasetype), pointer  matrix_sln 
)

This will be called from TspAptTypeapt_fc_expanded() in order to add matrix terms specifically for SFT

Definition at line 274 of file gwt-sft.f90.

275  ! -- modules
276  ! -- dummy
277  class(GwtSftType) :: this
278  real(DP), dimension(:), intent(inout) :: rhs
279  integer(I4B), dimension(:), intent(in) :: ia
280  integer(I4B), dimension(:), intent(in) :: idxglo
281  class(MatrixBaseType), pointer :: matrix_sln
282  ! -- local
283  integer(I4B) :: j, n1, n2
284  integer(I4B) :: iloc
285  integer(I4B) :: iposd
286  real(DP) :: rrate
287  real(DP) :: rhsval
288  real(DP) :: hcofval
289  !
290  ! -- add rainfall contribution
291  if (this%idxbudrain /= 0) then
292  do j = 1, this%flowbudptr%budterm(this%idxbudrain)%nlist
293  call this%sft_rain_term(j, n1, n2, rrate, rhsval, hcofval)
294  iloc = this%idxlocnode(n1)
295  iposd = this%idxpakdiag(n1)
296  call matrix_sln%add_value_pos(iposd, hcofval)
297  rhs(iloc) = rhs(iloc) + rhsval
298  end do
299  end if
300  !
301  ! -- add evaporation contribution
302  if (this%idxbudevap /= 0) then
303  do j = 1, this%flowbudptr%budterm(this%idxbudevap)%nlist
304  call this%sft_evap_term(j, n1, n2, rrate, rhsval, hcofval)
305  iloc = this%idxlocnode(n1)
306  iposd = this%idxpakdiag(n1)
307  call matrix_sln%add_value_pos(iposd, hcofval)
308  rhs(iloc) = rhs(iloc) + rhsval
309  end do
310  end if
311  !
312  ! -- add runoff contribution
313  if (this%idxbudroff /= 0) then
314  do j = 1, this%flowbudptr%budterm(this%idxbudroff)%nlist
315  call this%sft_roff_term(j, n1, n2, rrate, rhsval, hcofval)
316  iloc = this%idxlocnode(n1)
317  iposd = this%idxpakdiag(n1)
318  call matrix_sln%add_value_pos(iposd, hcofval)
319  rhs(iloc) = rhs(iloc) + rhsval
320  end do
321  end if
322  !
323  ! -- add inflow contribution
324  if (this%idxbudiflw /= 0) then
325  do j = 1, this%flowbudptr%budterm(this%idxbudiflw)%nlist
326  call this%sft_iflw_term(j, n1, n2, rrate, rhsval, hcofval)
327  iloc = this%idxlocnode(n1)
328  iposd = this%idxpakdiag(n1)
329  call matrix_sln%add_value_pos(iposd, hcofval)
330  rhs(iloc) = rhs(iloc) + rhsval
331  end do
332  end if
333  !
334  ! -- add outflow contribution
335  if (this%idxbudoutf /= 0) then
336  do j = 1, this%flowbudptr%budterm(this%idxbudoutf)%nlist
337  call this%sft_outf_term(j, n1, n2, rrate, rhsval, hcofval)
338  iloc = this%idxlocnode(n1)
339  iposd = this%idxpakdiag(n1)
340  call matrix_sln%add_value_pos(iposd, hcofval)
341  rhs(iloc) = rhs(iloc) + rhsval
342  end do
343  end if
344  !
345  ! -- Return
346  return

◆ sft_fill_budobj()

subroutine gwtsftmodule::sft_fill_budobj ( class(gwtsfttype this,
integer(i4b), intent(inout)  idx,
real(dp), dimension(:), intent(in)  x,
real(dp), dimension(:), intent(inout), contiguous  flowja,
real(dp), intent(inout)  ccratin,
real(dp), intent(inout)  ccratout 
)

Definition at line 505 of file gwt-sft.f90.

506  ! -- modules
507  ! -- dummy
508  class(GwtSftType) :: this
509  integer(I4B), intent(inout) :: idx
510  real(DP), dimension(:), intent(in) :: x
511  real(DP), dimension(:), contiguous, intent(inout) :: flowja
512  real(DP), intent(inout) :: ccratin
513  real(DP), intent(inout) :: ccratout
514  ! -- local
515  integer(I4B) :: j, n1, n2
516  integer(I4B) :: nlist
517  real(DP) :: q
518  ! -- formats
519  !
520  ! -- RAIN
521  idx = idx + 1
522  nlist = this%flowbudptr%budterm(this%idxbudrain)%nlist
523  call this%budobj%budterm(idx)%reset(nlist)
524  do j = 1, nlist
525  call this%sft_rain_term(j, n1, n2, q)
526  call this%budobj%budterm(idx)%update_term(n1, n2, q)
527  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
528  end do
529  !
530  ! -- EVAPORATION
531  idx = idx + 1
532  nlist = this%flowbudptr%budterm(this%idxbudevap)%nlist
533  call this%budobj%budterm(idx)%reset(nlist)
534  do j = 1, nlist
535  call this%sft_evap_term(j, n1, n2, q)
536  call this%budobj%budterm(idx)%update_term(n1, n2, q)
537  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
538  end do
539  !
540  ! -- RUNOFF
541  idx = idx + 1
542  nlist = this%flowbudptr%budterm(this%idxbudroff)%nlist
543  call this%budobj%budterm(idx)%reset(nlist)
544  do j = 1, nlist
545  call this%sft_roff_term(j, n1, n2, q)
546  call this%budobj%budterm(idx)%update_term(n1, n2, q)
547  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
548  end do
549  !
550  ! -- EXT-INFLOW
551  idx = idx + 1
552  nlist = this%flowbudptr%budterm(this%idxbudiflw)%nlist
553  call this%budobj%budterm(idx)%reset(nlist)
554  do j = 1, nlist
555  call this%sft_iflw_term(j, n1, n2, q)
556  call this%budobj%budterm(idx)%update_term(n1, n2, q)
557  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
558  end do
559  !
560  ! -- EXT-OUTFLOW
561  idx = idx + 1
562  nlist = this%flowbudptr%budterm(this%idxbudoutf)%nlist
563  call this%budobj%budterm(idx)%reset(nlist)
564  do j = 1, nlist
565  call this%sft_outf_term(j, n1, n2, q)
566  call this%budobj%budterm(idx)%update_term(n1, n2, q)
567  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
568  end do
569  !
570  ! -- Return
571  return

◆ sft_get_nbudterms()

integer(i4b) function gwtsftmodule::sft_get_nbudterms ( class(gwtsfttype this)

This overrides a function in the parent class.

Definition at line 407 of file gwt-sft.f90.

408  ! -- modules
409  ! -- dummy
410  class(GwtSftType) :: this
411  ! -- return
412  integer(I4B) :: nbudterms
413  ! -- local
414  !
415  ! -- Number of budget terms is 5
416  nbudterms = 5
417  !
418  ! -- Return
419  return

◆ sft_iflw_term()

subroutine gwtsftmodule::sft_iflw_term ( class(gwtsfttype this,
integer(i4b), intent(in)  ientry,
integer(i4b), intent(inout)  n1,
integer(i4b), intent(inout)  n2,
real(dp), intent(inout), optional  rrate,
real(dp), intent(inout), optional  rhsval,
real(dp), intent(inout), optional  hcofval 
)

Accounts for mass added via streamflow entering into a stream channel; for example, energy entering the model domain via a specified flow in a stream channel.

Definition at line 765 of file gwt-sft.f90.

767  ! -- dummy
768  class(GwtSftType) :: this
769  integer(I4B), intent(in) :: ientry
770  integer(I4B), intent(inout) :: n1
771  integer(I4B), intent(inout) :: n2
772  real(DP), intent(inout), optional :: rrate
773  real(DP), intent(inout), optional :: rhsval
774  real(DP), intent(inout), optional :: hcofval
775  ! -- local
776  real(DP) :: qbnd
777  real(DP) :: ctmp
778  !
779  n1 = this%flowbudptr%budterm(this%idxbudiflw)%id1(ientry)
780  n2 = this%flowbudptr%budterm(this%idxbudiflw)%id2(ientry)
781  qbnd = this%flowbudptr%budterm(this%idxbudiflw)%flow(ientry)
782  ctmp = this%conciflw(n1)
783  if (present(rrate)) rrate = ctmp * qbnd
784  if (present(rhsval)) rhsval = -rrate
785  if (present(hcofval)) hcofval = dzero
786  !
787  ! -- Return
788  return

◆ sft_outf_term()

subroutine gwtsftmodule::sft_outf_term ( class(gwtsfttype this,
integer(i4b), intent(in)  ientry,
integer(i4b), intent(inout)  n1,
integer(i4b), intent(inout)  n2,
real(dp), intent(inout), optional  rrate,
real(dp), intent(inout), optional  rhsval,
real(dp), intent(inout), optional  hcofval 
)

Accounts for the mass leaving a stream channel; for example, mass exiting the model domain via a flow in a stream channel flowing out of the active domain.

Definition at line 796 of file gwt-sft.f90.

798  ! -- dummy
799  class(GwtSftType) :: this
800  integer(I4B), intent(in) :: ientry
801  integer(I4B), intent(inout) :: n1
802  integer(I4B), intent(inout) :: n2
803  real(DP), intent(inout), optional :: rrate
804  real(DP), intent(inout), optional :: rhsval
805  real(DP), intent(inout), optional :: hcofval
806  ! -- local
807  real(DP) :: qbnd
808  real(DP) :: ctmp
809  !
810  n1 = this%flowbudptr%budterm(this%idxbudoutf)%id1(ientry)
811  n2 = this%flowbudptr%budterm(this%idxbudoutf)%id2(ientry)
812  qbnd = this%flowbudptr%budterm(this%idxbudoutf)%flow(ientry)
813  ctmp = this%xnewpak(n1)
814  if (present(rrate)) rrate = ctmp * qbnd
815  if (present(rhsval)) rhsval = dzero
816  if (present(hcofval)) hcofval = qbnd
817  !
818  ! -- Return
819  return

◆ sft_rain_term()

subroutine gwtsftmodule::sft_rain_term ( class(gwtsfttype this,
integer(i4b), intent(in)  ientry,
integer(i4b), intent(inout)  n1,
integer(i4b), intent(inout)  n2,
real(dp), intent(inout), optional  rrate,
real(dp), intent(inout), optional  rhsval,
real(dp), intent(inout), optional  hcofval 
)

Definition at line 668 of file gwt-sft.f90.

670  ! -- dummy
671  class(GwtSftType) :: this
672  integer(I4B), intent(in) :: ientry
673  integer(I4B), intent(inout) :: n1
674  integer(I4B), intent(inout) :: n2
675  real(DP), intent(inout), optional :: rrate
676  real(DP), intent(inout), optional :: rhsval
677  real(DP), intent(inout), optional :: hcofval
678  ! -- local
679  real(DP) :: qbnd
680  real(DP) :: ctmp
681  !
682  n1 = this%flowbudptr%budterm(this%idxbudrain)%id1(ientry)
683  n2 = this%flowbudptr%budterm(this%idxbudrain)%id2(ientry)
684  qbnd = this%flowbudptr%budterm(this%idxbudrain)%flow(ientry)
685  ctmp = this%concrain(n1)
686  if (present(rrate)) rrate = ctmp * qbnd
687  if (present(rhsval)) rhsval = -rrate
688  if (present(hcofval)) hcofval = dzero
689  !
690  ! -- Return
691  return

◆ sft_roff_term()

subroutine gwtsftmodule::sft_roff_term ( class(gwtsfttype this,
integer(i4b), intent(in)  ientry,
integer(i4b), intent(inout)  n1,
integer(i4b), intent(inout)  n2,
real(dp), intent(inout), optional  rrate,
real(dp), intent(inout), optional  rhsval,
real(dp), intent(inout), optional  hcofval 
)

Definition at line 733 of file gwt-sft.f90.

735  ! -- dummy
736  class(GwtSftType) :: this
737  integer(I4B), intent(in) :: ientry
738  integer(I4B), intent(inout) :: n1
739  integer(I4B), intent(inout) :: n2
740  real(DP), intent(inout), optional :: rrate
741  real(DP), intent(inout), optional :: rhsval
742  real(DP), intent(inout), optional :: hcofval
743  ! -- local
744  real(DP) :: qbnd
745  real(DP) :: ctmp
746  !
747  n1 = this%flowbudptr%budterm(this%idxbudroff)%id1(ientry)
748  n2 = this%flowbudptr%budterm(this%idxbudroff)%id2(ientry)
749  qbnd = this%flowbudptr%budterm(this%idxbudroff)%flow(ientry)
750  ctmp = this%concroff(n1)
751  if (present(rrate)) rrate = ctmp * qbnd
752  if (present(rhsval)) rhsval = -rrate
753  if (present(hcofval)) hcofval = dzero
754  !
755  ! -- Return
756  return

◆ sft_rp_obs()

subroutine gwtsftmodule::sft_rp_obs ( class(gwtsfttype), intent(inout)  this,
type(observetype), intent(inout)  obsrv,
logical, intent(inout)  found 
)

Method to process specific observations for this package.

Parameters
[in,out]thispackage class
[in,out]obsrvobservation object
[in,out]foundindicate whether observation was found

Definition at line 902 of file gwt-sft.f90.

903  ! -- dummy
904  class(GwtSftType), intent(inout) :: this !< package class
905  type(ObserveType), intent(inout) :: obsrv !< observation object
906  logical, intent(inout) :: found !< indicate whether observation was found
907  ! -- local
908  !
909  found = .true.
910  select case (obsrv%ObsTypeId)
911  case ('RAINFALL')
912  call this%rp_obs_byfeature(obsrv)
913  case ('EVAPORATION')
914  call this%rp_obs_byfeature(obsrv)
915  case ('RUNOFF')
916  call this%rp_obs_byfeature(obsrv)
917  case ('EXT-INFLOW')
918  call this%rp_obs_byfeature(obsrv)
919  case ('EXT-OUTFLOW')
920  call this%rp_obs_byfeature(obsrv)
921  case ('TO-MVR')
922  call this%rp_obs_byfeature(obsrv)
923  case default
924  found = .false.
925  end select
926  !
927  ! -- Return
928  return

◆ sft_set_stressperiod()

subroutine gwtsftmodule::sft_set_stressperiod ( class(gwtsfttype), intent(inout)  this,
integer(i4b), intent(in)  itemno,
character(len=*), intent(in)  keyword,
logical, intent(inout)  found 
)

Definition at line 975 of file gwt-sft.f90.

977  ! -- dummy
978  class(GwtSftType), intent(inout) :: this
979  integer(I4B), intent(in) :: itemno
980  character(len=*), intent(in) :: keyword
981  logical, intent(inout) :: found
982  ! -- local
983  character(len=LINELENGTH) :: text
984  integer(I4B) :: ierr
985  integer(I4B) :: jj
986  real(DP), pointer :: bndElem => null()
987  ! -- formats
988  !
989  ! RAINFALL <rainfall>
990  ! EVAPORATION <evaporation>
991  ! RUNOFF <runoff>
992  ! INFLOW <inflow>
993  ! WITHDRAWAL <withdrawal>
994  !
995  found = .true.
996  select case (keyword)
997  case ('RAINFALL')
998  ierr = this%apt_check_valid(itemno)
999  if (ierr /= 0) then
1000  goto 999
1001  end if
1002  call this%parser%GetString(text)
1003  jj = 1
1004  bndelem => this%concrain(itemno)
1005  call read_value_or_time_series_adv(text, itemno, jj, bndelem, &
1006  this%packName, 'BND', this%tsManager, &
1007  this%iprpak, 'RAINFALL')
1008  case ('EVAPORATION')
1009  ierr = this%apt_check_valid(itemno)
1010  if (ierr /= 0) then
1011  goto 999
1012  end if
1013  call this%parser%GetString(text)
1014  jj = 1
1015  bndelem => this%concevap(itemno)
1016  call read_value_or_time_series_adv(text, itemno, jj, bndelem, &
1017  this%packName, 'BND', this%tsManager, &
1018  this%iprpak, 'EVAPORATION')
1019  case ('RUNOFF')
1020  ierr = this%apt_check_valid(itemno)
1021  if (ierr /= 0) then
1022  goto 999
1023  end if
1024  call this%parser%GetString(text)
1025  jj = 1
1026  bndelem => this%concroff(itemno)
1027  call read_value_or_time_series_adv(text, itemno, jj, bndelem, &
1028  this%packName, 'BND', this%tsManager, &
1029  this%iprpak, 'RUNOFF')
1030  case ('INFLOW')
1031  ierr = this%apt_check_valid(itemno)
1032  if (ierr /= 0) then
1033  goto 999
1034  end if
1035  call this%parser%GetString(text)
1036  jj = 1
1037  bndelem => this%conciflw(itemno)
1038  call read_value_or_time_series_adv(text, itemno, jj, bndelem, &
1039  this%packName, 'BND', this%tsManager, &
1040  this%iprpak, 'INFLOW')
1041  case default
1042  !
1043  ! -- keyword not recognized so return to caller with found = .false.
1044  found = .false.
1045  end select
1046  !
1047 999 continue
1048  !
1049  ! -- Return
1050  return
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).
Here is the call graph for this function:

◆ sft_setup_budobj()

subroutine gwtsftmodule::sft_setup_budobj ( class(gwtsfttype this,
integer(i4b), intent(inout)  idx 
)

Definition at line 424 of file gwt-sft.f90.

425  ! -- modules
426  use constantsmodule, only: lenbudtxt
427  ! -- dummy
428  class(GwtSftType) :: this
429  integer(I4B), intent(inout) :: idx
430  ! -- local
431  integer(I4B) :: maxlist, naux
432  character(len=LENBUDTXT) :: text
433  !
434  ! --
435  text = ' RAINFALL'
436  idx = idx + 1
437  maxlist = this%flowbudptr%budterm(this%idxbudrain)%maxlist
438  naux = 0
439  call this%budobj%budterm(idx)%initialize(text, &
440  this%name_model, &
441  this%packName, &
442  this%name_model, &
443  this%packName, &
444  maxlist, .false., .false., &
445  naux)
446  !
447  ! --
448  text = ' EVAPORATION'
449  idx = idx + 1
450  maxlist = this%flowbudptr%budterm(this%idxbudevap)%maxlist
451  naux = 0
452  call this%budobj%budterm(idx)%initialize(text, &
453  this%name_model, &
454  this%packName, &
455  this%name_model, &
456  this%packName, &
457  maxlist, .false., .false., &
458  naux)
459  !
460  ! --
461  text = ' RUNOFF'
462  idx = idx + 1
463  maxlist = this%flowbudptr%budterm(this%idxbudroff)%maxlist
464  naux = 0
465  call this%budobj%budterm(idx)%initialize(text, &
466  this%name_model, &
467  this%packName, &
468  this%name_model, &
469  this%packName, &
470  maxlist, .false., .false., &
471  naux)
472  !
473  ! --
474  text = ' EXT-INFLOW'
475  idx = idx + 1
476  maxlist = this%flowbudptr%budterm(this%idxbudiflw)%maxlist
477  naux = 0
478  call this%budobj%budterm(idx)%initialize(text, &
479  this%name_model, &
480  this%packName, &
481  this%name_model, &
482  this%packName, &
483  maxlist, .false., .false., &
484  naux)
485  !
486  ! --
487  text = ' EXT-OUTFLOW'
488  idx = idx + 1
489  maxlist = this%flowbudptr%budterm(this%idxbudoutf)%maxlist
490  naux = 0
491  call this%budobj%budterm(idx)%initialize(text, &
492  this%name_model, &
493  this%packName, &
494  this%name_model, &
495  this%packName, &
496  maxlist, .false., .false., &
497  naux)
498  !
499  ! -- return
500  return
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter lenbudtxt
maximum length of a budget component names
Definition: Constants.f90:36

◆ sft_solve()

subroutine gwtsftmodule::sft_solve ( class(gwtsfttype this)

Definition at line 351 of file gwt-sft.f90.

352  ! -- dummy
353  class(GwtSftType) :: this
354  ! -- local
355  integer(I4B) :: j
356  integer(I4B) :: n1, n2
357  real(DP) :: rrate
358  !
359  ! -- add rainfall contribution
360  if (this%idxbudrain /= 0) then
361  do j = 1, this%flowbudptr%budterm(this%idxbudrain)%nlist
362  call this%sft_rain_term(j, n1, n2, rrate)
363  this%dbuff(n1) = this%dbuff(n1) + rrate
364  end do
365  end if
366  !
367  ! -- add evaporation contribution
368  if (this%idxbudevap /= 0) then
369  do j = 1, this%flowbudptr%budterm(this%idxbudevap)%nlist
370  call this%sft_evap_term(j, n1, n2, rrate)
371  this%dbuff(n1) = this%dbuff(n1) + rrate
372  end do
373  end if
374  !
375  ! -- add runoff contribution
376  if (this%idxbudroff /= 0) then
377  do j = 1, this%flowbudptr%budterm(this%idxbudroff)%nlist
378  call this%sft_roff_term(j, n1, n2, rrate)
379  this%dbuff(n1) = this%dbuff(n1) + rrate
380  end do
381  end if
382  !
383  ! -- add inflow contribution
384  if (this%idxbudiflw /= 0) then
385  do j = 1, this%flowbudptr%budterm(this%idxbudiflw)%nlist
386  call this%sft_iflw_term(j, n1, n2, rrate)
387  this%dbuff(n1) = this%dbuff(n1) + rrate
388  end do
389  end if
390  !
391  ! -- add outflow contribution
392  if (this%idxbudoutf /= 0) then
393  do j = 1, this%flowbudptr%budterm(this%idxbudoutf)%nlist
394  call this%sft_outf_term(j, n1, n2, rrate)
395  this%dbuff(n1) = this%dbuff(n1) + rrate
396  end do
397  end if
398  !
399  ! -- Return
400  return

Variable Documentation

◆ flowtype

character(len=*), parameter gwtsftmodule::flowtype = 'SFR'

Definition at line 51 of file gwt-sft.f90.

51  character(len=*), parameter :: flowtype = 'SFR'

◆ ftype

character(len=*), parameter gwtsftmodule::ftype = 'SFT'

Definition at line 50 of file gwt-sft.f90.

50  character(len=*), parameter :: ftype = 'SFT'

◆ text

character(len=16) gwtsftmodule::text = ' SFT'

Definition at line 52 of file gwt-sft.f90.

52  character(len=16) :: text = ' SFT'