MODFLOW 6  version 6.7.0.dev0
USGS Modular Hydrologic Model
gwesfemodule Module Reference

Data Types

type  gwesfetype
 

Functions/Subroutines

subroutine, public sfe_create (packobj, id, ibcnum, inunit, iout, namemodel, pakname, fmi, eqnsclfac, gwecommon, dvt, dvu, dvua)
 Create a new sfe package. More...
 
subroutine find_sfe_package (this)
 Find corresponding sfe package. More...
 
subroutine sfe_fc_expanded (this, rhs, ia, idxglo, matrix_sln)
 Add matrix terms related to SFE. More...
 
subroutine sfe_solve (this)
 @ brief Add terms specific to sfr to the explicit sfe solve More...
 
integer(i4b) function sfe_get_nbudterms (this)
 Function to return the number of budget terms just for this package. More...
 
subroutine sfe_setup_budobj (this, idx)
 Set up the budget object that stores all the sfe flows. More...
 
subroutine sfe_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 sfe_allocate_arrays (this)
 Allocate arrays specific to the streamflow energy transport (SFE) package. More...
 
subroutine sfe_da (this)
 Deallocate memory. More...
 
subroutine sfe_rain_term (this, ientry, n1, n2, rrate, rhsval, hcofval)
 Rain term. More...
 
subroutine sfe_evap_term (this, ientry, n1, n2, rrate, rhsval, hcofval)
 Evaporative term. More...
 
subroutine sfe_roff_term (this, ientry, n1, n2, rrate, rhsval, hcofval)
 Runoff term. More...
 
subroutine sfe_iflw_term (this, ientry, n1, n2, rrate, rhsval, hcofval)
 Inflow Term. More...
 
subroutine sfe_outf_term (this, ientry, n1, n2, rrate, rhsval, hcofval)
 Outflow term. More...
 
subroutine sfe_df_obs (this)
 Observations. More...
 
subroutine sfe_rp_obs (this, obsrv, found)
 Process package specific obs. More...
 
subroutine sfe_bd_obs (this, obstypeid, jj, v, found)
 Calculate observation value and pass it back to APT. More...
 
subroutine sfe_set_stressperiod (this, itemno, keyword, found)
 Sets the stress period attributes for keyword use. More...
 
subroutine sfe_read_cvs (this)
 Read feature information for this advanced package. More...
 

Variables

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

Function/Subroutine Documentation

◆ allocate_scalars()

subroutine gwesfemodule::allocate_scalars ( class(gwesfetype this)
private

Definition at line 667 of file gwe-sfe.f90.

668  ! -- modules
670  ! -- dummy
671  class(GweSfeType) :: this
672  !
673  ! -- Allocate scalars in TspAptType
674  call this%TspAptType%allocate_scalars()
675  !
676  ! -- Allocate
677  call mem_allocate(this%idxbudrain, 'IDXBUDRAIN', this%memoryPath)
678  call mem_allocate(this%idxbudevap, 'IDXBUDEVAP', this%memoryPath)
679  call mem_allocate(this%idxbudroff, 'IDXBUDROFF', this%memoryPath)
680  call mem_allocate(this%idxbudiflw, 'IDXBUDIFLW', this%memoryPath)
681  call mem_allocate(this%idxbudoutf, 'IDXBUDOUTF', this%memoryPath)
682  call mem_allocate(this%idxbudsbcd, 'IDXBUDSBCD', this%memoryPath)
683  !
684  ! -- Initialize
685  this%idxbudrain = 0
686  this%idxbudevap = 0
687  this%idxbudroff = 0
688  this%idxbudiflw = 0
689  this%idxbudoutf = 0
690  this%idxbudsbcd = 0

◆ find_sfe_package()

subroutine gwesfemodule::find_sfe_package ( class(gwesfetype this)
private

Definition at line 165 of file gwe-sfe.f90.

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

◆ sfe_allocate_arrays()

subroutine gwesfemodule::sfe_allocate_arrays ( class(gwesfetype), intent(inout)  this)

Definition at line 696 of file gwe-sfe.f90.

697  ! -- modules
699  ! -- dummy
700  class(GweSfeType), intent(inout) :: this
701  ! -- local
702  integer(I4B) :: n
703  !
704  ! -- Time series
705  call mem_allocate(this%temprain, this%ncv, 'TEMPRAIN', this%memoryPath)
706  call mem_allocate(this%tempevap, this%ncv, 'TEMPEVAP', this%memoryPath)
707  call mem_allocate(this%temproff, this%ncv, 'TEMPROFF', this%memoryPath)
708  call mem_allocate(this%tempiflw, this%ncv, 'TEMPIFLW', this%memoryPath)
709  !
710  ! -- Call standard TspAptType allocate arrays
711  call this%TspAptType%apt_allocate_arrays()
712  !
713  ! -- Initialize
714  do n = 1, this%ncv
715  this%temprain(n) = dzero
716  this%tempevap(n) = dzero
717  this%temproff(n) = dzero
718  this%tempiflw(n) = dzero
719  end do

◆ sfe_bd_obs()

subroutine gwesfemodule::sfe_bd_obs ( class(gwesfetype), intent(inout)  this,
character(len=*), intent(in)  obstypeid,
integer(i4b), intent(in)  jj,
real(dp), intent(inout)  v,
logical, intent(inout)  found 
)
private

Definition at line 986 of file gwe-sfe.f90.

987  ! -- dummy
988  class(GweSfeType), intent(inout) :: this
989  character(len=*), intent(in) :: obstypeid
990  real(DP), intent(inout) :: v
991  integer(I4B), intent(in) :: jj
992  logical, intent(inout) :: found
993  ! -- local
994  integer(I4B) :: n1, n2
995  !
996  found = .true.
997  select case (obstypeid)
998  case ('RAINFALL')
999  if (this%iboundpak(jj) /= 0) then
1000  call this%sfe_rain_term(jj, n1, n2, v)
1001  end if
1002  case ('EVAPORATION')
1003  if (this%iboundpak(jj) /= 0) then
1004  call this%sfe_evap_term(jj, n1, n2, v)
1005  end if
1006  case ('RUNOFF')
1007  if (this%iboundpak(jj) /= 0) then
1008  call this%sfe_roff_term(jj, n1, n2, v)
1009  end if
1010  case ('EXT-INFLOW')
1011  if (this%iboundpak(jj) /= 0) then
1012  call this%sfe_iflw_term(jj, n1, n2, v)
1013  end if
1014  case ('EXT-OUTFLOW')
1015  if (this%iboundpak(jj) /= 0) then
1016  call this%sfe_outf_term(jj, n1, n2, v)
1017  end if
1018  case default
1019  found = .false.
1020  end select

◆ sfe_create()

subroutine, public gwesfemodule::sfe_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,
type(gweinputdatatype), intent(in), target  gwecommon,
character(len=*), intent(in)  dvt,
character(len=*), intent(in)  dvu,
character(len=*), intent(in)  dvua 
)
Parameters
[in]eqnsclfacGoverning equation scale factor
[in]gwecommonShared data container for use by multiple GWE packages
[in]dvtFor GWE, set to "TEMPERATURE" in TspAptType
[in]dvuFor GWE, set to "energy" in TspAptType
[in]dvuaFor GWE, set to "E" in TspAptType

Definition at line 104 of file gwe-sfe.f90.

106  ! -- dummy
107  class(BndType), pointer :: packobj
108  integer(I4B), intent(in) :: id
109  integer(I4B), intent(in) :: ibcnum
110  integer(I4B), intent(in) :: inunit
111  integer(I4B), intent(in) :: iout
112  character(len=*), intent(in) :: namemodel
113  character(len=*), intent(in) :: pakname
114  type(TspFmiType), pointer :: fmi
115  real(DP), intent(in), pointer :: eqnsclfac !< Governing equation scale factor
116  type(GweInputDataType), intent(in), target :: gwecommon !< Shared data container for use by multiple GWE packages
117  character(len=*), intent(in) :: dvt !< For GWE, set to "TEMPERATURE" in TspAptType
118  character(len=*), intent(in) :: dvu !< For GWE, set to "energy" in TspAptType
119  character(len=*), intent(in) :: dvua !< For GWE, set to "E" in TspAptType
120  ! -- local
121  type(GweSfeType), pointer :: sfeobj
122  !
123  ! -- Allocate the object and assign values to object variables
124  allocate (sfeobj)
125  packobj => sfeobj
126  !
127  ! -- Create name and memory path
128  call packobj%set_names(ibcnum, namemodel, pakname, ftype)
129  packobj%text = text
130  !
131  ! -- Allocate scalars
132  call sfeobj%allocate_scalars()
133  !
134  ! -- Initialize package
135  call packobj%pack_initialize()
136  !
137  packobj%inunit = inunit
138  packobj%iout = iout
139  packobj%id = id
140  packobj%ibcnum = ibcnum
141  packobj%ncolbnd = 1
142  packobj%iscloc = 1
143  !
144  ! -- Store pointer to flow model interface. When the GwfGwt exchange is
145  ! created, it sets fmi%bndlist so that the GWT model has access to all
146  ! the flow packages
147  sfeobj%fmi => fmi
148  !
149  ! -- Store pointer to governing equation scale factor
150  sfeobj%eqnsclfac => eqnsclfac
151  !
152  ! -- Store pointer to shared data module for accessing cpw, rhow
153  ! for the budget calculations, and for accessing the latent heat of
154  ! vaporization for evaporative cooling.
155  sfeobj%gwecommon => gwecommon
156  !
157  ! -- Set labels that will be used in generalized APT class
158  sfeobj%depvartype = dvt
159  sfeobj%depvarunit = dvu
160  sfeobj%depvarunitabbrev = dvua
Here is the caller graph for this function:

◆ sfe_da()

subroutine gwesfemodule::sfe_da ( class(gwesfetype this)

Definition at line 724 of file gwe-sfe.f90.

725  ! -- modules
727  ! -- dummy
728  class(GweSfeType) :: this
729  !
730  ! -- Deallocate scalars
731  call mem_deallocate(this%idxbudrain)
732  call mem_deallocate(this%idxbudevap)
733  call mem_deallocate(this%idxbudroff)
734  call mem_deallocate(this%idxbudiflw)
735  call mem_deallocate(this%idxbudoutf)
736  call mem_deallocate(this%idxbudsbcd)
737  !
738  ! -- Deallocate time series
739  call mem_deallocate(this%temprain)
740  call mem_deallocate(this%tempevap)
741  call mem_deallocate(this%temproff)
742  call mem_deallocate(this%tempiflw)
743  !
744  ! -- Deallocate arrays
745  call mem_deallocate(this%ktf)
746  call mem_deallocate(this%rfeatthk)
747  !
748  ! -- Deallocate scalars in TspAptType
749  call this%TspAptType%bnd_da()

◆ sfe_df_obs()

subroutine gwesfemodule::sfe_df_obs ( class(gwesfetype this)
private

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

Definition at line 886 of file gwe-sfe.f90.

887  ! -- modules
888  ! -- dummy
889  class(GweSfeType) :: this
890  ! -- local
891  integer(I4B) :: indx
892  !
893  ! -- Store obs type and assign procedure pointer
894  ! for temperature observation type.
895  call this%obs%StoreObsType('temperature', .false., indx)
896  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
897  !
898  ! -- Store obs type and assign procedure pointer
899  ! for flow between reaches.
900  call this%obs%StoreObsType('flow-ja-face', .true., indx)
901  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid12
902  !
903  ! -- Store obs type and assign procedure pointer
904  ! for from-mvr observation type.
905  call this%obs%StoreObsType('from-mvr', .true., indx)
906  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
907  !
908  ! -- Store obs type and assign procedure pointer
909  ! for to-mvr observation type.
910  call this%obs%StoreObsType('to-mvr', .true., indx)
911  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
912  !
913  ! -- Store obs type and assign procedure pointer
914  ! for storage observation type.
915  call this%obs%StoreObsType('storage', .true., indx)
916  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
917  !
918  ! -- Store obs type and assign procedure pointer
919  ! for constant observation type.
920  call this%obs%StoreObsType('constant', .true., indx)
921  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
922  !
923  ! -- Store obs type and assign procedure pointer
924  ! for observation type: sfe
925  call this%obs%StoreObsType('sfe', .true., indx)
926  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
927  !
928  ! -- Store obs type and assign procedure pointer
929  ! for rainfall observation type.
930  call this%obs%StoreObsType('rainfall', .true., indx)
931  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
932  !
933  ! -- Store obs type and assign procedure pointer
934  ! for evaporation observation type.
935  call this%obs%StoreObsType('evaporation', .true., indx)
936  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
937  !
938  ! -- Store obs type and assign procedure pointer
939  ! for runoff observation type.
940  call this%obs%StoreObsType('runoff', .true., indx)
941  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
942  !
943  ! -- Store obs type and assign procedure pointer
944  ! for inflow observation type.
945  call this%obs%StoreObsType('ext-inflow', .true., indx)
946  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
947  !
948  ! -- Store obs type and assign procedure pointer
949  ! for ext-outflow observation type.
950  call this%obs%StoreObsType('ext-outflow', .true., indx)
951  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
Here is the call graph for this function:

◆ sfe_evap_term()

subroutine gwesfemodule::sfe_evap_term ( class(gwesfetype 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 
)
private

Definition at line 778 of file gwe-sfe.f90.

779  ! -- dummy
780  class(GweSfeType) :: this
781  integer(I4B), intent(in) :: ientry
782  integer(I4B), intent(inout) :: n1
783  integer(I4B), intent(inout) :: n2
784  real(DP), intent(inout), optional :: rrate
785  real(DP), intent(inout), optional :: rhsval
786  real(DP), intent(inout), optional :: hcofval
787  ! -- local
788  real(DP) :: qbnd
789  real(DP) :: heatlat
790  !
791  n1 = this%flowbudptr%budterm(this%idxbudevap)%id1(ientry)
792  n2 = this%flowbudptr%budterm(this%idxbudevap)%id2(ientry)
793  ! -- note that qbnd is negative for evap
794  qbnd = this%flowbudptr%budterm(this%idxbudevap)%flow(ientry)
795  heatlat = this%gwecommon%gwerhow * this%gwecommon%gwelatheatvap
796  if (present(rrate)) rrate = qbnd * heatlat
797  !!if (present(rhsval)) rhsval = -rrate / this%eqnsclfac ! kluge note: divided by eqnsclfac for fc purposes because rrate is in terms of energy
798  if (present(rhsval)) rhsval = -rrate
799  if (present(hcofval)) hcofval = dzero

◆ sfe_fc_expanded()

subroutine gwesfemodule::sfe_fc_expanded ( class(gwesfetype 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 SFE

Definition at line 287 of file gwe-sfe.f90.

288  ! -- dummy
289  class(GweSfeType) :: this
290  real(DP), dimension(:), intent(inout) :: rhs
291  integer(I4B), dimension(:), intent(in) :: ia
292  integer(I4B), dimension(:), intent(in) :: idxglo
293  class(MatrixBaseType), pointer :: matrix_sln
294  ! -- local
295  integer(I4B) :: j, n, n1, n2
296  integer(I4B) :: iloc
297  integer(I4B) :: iposd, iposoffd
298  integer(I4B) :: ipossymd, ipossymoffd
299  integer(I4B) :: auxpos
300  real(DP) :: rrate
301  real(DP) :: rhsval
302  real(DP) :: hcofval
303  real(DP) :: ctherm
304  real(DP) :: wa !< wetted area
305  real(DP) :: ktf !< thermal conductivity of streambed material
306  real(DP) :: s !< thickness of conductive streambed material
307  !
308  ! -- Add rainfall contribution
309  if (this%idxbudrain /= 0) then
310  do j = 1, this%flowbudptr%budterm(this%idxbudrain)%nlist
311  call this%sfe_rain_term(j, n1, n2, rrate, rhsval, hcofval)
312  iloc = this%idxlocnode(n1)
313  iposd = this%idxpakdiag(n1)
314  call matrix_sln%add_value_pos(iposd, hcofval)
315  rhs(iloc) = rhs(iloc) + rhsval
316  end do
317  end if
318  !
319  ! -- Add evaporation contribution
320  if (this%idxbudevap /= 0) then
321  do j = 1, this%flowbudptr%budterm(this%idxbudevap)%nlist
322  call this%sfe_evap_term(j, n1, n2, rrate, rhsval, hcofval)
323  iloc = this%idxlocnode(n1)
324  iposd = this%idxpakdiag(n1)
325  call matrix_sln%add_value_pos(iposd, hcofval)
326  rhs(iloc) = rhs(iloc) + rhsval
327  end do
328  end if
329  !
330  ! -- Add runoff contribution
331  if (this%idxbudroff /= 0) then
332  do j = 1, this%flowbudptr%budterm(this%idxbudroff)%nlist
333  call this%sfe_roff_term(j, n1, n2, rrate, rhsval, hcofval)
334  iloc = this%idxlocnode(n1)
335  iposd = this%idxpakdiag(n1)
336  call matrix_sln%add_value_pos(iposd, hcofval)
337  rhs(iloc) = rhs(iloc) + rhsval
338  end do
339  end if
340  !
341  ! -- Add inflow contribution
342  if (this%idxbudiflw /= 0) then
343  do j = 1, this%flowbudptr%budterm(this%idxbudiflw)%nlist
344  call this%sfe_iflw_term(j, n1, n2, rrate, rhsval, hcofval)
345  iloc = this%idxlocnode(n1)
346  iposd = this%idxpakdiag(n1)
347  call matrix_sln%add_value_pos(iposd, hcofval)
348  rhs(iloc) = rhs(iloc) + rhsval
349  end do
350  end if
351  !
352  ! -- Add outflow contribution
353  if (this%idxbudoutf /= 0) then
354  do j = 1, this%flowbudptr%budterm(this%idxbudoutf)%nlist
355  call this%sfe_outf_term(j, n1, n2, rrate, rhsval, hcofval)
356  iloc = this%idxlocnode(n1)
357  iposd = this%idxpakdiag(n1)
358  call matrix_sln%add_value_pos(iposd, hcofval)
359  rhs(iloc) = rhs(iloc) + rhsval
360  end do
361  end if
362  !
363  ! -- Add streambed conduction contribution
364  do j = 1, this%flowbudptr%budterm(this%idxbudgwf)%nlist
365  !
366  ! -- Set n to feature number and process if active feature
367  n = this%flowbudptr%budterm(this%idxbudgwf)%id1(j)
368  if (this%iboundpak(n) /= 0) then
369  !
370  ! -- Set acoef and rhs to negative so they are relative to sfe and not gwe
371  auxpos = this%flowbudptr%budterm(this%idxbudgwf)%naux
372  wa = this%flowbudptr%budterm(this%idxbudgwf)%auxvar(auxpos, j)
373  ktf = this%ktf(n)
374  s = this%rfeatthk(n)
375  ctherm = ktf * wa / s
376  !
377  ! -- Add to sfe row
378  iposd = this%idxdglo(j)
379  iposoffd = this%idxoffdglo(j)
380  call matrix_sln%add_value_pos(iposd, -ctherm)
381  call matrix_sln%add_value_pos(iposoffd, ctherm)
382  !
383  ! -- Add to gwe row for sfe connection
384  ipossymd = this%idxsymdglo(j)
385  ipossymoffd = this%idxsymoffdglo(j)
386  call matrix_sln%add_value_pos(ipossymd, -ctherm)
387  call matrix_sln%add_value_pos(ipossymoffd, ctherm)
388  end if
389  end do

◆ sfe_fill_budobj()

subroutine gwesfemodule::sfe_fill_budobj ( class(gwesfetype 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 567 of file gwe-sfe.f90.

568  ! -- dummy
569  class(GweSfeType) :: this
570  integer(I4B), intent(inout) :: idx
571  real(DP), dimension(:), intent(in) :: x
572  real(DP), dimension(:), contiguous, intent(inout) :: flowja
573  real(DP), intent(inout) :: ccratin
574  real(DP), intent(inout) :: ccratout
575  ! -- local
576  integer(I4B) :: j, n1, n2
577  integer(I4B) :: nlist
578  integer(I4B) :: igwfnode
579  integer(I4B) :: idiag
580  integer(I4B) :: auxpos
581  real(DP) :: q
582  real(DP) :: ctherm
583  real(DP) :: wa !< wetted area
584  real(DP) :: ktf !< thermal conductivity of streambed material
585  real(DP) :: s !< thickness of conductive streambed materia
586  !
587  ! -- Rain
588  idx = idx + 1
589  nlist = this%flowbudptr%budterm(this%idxbudrain)%nlist
590  call this%budobj%budterm(idx)%reset(nlist)
591  do j = 1, nlist
592  call this%sfe_rain_term(j, n1, n2, q)
593  call this%budobj%budterm(idx)%update_term(n1, n2, q)
594  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
595  end do
596  !
597  ! -- Evaporation
598  idx = idx + 1
599  nlist = this%flowbudptr%budterm(this%idxbudevap)%nlist
600  call this%budobj%budterm(idx)%reset(nlist)
601  do j = 1, nlist
602  call this%sfe_evap_term(j, n1, n2, q)
603  call this%budobj%budterm(idx)%update_term(n1, n2, q)
604  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
605  end do
606  !
607  ! -- Runoff
608  idx = idx + 1
609  nlist = this%flowbudptr%budterm(this%idxbudroff)%nlist
610  call this%budobj%budterm(idx)%reset(nlist)
611  do j = 1, nlist
612  call this%sfe_roff_term(j, n1, n2, q)
613  call this%budobj%budterm(idx)%update_term(n1, n2, q)
614  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
615  end do
616  !
617  ! -- Ext-inflow
618  idx = idx + 1
619  nlist = this%flowbudptr%budterm(this%idxbudiflw)%nlist
620  call this%budobj%budterm(idx)%reset(nlist)
621  do j = 1, nlist
622  call this%sfe_iflw_term(j, n1, n2, q)
623  call this%budobj%budterm(idx)%update_term(n1, n2, q)
624  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
625  end do
626  !
627  ! -- Ext-outflow
628  idx = idx + 1
629  nlist = this%flowbudptr%budterm(this%idxbudoutf)%nlist
630  call this%budobj%budterm(idx)%reset(nlist)
631  do j = 1, nlist
632  call this%sfe_outf_term(j, n1, n2, q)
633  call this%budobj%budterm(idx)%update_term(n1, n2, q)
634  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
635  end do
636  !
637  ! -- Strmbd-cond
638  idx = idx + 1
639  call this%budobj%budterm(idx)%reset(this%maxbound)
640  do j = 1, this%flowbudptr%budterm(this%idxbudsbcd)%nlist
641  q = dzero
642  n1 = this%flowbudptr%budterm(this%idxbudsbcd)%id1(j)
643  if (this%iboundpak(n1) /= 0) then
644  igwfnode = this%flowbudptr%budterm(this%idxbudsbcd)%id2(j)
645  ! -- For now, there is only 1 aux variable under 'GWF'
646  auxpos = this%flowbudptr%budterm(this%idxbudgwf)%naux
647  wa = this%flowbudptr%budterm(this%idxbudgwf)%auxvar(auxpos, j)
648  ktf = this%ktf(n1)
649  s = this%rfeatthk(n1)
650  ctherm = ktf * wa / s
651  q = ctherm * (x(igwfnode) - this%xnewpak(n1))
652  end if
653  call this%budobj%budterm(idx)%update_term(n1, igwfnode, q)
654  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
655  if (this%iboundpak(n1) /= 0) then
656  ! -- Contribution to gwe cell budget
657  this%simvals(n1) = this%simvals(n1) - q
658  idiag = this%dis%con%ia(igwfnode)
659  flowja(idiag) = flowja(idiag) - q
660  end if
661  end do

◆ sfe_get_nbudterms()

integer(i4b) function gwesfemodule::sfe_get_nbudterms ( class(gwesfetype this)
private

This overrides a function in the parent class.

Definition at line 449 of file gwe-sfe.f90.

450  ! -- dummy
451  class(GweSfeType) :: this
452  ! -- return
453  integer(I4B) :: nbudterms
454  !
455  ! -- Number of budget terms is 6:
456  ! 1. rainfall
457  ! 2. evaporation
458  ! 3. runoff
459  ! 4. ext-inflow
460  ! 5. ext-outflow
461  ! 6. streambed-cond
462  nbudterms = 6

◆ sfe_iflw_term()

subroutine gwesfemodule::sfe_iflw_term ( class(gwesfetype 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 
)
private

Accounts for energy 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 832 of file gwe-sfe.f90.

833  ! -- dummy
834  class(GweSfeType) :: this
835  integer(I4B), intent(in) :: ientry
836  integer(I4B), intent(inout) :: n1
837  integer(I4B), intent(inout) :: n2
838  real(DP), intent(inout), optional :: rrate
839  real(DP), intent(inout), optional :: rhsval
840  real(DP), intent(inout), optional :: hcofval
841  ! -- local
842  real(DP) :: qbnd
843  real(DP) :: ctmp
844  !
845  n1 = this%flowbudptr%budterm(this%idxbudiflw)%id1(ientry)
846  n2 = this%flowbudptr%budterm(this%idxbudiflw)%id2(ientry)
847  qbnd = this%flowbudptr%budterm(this%idxbudiflw)%flow(ientry)
848  ctmp = this%tempiflw(n1)
849  if (present(rrate)) rrate = ctmp * qbnd * this%eqnsclfac
850  if (present(rhsval)) rhsval = -rrate
851  if (present(hcofval)) hcofval = dzero

◆ sfe_outf_term()

subroutine gwesfemodule::sfe_outf_term ( class(gwesfetype 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 
)
private

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

Definition at line 859 of file gwe-sfe.f90.

860  ! -- dummy
861  class(GweSfeType) :: this
862  integer(I4B), intent(in) :: ientry
863  integer(I4B), intent(inout) :: n1
864  integer(I4B), intent(inout) :: n2
865  real(DP), intent(inout), optional :: rrate
866  real(DP), intent(inout), optional :: rhsval
867  real(DP), intent(inout), optional :: hcofval
868  ! -- local
869  real(DP) :: qbnd
870  real(DP) :: ctmp
871  !
872  n1 = this%flowbudptr%budterm(this%idxbudoutf)%id1(ientry)
873  n2 = this%flowbudptr%budterm(this%idxbudoutf)%id2(ientry)
874  qbnd = this%flowbudptr%budterm(this%idxbudoutf)%flow(ientry)
875  ctmp = this%xnewpak(n1)
876  if (present(rrate)) rrate = ctmp * qbnd * this%eqnsclfac
877  if (present(rhsval)) rhsval = dzero
878  if (present(hcofval)) hcofval = qbnd * this%eqnsclfac

◆ sfe_rain_term()

subroutine gwesfemodule::sfe_rain_term ( class(gwesfetype 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 754 of file gwe-sfe.f90.

755  ! -- dummy
756  class(GweSfeType) :: this
757  integer(I4B), intent(in) :: ientry
758  integer(I4B), intent(inout) :: n1
759  integer(I4B), intent(inout) :: n2
760  real(DP), intent(inout), optional :: rrate
761  real(DP), intent(inout), optional :: rhsval
762  real(DP), intent(inout), optional :: hcofval
763  ! -- local
764  real(DP) :: qbnd
765  real(DP) :: ctmp
766  !
767  n1 = this%flowbudptr%budterm(this%idxbudrain)%id1(ientry)
768  n2 = this%flowbudptr%budterm(this%idxbudrain)%id2(ientry)
769  qbnd = this%flowbudptr%budterm(this%idxbudrain)%flow(ientry)
770  ctmp = this%temprain(n1)
771  if (present(rrate)) rrate = ctmp * qbnd * this%eqnsclfac ! kluge note: think about budget / sensible heat issue
772  if (present(rhsval)) rhsval = -rrate
773  if (present(hcofval)) hcofval = dzero

◆ sfe_read_cvs()

subroutine gwesfemodule::sfe_read_cvs ( class(gwesfetype), intent(inout)  this)

Definition at line 1102 of file gwe-sfe.f90.

1103  ! -- modules
1106  ! -- dummy
1107  class(GweSfeType), intent(inout) :: this
1108  ! -- local
1109  character(len=LINELENGTH) :: text
1110  character(len=LENBOUNDNAME) :: bndName, bndNameTemp
1111  character(len=9) :: cno
1112  character(len=50), dimension(:), allocatable :: caux
1113  integer(I4B) :: ierr
1114  logical :: isfound, endOfBlock
1115  integer(I4B) :: n
1116  integer(I4B) :: ii, jj
1117  integer(I4B) :: iaux
1118  integer(I4B) :: itmp
1119  integer(I4B) :: nlak
1120  integer(I4B) :: nconn
1121  integer(I4B), dimension(:), pointer, contiguous :: nboundchk
1122  real(DP), pointer :: bndElem => null()
1123  !
1124  ! -- initialize itmp
1125  itmp = 0
1126  !
1127  ! -- allocate apt data
1128  call mem_allocate(this%strt, this%ncv, 'STRT', this%memoryPath)
1129  call mem_allocate(this%ktf, this%ncv, 'KTF', this%memoryPath)
1130  call mem_allocate(this%rfeatthk, this%ncv, 'RFEATTHK', this%memoryPath)
1131  call mem_allocate(this%lauxvar, this%naux, this%ncv, 'LAUXVAR', &
1132  this%memoryPath)
1133  !
1134  ! -- lake boundary and concentrations
1135  if (this%imatrows == 0) then
1136  call mem_allocate(this%iboundpak, this%ncv, 'IBOUND', this%memoryPath)
1137  call mem_allocate(this%xnewpak, this%ncv, 'XNEWPAK', this%memoryPath)
1138  end if
1139  call mem_allocate(this%xoldpak, this%ncv, 'XOLDPAK', this%memoryPath)
1140  !
1141  ! -- allocate character storage not managed by the memory manager
1142  allocate (this%featname(this%ncv)) ! ditch after boundnames allocated??
1143  !allocate(this%status(this%ncv))
1144  !
1145  do n = 1, this%ncv
1146  this%strt(n) = dep20
1147  this%ktf(n) = dzero
1148  this%rfeatthk(n) = dzero
1149  this%lauxvar(:, n) = dzero
1150  this%xoldpak(n) = dep20
1151  if (this%imatrows == 0) then
1152  this%iboundpak(n) = 1
1153  this%xnewpak(n) = dep20
1154  end if
1155  end do
1156  !
1157  ! -- allocate local storage for aux variables
1158  if (this%naux > 0) then
1159  allocate (caux(this%naux))
1160  end if
1161  !
1162  ! -- allocate and initialize temporary variables
1163  allocate (nboundchk(this%ncv))
1164  do n = 1, this%ncv
1165  nboundchk(n) = 0
1166  end do
1167  !
1168  ! -- get packagedata block
1169  call this%parser%GetBlock('PACKAGEDATA', isfound, ierr, &
1170  supportopenclose=.true.)
1171  !
1172  ! -- parse locations block if detected
1173  if (isfound) then
1174  write (this%iout, '(/1x,a)') 'PROCESSING '//trim(adjustl(this%text))// &
1175  ' PACKAGEDATA'
1176  nlak = 0
1177  nconn = 0
1178  do
1179  call this%parser%GetNextLine(endofblock)
1180  if (endofblock) exit
1181  n = this%parser%GetInteger()
1182 
1183  if (n < 1 .or. n > this%ncv) then
1184  write (errmsg, '(a,1x,i6)') &
1185  'Itemno must be > 0 and <= ', this%ncv
1186  call store_error(errmsg)
1187  cycle
1188  end if
1189  !
1190  ! -- increment nboundchk
1191  nboundchk(n) = nboundchk(n) + 1
1192  !
1193  ! -- strt
1194  this%strt(n) = this%parser%GetDouble()
1195  !
1196  ! -- read additional thermal conductivity terms
1197  this%ktf(n) = this%parser%GetDouble()
1198  this%rfeatthk(n) = this%parser%GetDouble()
1199  if (this%rfeatthk(n) <= dzero) then
1200  write (errmsg, '(4x,a)') &
1201  '****ERROR. Specified thickness used for thermal &
1202  &conduction MUST BE > 0 else divide by zero error occurs'
1203  call store_error(errmsg)
1204  cycle
1205  end if
1206  !
1207  ! -- get aux data
1208  do iaux = 1, this%naux
1209  call this%parser%GetString(caux(iaux))
1210  end do
1211 
1212  ! -- set default bndName
1213  write (cno, '(i9.9)') n
1214  bndname = 'Feature'//cno
1215 
1216  ! -- featname
1217  if (this%inamedbound /= 0) then
1218  call this%parser%GetStringCaps(bndnametemp)
1219  if (bndnametemp /= '') then
1220  bndname = bndnametemp
1221  end if
1222  end if
1223  this%featname(n) = bndname
1224 
1225  ! -- fill time series aware data
1226  ! -- fill aux data
1227  do jj = 1, this%naux
1228  text = caux(jj)
1229  ii = n
1230  bndelem => this%lauxvar(jj, ii)
1231  call read_value_or_time_series_adv(text, ii, jj, bndelem, &
1232  this%packName, 'AUX', &
1233  this%tsManager, this%iprpak, &
1234  this%auxname(jj))
1235  end do
1236  !
1237  nlak = nlak + 1
1238  end do
1239  !
1240  ! -- check for duplicate or missing lakes
1241  do n = 1, this%ncv
1242  if (nboundchk(n) == 0) then
1243  write (errmsg, '(a,1x,i0)') 'No data specified for feature', n
1244  call store_error(errmsg)
1245  else if (nboundchk(n) > 1) then
1246  write (errmsg, '(a,1x,i0,1x,a,1x,i0,1x,a)') &
1247  'Data for feature', n, 'specified', nboundchk(n), 'times'
1248  call store_error(errmsg)
1249  end if
1250  end do
1251  !
1252  write (this%iout, '(1x,a)') &
1253  'END OF '//trim(adjustl(this%text))//' PACKAGEDATA'
1254  else
1255  call store_error('Required packagedata block not found.')
1256  end if
1257  !
1258  ! -- terminate if any errors were detected
1259  if (count_errors() > 0) then
1260  call this%parser%StoreErrorUnit()
1261  end if
1262  !
1263  ! -- deallocate local storage for aux variables
1264  if (this%naux > 0) then
1265  deallocate (caux)
1266  end if
1267  !
1268  ! -- deallocate local storage for nboundchk
1269  deallocate (nboundchk)
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:

◆ sfe_roff_term()

subroutine gwesfemodule::sfe_roff_term ( class(gwesfetype 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 
)
private

Definition at line 804 of file gwe-sfe.f90.

805  ! -- dummy
806  class(GweSfeType) :: this
807  integer(I4B), intent(in) :: ientry
808  integer(I4B), intent(inout) :: n1
809  integer(I4B), intent(inout) :: n2
810  real(DP), intent(inout), optional :: rrate
811  real(DP), intent(inout), optional :: rhsval
812  real(DP), intent(inout), optional :: hcofval
813  ! -- local
814  real(DP) :: qbnd
815  real(DP) :: ctmp
816  !
817  n1 = this%flowbudptr%budterm(this%idxbudroff)%id1(ientry)
818  n2 = this%flowbudptr%budterm(this%idxbudroff)%id2(ientry)
819  qbnd = this%flowbudptr%budterm(this%idxbudroff)%flow(ientry)
820  ctmp = this%temproff(n1)
821  if (present(rrate)) rrate = ctmp * qbnd * this%eqnsclfac
822  if (present(rhsval)) rhsval = -rrate
823  if (present(hcofval)) hcofval = dzero

◆ sfe_rp_obs()

subroutine gwesfemodule::sfe_rp_obs ( class(gwesfetype), intent(inout)  this,
type(observetype), intent(inout)  obsrv,
logical, intent(inout)  found 
)
private

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 958 of file gwe-sfe.f90.

959  ! -- dummy
960  class(GweSfeType), intent(inout) :: this !< package class
961  type(ObserveType), intent(inout) :: obsrv !< observation object
962  logical, intent(inout) :: found !< indicate whether observation was found
963  ! -- local
964  !
965  found = .true.
966  select case (obsrv%ObsTypeId)
967  case ('RAINFALL')
968  call this%rp_obs_byfeature(obsrv)
969  case ('EVAPORATION')
970  call this%rp_obs_byfeature(obsrv)
971  case ('RUNOFF')
972  call this%rp_obs_byfeature(obsrv)
973  case ('EXT-INFLOW')
974  call this%rp_obs_byfeature(obsrv)
975  case ('EXT-OUTFLOW')
976  call this%rp_obs_byfeature(obsrv)
977  case ('TO-MVR')
978  call this%rp_obs_byfeature(obsrv)
979  case default
980  found = .false.
981  end select

◆ sfe_set_stressperiod()

subroutine gwesfemodule::sfe_set_stressperiod ( class(gwesfetype), intent(inout)  this,
integer(i4b), intent(in)  itemno,
character(len=*), intent(in)  keyword,
logical, intent(inout)  found 
)
private

Definition at line 1025 of file gwe-sfe.f90.

1026  ! -- modules
1028  ! -- dummy
1029  class(GweSfeType), intent(inout) :: this
1030  integer(I4B), intent(in) :: itemno
1031  character(len=*), intent(in) :: keyword
1032  logical, intent(inout) :: found
1033  ! -- local
1034  character(len=LINELENGTH) :: text
1035  integer(I4B) :: ierr
1036  integer(I4B) :: jj
1037  real(DP), pointer :: bndElem => null()
1038  !
1039  ! RAINFALL <rainfall>
1040  ! EVAPORATION <evaporation>
1041  ! RUNOFF <runoff>
1042  ! INFLOW <inflow>
1043  ! WITHDRAWAL <withdrawal>
1044  !
1045  found = .true.
1046  select case (keyword)
1047  case ('RAINFALL')
1048  ierr = this%apt_check_valid(itemno)
1049  if (ierr /= 0) then
1050  goto 999
1051  end if
1052  call this%parser%GetString(text)
1053  jj = 1
1054  bndelem => this%temprain(itemno)
1055  call read_value_or_time_series_adv(text, itemno, jj, bndelem, &
1056  this%packName, 'BND', this%tsManager, &
1057  this%iprpak, 'RAINFALL')
1058  case ('EVAPORATION')
1059  ierr = this%apt_check_valid(itemno)
1060  if (ierr /= 0) then
1061  goto 999
1062  end if
1063  call this%parser%GetString(text)
1064  jj = 1
1065  bndelem => this%tempevap(itemno)
1066  call read_value_or_time_series_adv(text, itemno, jj, bndelem, &
1067  this%packName, 'BND', this%tsManager, &
1068  this%iprpak, 'EVAPORATION')
1069  case ('RUNOFF')
1070  ierr = this%apt_check_valid(itemno)
1071  if (ierr /= 0) then
1072  goto 999
1073  end if
1074  call this%parser%GetString(text)
1075  jj = 1
1076  bndelem => this%temproff(itemno)
1077  call read_value_or_time_series_adv(text, itemno, jj, bndelem, &
1078  this%packName, 'BND', this%tsManager, &
1079  this%iprpak, 'RUNOFF')
1080  case ('INFLOW')
1081  ierr = this%apt_check_valid(itemno)
1082  if (ierr /= 0) then
1083  goto 999
1084  end if
1085  call this%parser%GetString(text)
1086  jj = 1
1087  bndelem => this%tempiflw(itemno)
1088  call read_value_or_time_series_adv(text, itemno, jj, bndelem, &
1089  this%packName, 'BND', this%tsManager, &
1090  this%iprpak, 'INFLOW')
1091  case default
1092  !
1093  ! -- Keyword not recognized so return to caller with found = .false.
1094  found = .false.
1095  end select
1096  !
1097 999 continue
Here is the call graph for this function:

◆ sfe_setup_budobj()

subroutine gwesfemodule::sfe_setup_budobj ( class(gwesfetype this,
integer(i4b), intent(inout)  idx 
)
private

Definition at line 467 of file gwe-sfe.f90.

468  ! -- modules
469  use constantsmodule, only: lenbudtxt
470  ! -- dummy
471  class(GweSfeType) :: this
472  integer(I4B), intent(inout) :: idx
473  ! -- local
474  integer(I4B) :: n, n1, n2
475  integer(I4B) :: maxlist, naux
476  real(DP) :: q
477  character(len=LENBUDTXT) :: text
478  !
479  ! --
480  text = ' RAINFALL'
481  idx = idx + 1
482  maxlist = this%flowbudptr%budterm(this%idxbudrain)%maxlist
483  naux = 0
484  call this%budobj%budterm(idx)%initialize(text, &
485  this%name_model, &
486  this%packName, &
487  this%name_model, &
488  this%packName, &
489  maxlist, .false., .false., &
490  naux)
491  !
492  ! --
493  text = ' EVAPORATION'
494  idx = idx + 1
495  maxlist = this%flowbudptr%budterm(this%idxbudevap)%maxlist
496  naux = 0
497  call this%budobj%budterm(idx)%initialize(text, &
498  this%name_model, &
499  this%packName, &
500  this%name_model, &
501  this%packName, &
502  maxlist, .false., .false., &
503  naux)
504  !
505  ! --
506  text = ' RUNOFF'
507  idx = idx + 1
508  maxlist = this%flowbudptr%budterm(this%idxbudroff)%maxlist
509  naux = 0
510  call this%budobj%budterm(idx)%initialize(text, &
511  this%name_model, &
512  this%packName, &
513  this%name_model, &
514  this%packName, &
515  maxlist, .false., .false., &
516  naux)
517  !
518  ! --
519  text = ' EXT-INFLOW'
520  idx = idx + 1
521  maxlist = this%flowbudptr%budterm(this%idxbudiflw)%maxlist
522  naux = 0
523  call this%budobj%budterm(idx)%initialize(text, &
524  this%name_model, &
525  this%packName, &
526  this%name_model, &
527  this%packName, &
528  maxlist, .false., .false., &
529  naux)
530  !
531  ! --
532  text = ' EXT-OUTFLOW'
533  idx = idx + 1
534  maxlist = this%flowbudptr%budterm(this%idxbudoutf)%maxlist
535  naux = 0
536  call this%budobj%budterm(idx)%initialize(text, &
537  this%name_model, &
538  this%packName, &
539  this%name_model, &
540  this%packName, &
541  maxlist, .false., .false., &
542  naux)
543  !
544  ! -- Conduction through the wetted streambed
545  text = ' STREAMBED-COND'
546  idx = idx + 1
547  maxlist = this%flowbudptr%budterm(this%idxbudsbcd)%maxlist
548  naux = 0
549  call this%budobj%budterm(idx)%initialize(text, &
550  this%name_model, &
551  this%packName, &
552  this%name_model, &
553  this%packName, &
554  maxlist, .false., .false., &
555  naux)
556  call this%budobj%budterm(idx)%reset(maxlist)
557  q = dzero
558  do n = 1, maxlist
559  n1 = this%flowbudptr%budterm(this%idxbudgwf)%id1(n)
560  n2 = this%flowbudptr%budterm(this%idxbudgwf)%id2(n)
561  call this%budobj%budterm(idx)%update_term(n1, n2, q)
562  end do
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter lenbudtxt
maximum length of a budget component names
Definition: Constants.f90:37

◆ sfe_solve()

subroutine gwesfemodule::sfe_solve ( class(gwesfetype this)
private

Definition at line 394 of file gwe-sfe.f90.

395  ! -- dummy
396  class(GweSfeType) :: this
397  ! -- local
398  integer(I4B) :: j
399  integer(I4B) :: n1, n2
400  real(DP) :: rrate
401  !
402  ! -- Add rainfall contribution
403  if (this%idxbudrain /= 0) then
404  do j = 1, this%flowbudptr%budterm(this%idxbudrain)%nlist
405  call this%sfe_rain_term(j, n1, n2, rrate)
406  this%dbuff(n1) = this%dbuff(n1) + rrate
407  end do
408  end if
409  !
410  ! -- Add evaporation contribution
411  if (this%idxbudevap /= 0) then
412  do j = 1, this%flowbudptr%budterm(this%idxbudevap)%nlist
413  call this%sfe_evap_term(j, n1, n2, rrate)
414  this%dbuff(n1) = this%dbuff(n1) + rrate
415  end do
416  end if
417  !
418  ! -- Add runoff contribution
419  if (this%idxbudroff /= 0) then
420  do j = 1, this%flowbudptr%budterm(this%idxbudroff)%nlist
421  call this%sfe_roff_term(j, n1, n2, rrate)
422  this%dbuff(n1) = this%dbuff(n1) + rrate
423  end do
424  end if
425  !
426  ! -- Add inflow contribution
427  if (this%idxbudiflw /= 0) then
428  do j = 1, this%flowbudptr%budterm(this%idxbudiflw)%nlist
429  call this%sfe_iflw_term(j, n1, n2, rrate)
430  this%dbuff(n1) = this%dbuff(n1) + rrate
431  end do
432  end if
433  !
434  ! -- Add outflow contribution
435  if (this%idxbudoutf /= 0) then
436  do j = 1, this%flowbudptr%budterm(this%idxbudoutf)%nlist
437  call this%sfe_outf_term(j, n1, n2, rrate)
438  this%dbuff(n1) = this%dbuff(n1) + rrate
439  end do
440  end if
441  !
442  ! Note: explicit streambed conduction terms???

Variable Documentation

◆ flowtype

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

Definition at line 55 of file gwe-sfe.f90.

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

◆ ftype

character(len=*), parameter gwesfemodule::ftype = 'SFE'
private

Definition at line 54 of file gwe-sfe.f90.

54  character(len=*), parameter :: ftype = 'SFE'

◆ text

character(len=16) gwesfemodule::text = ' SFE'
private

Definition at line 56 of file gwe-sfe.f90.

56  character(len=16) :: text = ' SFE'