MODFLOW 6  version 6.7.0.dev3
USGS Modular Hydrologic Model
gwt-sft.f90
Go to the documentation of this file.
1 ! -- Stream Transport Module
2 ! -- todo: what to do about reactions in stream? Decay?
3 ! -- todo: save the sft concentration into the sfr aux variable?
4 ! -- todo: calculate the sfr DENSE aux variable using concentration?
5 !
6 ! SFR flows (sfrbudptr) index var SFT term Transport Type
7 !---------------------------------------------------------------------------------
8 
9 ! -- terms from SFR that will be handled by parent APT Package
10 ! FLOW-JA-FACE idxbudfjf FLOW-JA-FACE cv2cv
11 ! GWF (aux FLOW-AREA) idxbudgwf GWF cv2gwf
12 ! STORAGE (aux VOLUME) idxbudsto none used for cv volumes
13 ! FROM-MVR idxbudfmvr FROM-MVR q * cext = this%qfrommvr(:)
14 ! TO-MVR idxbudtmvr TO-MVR q * cfeat
15 
16 ! -- SFR terms
17 ! RAINFALL idxbudrain RAINFALL q * crain
18 ! EVAPORATION idxbudevap EVAPORATION cfeat<cevap: q*cfeat, else: q*cevap
19 ! RUNOFF idxbudroff RUNOFF q * croff
20 ! EXT-INFLOW idxbudiflw EXT-INFLOW q * ciflw
21 ! EXT-OUTFLOW idxbudoutf EXT-OUTFLOW q * cfeat
22 
23 ! -- terms from a flow file that should be skipped
24 ! CONSTANT none none none
25 ! AUXILIARY none none none
26 
27 ! -- terms that are written to the transport budget file
28 ! none none STORAGE (aux MASS) dM/dt
29 ! none none AUXILIARY none
30 ! none none CONSTANT accumulate
31 !
32 !
34 
35  use kindmodule, only: dp, i4b
37  use simmodule, only: store_error
38  use bndmodule, only: bndtype, getbndfromlist
39  use tspfmimodule, only: tspfmitype
40  use sfrmodule, only: sfrtype
41  use observemodule, only: observetype
45 
46  implicit none
47 
48  public sft_create
49 
50  character(len=*), parameter :: ftype = 'SFT'
51  character(len=*), parameter :: flowtype = 'SFR'
52  character(len=16) :: text = ' SFT'
53 
54  type, extends(tspapttype) :: gwtsfttype
55 
56  integer(I4B), pointer :: idxbudrain => null() !< index of rainfall terms in flowbudptr
57  integer(I4B), pointer :: idxbudevap => null() !< index of evaporation terms in flowbudptr
58  integer(I4B), pointer :: idxbudroff => null() !< index of runoff terms in flowbudptr
59  integer(I4B), pointer :: idxbudiflw => null() !< index of inflow terms in flowbudptr
60  integer(I4B), pointer :: idxbudoutf => null() !< index of outflow terms in flowbudptr
61 
62  real(dp), dimension(:), pointer, contiguous :: concrain => null() !< rainfall concentration
63  real(dp), dimension(:), pointer, contiguous :: concevap => null() !< evaporation concentration
64  real(dp), dimension(:), pointer, contiguous :: concroff => null() !< runoff concentration
65  real(dp), dimension(:), pointer, contiguous :: conciflw => null() !< inflow concentration
66 
67  real(dp), dimension(:), pointer, contiguous :: vnew => null() !< current reach volume
68  real(dp), dimension(:), pointer, contiguous :: vold => null() !< previous reach volume
69 
70  contains
71 
72  procedure :: bnd_ad => sft_ad
73  procedure :: bnd_da => sft_da
74  procedure :: allocate_scalars
75  procedure :: apt_allocate_arrays => sft_allocate_arrays
76  procedure :: find_apt_package => find_sft_package
77  procedure :: pak_fc_expanded => sft_fc_expanded
78  procedure :: pak_solve => sft_solve
79  procedure :: pak_get_nbudterms => sft_get_nbudterms
80  procedure :: pak_setup_budobj => sft_setup_budobj
81  procedure :: pak_fill_budobj => sft_fill_budobj
82  procedure :: sft_rain_term
83  procedure :: sft_evap_term
84  procedure :: sft_roff_term
85  procedure :: sft_iflw_term
86  procedure :: sft_outf_term
87  procedure :: pak_df_obs => sft_df_obs
88  procedure :: pak_rp_obs => sft_rp_obs
89  procedure :: pak_bd_obs => sft_bd_obs
90  procedure :: pak_set_stressperiod => sft_set_stressperiod
91  procedure :: apt_get_volumes => sft_get_volumes
92 
93  end type gwtsfttype
94 
95 contains
96 
97  !> @brief Create a new sft package
98  !<
99  subroutine sft_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, &
100  fmi, eqnsclfac, dvt, dvu, dvua)
101  ! -- dummy
102  class(bndtype), pointer :: packobj
103  integer(I4B), intent(in) :: id
104  integer(I4B), intent(in) :: ibcnum
105  integer(I4B), intent(in) :: inunit
106  integer(I4B), intent(in) :: iout
107  character(len=*), intent(in) :: namemodel
108  character(len=*), intent(in) :: pakname
109  type(tspfmitype), pointer :: fmi
110  real(dp), intent(in), pointer :: eqnsclfac !< governing equation scale factor
111  character(len=*), intent(in) :: dvt !< For GWT, set to "CONCENTRATION" in TspAptType
112  character(len=*), intent(in) :: dvu !< For GWT, set to "mass" in TspAptType
113  character(len=*), intent(in) :: dvua !< For GWT, set to "M" in TspAptType
114  ! -- local
115  type(gwtsfttype), pointer :: sftobj
116  !
117  ! -- allocate the object and assign values to object variables
118  allocate (sftobj)
119  packobj => sftobj
120  !
121  ! -- create name and memory path
122  call packobj%set_names(ibcnum, namemodel, pakname, ftype)
123  packobj%text = text
124  !
125  ! -- allocate scalars
126  call sftobj%allocate_scalars()
127  !
128  ! -- initialize package
129  call packobj%pack_initialize()
130  !
131  packobj%inunit = inunit
132  packobj%iout = iout
133  packobj%id = id
134  packobj%ibcnum = ibcnum
135  packobj%ncolbnd = 1
136  packobj%iscloc = 1
137  !
138  ! -- Store pointer to flow model interface. When the GwfGwt exchange is
139  ! created, it sets fmi%bndlist so that the GWT model has access to all
140  ! the flow packages
141  sftobj%fmi => fmi
142  !
143  ! -- Store pointer to governing equation scale factor
144  sftobj%eqnsclfac => eqnsclfac
145  !
146  ! -- Set labels that will be used in generalized APT class
147  sftobj%depvartype = dvt
148  sftobj%depvarunit = dvu
149  sftobj%depvarunitabbrev = dvua
150  end subroutine sft_create
151 
152  !> @brief Find corresponding sft package
153  !<
154  subroutine find_sft_package(this)
155  ! -- modules
157  ! -- dummy
158  class(gwtsfttype) :: this
159  ! -- local
160  character(len=LINELENGTH) :: errmsg
161  class(bndtype), pointer :: packobj
162  integer(I4B) :: ip, icount
163  integer(I4B) :: nbudterm
164  logical :: found
165  !
166  ! -- Initialize found to false, and error later if flow package cannot
167  ! be found
168  found = .false.
169  !
170  ! -- If user is specifying flows in a binary budget file, then set up
171  ! the budget file reader, otherwise set a pointer to the flow package
172  ! budobj
173  if (this%fmi%flows_from_file) then
174  call this%fmi%set_aptbudobj_pointer(this%flowpackagename, this%flowbudptr)
175  if (associated(this%flowbudptr)) found = .true.
176  !
177  else
178  if (associated(this%fmi%gwfbndlist)) then
179  ! -- Look through gwfbndlist for a flow package with the same name as
180  ! this transport package name
181  do ip = 1, this%fmi%gwfbndlist%Count()
182  packobj => getbndfromlist(this%fmi%gwfbndlist, ip)
183  if (packobj%packName == this%flowpackagename) then
184  found = .true.
185  !
186  ! -- store BndType pointer to packobj, and then
187  ! use the select type to point to the budobj in flow package
188  this%flowpackagebnd => packobj
189  select type (packobj)
190  type is (sfrtype)
191  this%flowbudptr => packobj%budobj
192  end select
193  end if
194  if (found) exit
195  end do
196  end if
197  end if
198  !
199  ! -- error if flow package not found
200  if (.not. found) then
201  write (errmsg, '(a)') 'Could not find flow package with name '&
202  &//trim(adjustl(this%flowpackagename))//'.'
203  call store_error(errmsg)
204  call this%parser%StoreErrorUnit()
205  end if
206  !
207  ! -- allocate space for idxbudssm, which indicates whether this is a
208  ! special budget term or one that is a general source and sink
209  nbudterm = this%flowbudptr%nbudterm
210  call mem_allocate(this%idxbudssm, nbudterm, 'IDXBUDSSM', this%memoryPath)
211  !
212  ! -- Process budget terms and identify special budget terms
213  write (this%iout, '(/, a, a)') &
214  'PROCESSING '//ftype//' INFORMATION FOR ', this%packName
215  write (this%iout, '(a)') ' IDENTIFYING FLOW TERMS IN '//flowtype//' PACKAGE'
216  write (this%iout, '(a, i0)') &
217  ' NUMBER OF '//flowtype//' = ', this%flowbudptr%ncv
218  icount = 1
219  do ip = 1, this%flowbudptr%nbudterm
220  select case (trim(adjustl(this%flowbudptr%budterm(ip)%flowtype)))
221  case ('FLOW-JA-FACE')
222  this%idxbudfjf = ip
223  this%idxbudssm(ip) = 0
224  case ('GWF')
225  this%idxbudgwf = ip
226  this%idxbudssm(ip) = 0
227  case ('STORAGE')
228  this%idxbudsto = ip
229  this%idxbudssm(ip) = 0
230  case ('RAINFALL')
231  this%idxbudrain = ip
232  this%idxbudssm(ip) = 0
233  case ('EVAPORATION')
234  this%idxbudevap = ip
235  this%idxbudssm(ip) = 0
236  case ('RUNOFF')
237  this%idxbudroff = ip
238  this%idxbudssm(ip) = 0
239  case ('EXT-INFLOW')
240  this%idxbudiflw = ip
241  this%idxbudssm(ip) = 0
242  case ('EXT-OUTFLOW')
243  this%idxbudoutf = ip
244  this%idxbudssm(ip) = 0
245  case ('TO-MVR')
246  this%idxbudtmvr = ip
247  this%idxbudssm(ip) = 0
248  case ('FROM-MVR')
249  this%idxbudfmvr = ip
250  this%idxbudssm(ip) = 0
251  case ('AUXILIARY')
252  this%idxbudaux = ip
253  this%idxbudssm(ip) = 0
254  case default
255  !
256  ! -- set idxbudssm equal to a column index for where the concentrations
257  ! are stored in the concbud(nbudssm, ncv) array
258  this%idxbudssm(ip) = icount
259  icount = icount + 1
260  end select
261  write (this%iout, '(a, i0, " = ", a,/, a, i0)') &
262  ' TERM ', ip, trim(adjustl(this%flowbudptr%budterm(ip)%flowtype)), &
263  ' MAX NO. OF ENTRIES = ', this%flowbudptr%budterm(ip)%maxlist
264  end do
265  write (this%iout, '(a, //)') 'DONE PROCESSING '//ftype//' INFORMATION'
266  end subroutine find_sft_package
267 
268  !> @brief Add matrix terms related to SFT
269  !!
270  !! This will be called from TspAptType%apt_fc_expanded()
271  !! in order to add matrix terms specifically for SFT
272  !<
273  subroutine sft_fc_expanded(this, rhs, ia, idxglo, matrix_sln)
274  ! -- modules
275  ! -- dummy
276  class(gwtsfttype) :: this
277  real(DP), dimension(:), intent(inout) :: rhs
278  integer(I4B), dimension(:), intent(in) :: ia
279  integer(I4B), dimension(:), intent(in) :: idxglo
280  class(matrixbasetype), pointer :: matrix_sln
281  ! -- local
282  integer(I4B) :: j, n1, n2
283  integer(I4B) :: iloc
284  integer(I4B) :: iposd
285  real(DP) :: rrate
286  real(DP) :: rhsval
287  real(DP) :: hcofval
288  !
289  ! -- add rainfall contribution
290  if (this%idxbudrain /= 0) then
291  do j = 1, this%flowbudptr%budterm(this%idxbudrain)%nlist
292  call this%sft_rain_term(j, n1, n2, rrate, rhsval, hcofval)
293  iloc = this%idxlocnode(n1)
294  iposd = this%idxpakdiag(n1)
295  call matrix_sln%add_value_pos(iposd, hcofval)
296  rhs(iloc) = rhs(iloc) + rhsval
297  end do
298  end if
299  !
300  ! -- add evaporation contribution
301  if (this%idxbudevap /= 0) then
302  do j = 1, this%flowbudptr%budterm(this%idxbudevap)%nlist
303  call this%sft_evap_term(j, n1, n2, rrate, rhsval, hcofval)
304  iloc = this%idxlocnode(n1)
305  iposd = this%idxpakdiag(n1)
306  call matrix_sln%add_value_pos(iposd, hcofval)
307  rhs(iloc) = rhs(iloc) + rhsval
308  end do
309  end if
310  !
311  ! -- add runoff contribution
312  if (this%idxbudroff /= 0) then
313  do j = 1, this%flowbudptr%budterm(this%idxbudroff)%nlist
314  call this%sft_roff_term(j, n1, n2, rrate, rhsval, hcofval)
315  iloc = this%idxlocnode(n1)
316  iposd = this%idxpakdiag(n1)
317  call matrix_sln%add_value_pos(iposd, hcofval)
318  rhs(iloc) = rhs(iloc) + rhsval
319  end do
320  end if
321  !
322  ! -- add inflow contribution
323  if (this%idxbudiflw /= 0) then
324  do j = 1, this%flowbudptr%budterm(this%idxbudiflw)%nlist
325  call this%sft_iflw_term(j, n1, n2, rrate, rhsval, hcofval)
326  iloc = this%idxlocnode(n1)
327  iposd = this%idxpakdiag(n1)
328  call matrix_sln%add_value_pos(iposd, hcofval)
329  rhs(iloc) = rhs(iloc) + rhsval
330  end do
331  end if
332  !
333  ! -- add outflow contribution
334  if (this%idxbudoutf /= 0) then
335  do j = 1, this%flowbudptr%budterm(this%idxbudoutf)%nlist
336  call this%sft_outf_term(j, n1, n2, rrate, rhsval, hcofval)
337  iloc = this%idxlocnode(n1)
338  iposd = this%idxpakdiag(n1)
339  call matrix_sln%add_value_pos(iposd, hcofval)
340  rhs(iloc) = rhs(iloc) + rhsval
341  end do
342  end if
343  end subroutine sft_fc_expanded
344 
345  !> @brief Add terms specific to sft to the explicit sft solve
346  !<
347  subroutine sft_solve(this)
348  ! -- dummy
349  class(gwtsfttype) :: this
350  ! -- local
351  integer(I4B) :: j
352  integer(I4B) :: n1, n2
353  real(DP) :: rrate
354  !
355  ! -- add rainfall contribution
356  if (this%idxbudrain /= 0) then
357  do j = 1, this%flowbudptr%budterm(this%idxbudrain)%nlist
358  call this%sft_rain_term(j, n1, n2, rrate)
359  this%dbuff(n1) = this%dbuff(n1) + rrate
360  end do
361  end if
362  !
363  ! -- add evaporation contribution
364  if (this%idxbudevap /= 0) then
365  do j = 1, this%flowbudptr%budterm(this%idxbudevap)%nlist
366  call this%sft_evap_term(j, n1, n2, rrate)
367  this%dbuff(n1) = this%dbuff(n1) + rrate
368  end do
369  end if
370  !
371  ! -- add runoff contribution
372  if (this%idxbudroff /= 0) then
373  do j = 1, this%flowbudptr%budterm(this%idxbudroff)%nlist
374  call this%sft_roff_term(j, n1, n2, rrate)
375  this%dbuff(n1) = this%dbuff(n1) + rrate
376  end do
377  end if
378  !
379  ! -- add inflow contribution
380  if (this%idxbudiflw /= 0) then
381  do j = 1, this%flowbudptr%budterm(this%idxbudiflw)%nlist
382  call this%sft_iflw_term(j, n1, n2, rrate)
383  this%dbuff(n1) = this%dbuff(n1) + rrate
384  end do
385  end if
386  !
387  ! -- add outflow contribution
388  if (this%idxbudoutf /= 0) then
389  do j = 1, this%flowbudptr%budterm(this%idxbudoutf)%nlist
390  call this%sft_outf_term(j, n1, n2, rrate)
391  this%dbuff(n1) = this%dbuff(n1) + rrate
392  end do
393  end if
394  end subroutine sft_solve
395 
396  !> @brief Function to return the number of budget terms just for this package.
397  !!
398  !! This overrides a function in the parent class.
399  !<
400  function sft_get_nbudterms(this) result(nbudterms)
401  ! -- modules
402  ! -- dummy
403  class(gwtsfttype) :: this
404  ! -- return
405  integer(I4B) :: nbudterms
406  ! -- local
407  !
408  ! -- Number of budget terms is 5
409  nbudterms = 5
410  end function sft_get_nbudterms
411 
412  !> @brief Set up the budget object that stores all the sft flows
413  !<
414  subroutine sft_setup_budobj(this, idx)
415  ! -- modules
416  use constantsmodule, only: lenbudtxt
417  ! -- dummy
418  class(gwtsfttype) :: this
419  integer(I4B), intent(inout) :: idx
420  ! -- local
421  integer(I4B) :: maxlist, naux
422  character(len=LENBUDTXT) :: text
423  !
424  ! --
425  text = ' RAINFALL'
426  idx = idx + 1
427  maxlist = this%flowbudptr%budterm(this%idxbudrain)%maxlist
428  naux = 0
429  call this%budobj%budterm(idx)%initialize(text, &
430  this%name_model, &
431  this%packName, &
432  this%name_model, &
433  this%packName, &
434  maxlist, .false., .false., &
435  naux)
436  !
437  ! --
438  text = ' EVAPORATION'
439  idx = idx + 1
440  maxlist = this%flowbudptr%budterm(this%idxbudevap)%maxlist
441  naux = 0
442  call this%budobj%budterm(idx)%initialize(text, &
443  this%name_model, &
444  this%packName, &
445  this%name_model, &
446  this%packName, &
447  maxlist, .false., .false., &
448  naux)
449  !
450  ! --
451  text = ' RUNOFF'
452  idx = idx + 1
453  maxlist = this%flowbudptr%budterm(this%idxbudroff)%maxlist
454  naux = 0
455  call this%budobj%budterm(idx)%initialize(text, &
456  this%name_model, &
457  this%packName, &
458  this%name_model, &
459  this%packName, &
460  maxlist, .false., .false., &
461  naux)
462  !
463  ! --
464  text = ' EXT-INFLOW'
465  idx = idx + 1
466  maxlist = this%flowbudptr%budterm(this%idxbudiflw)%maxlist
467  naux = 0
468  call this%budobj%budterm(idx)%initialize(text, &
469  this%name_model, &
470  this%packName, &
471  this%name_model, &
472  this%packName, &
473  maxlist, .false., .false., &
474  naux)
475  !
476  ! --
477  text = ' EXT-OUTFLOW'
478  idx = idx + 1
479  maxlist = this%flowbudptr%budterm(this%idxbudoutf)%maxlist
480  naux = 0
481  call this%budobj%budterm(idx)%initialize(text, &
482  this%name_model, &
483  this%packName, &
484  this%name_model, &
485  this%packName, &
486  maxlist, .false., .false., &
487  naux)
488  end subroutine sft_setup_budobj
489 
490  !> @brief Copy flow terms into this%budobj
491  !<
492  subroutine sft_fill_budobj(this, idx, x, flowja, ccratin, ccratout)
493  ! -- modules
494  ! -- dummy
495  class(gwtsfttype) :: this
496  integer(I4B), intent(inout) :: idx
497  real(DP), dimension(:), intent(in) :: x
498  real(DP), dimension(:), contiguous, intent(inout) :: flowja
499  real(DP), intent(inout) :: ccratin
500  real(DP), intent(inout) :: ccratout
501  ! -- local
502  integer(I4B) :: j, n1, n2
503  integer(I4B) :: nlist
504  real(DP) :: q
505  ! -- formats
506  !
507  ! -- RAIN
508  idx = idx + 1
509  nlist = this%flowbudptr%budterm(this%idxbudrain)%nlist
510  call this%budobj%budterm(idx)%reset(nlist)
511  do j = 1, nlist
512  call this%sft_rain_term(j, n1, n2, q)
513  call this%budobj%budterm(idx)%update_term(n1, n2, q)
514  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
515  end do
516  !
517  ! -- EVAPORATION
518  idx = idx + 1
519  nlist = this%flowbudptr%budterm(this%idxbudevap)%nlist
520  call this%budobj%budterm(idx)%reset(nlist)
521  do j = 1, nlist
522  call this%sft_evap_term(j, n1, n2, q)
523  call this%budobj%budterm(idx)%update_term(n1, n2, q)
524  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
525  end do
526  !
527  ! -- RUNOFF
528  idx = idx + 1
529  nlist = this%flowbudptr%budterm(this%idxbudroff)%nlist
530  call this%budobj%budterm(idx)%reset(nlist)
531  do j = 1, nlist
532  call this%sft_roff_term(j, n1, n2, q)
533  call this%budobj%budterm(idx)%update_term(n1, n2, q)
534  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
535  end do
536  !
537  ! -- EXT-INFLOW
538  idx = idx + 1
539  nlist = this%flowbudptr%budterm(this%idxbudiflw)%nlist
540  call this%budobj%budterm(idx)%reset(nlist)
541  do j = 1, nlist
542  call this%sft_iflw_term(j, n1, n2, q)
543  call this%budobj%budterm(idx)%update_term(n1, n2, q)
544  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
545  end do
546  !
547  ! -- EXT-OUTFLOW
548  idx = idx + 1
549  nlist = this%flowbudptr%budterm(this%idxbudoutf)%nlist
550  call this%budobj%budterm(idx)%reset(nlist)
551  do j = 1, nlist
552  call this%sft_outf_term(j, n1, n2, q)
553  call this%budobj%budterm(idx)%update_term(n1, n2, q)
554  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
555  end do
556  end subroutine sft_fill_budobj
557 
558  !> @brief Allocate scalars specific to the streamflow energy transport (SFE)
559  !! package.
560  !<
561  subroutine allocate_scalars(this)
562  ! -- modules
564  ! -- dummy
565  class(gwtsfttype) :: this
566  ! -- local
567  !
568  ! -- allocate scalars in TspAptType
569  call this%TspAptType%allocate_scalars()
570  !
571  ! -- Allocate
572  call mem_allocate(this%idxbudrain, 'IDXBUDRAIN', this%memoryPath)
573  call mem_allocate(this%idxbudevap, 'IDXBUDEVAP', this%memoryPath)
574  call mem_allocate(this%idxbudroff, 'IDXBUDROFF', this%memoryPath)
575  call mem_allocate(this%idxbudiflw, 'IDXBUDIFLW', this%memoryPath)
576  call mem_allocate(this%idxbudoutf, 'IDXBUDOUTF', this%memoryPath)
577  !
578  ! -- Initialize
579  this%idxbudrain = 0
580  this%idxbudevap = 0
581  this%idxbudroff = 0
582  this%idxbudiflw = 0
583  this%idxbudoutf = 0
584  end subroutine allocate_scalars
585 
586  !> @brief Allocate arrays specific to the streamflow energy transport (SFE)
587  !! package.
588  !<
589  subroutine sft_allocate_arrays(this)
590  ! -- modules
592  ! -- dummy
593  class(gwtsfttype), intent(inout) :: this
594  ! -- local
595  integer(I4B) :: n
596  !
597  ! -- time series
598  call mem_allocate(this%concrain, this%ncv, 'CONCRAIN', this%memoryPath)
599  call mem_allocate(this%concevap, this%ncv, 'CONCEVAP', this%memoryPath)
600  call mem_allocate(this%concroff, this%ncv, 'CONCROFF', this%memoryPath)
601  call mem_allocate(this%conciflw, this%ncv, 'CONCIFLW', this%memoryPath)
602 
603  call mem_allocate(this%vnew, this%ncv, 'VNEW', this%memoryPath)
604  call mem_allocate(this%vold, this%ncv, 'VOLD', this%memoryPath)
605 
606  !
607  ! -- call standard TspAptType allocate arrays
608  call this%TspAptType%apt_allocate_arrays()
609  !
610  ! -- Initialize
611  do n = 1, this%ncv
612  this%concrain(n) = dzero
613  this%concevap(n) = dzero
614  this%concroff(n) = dzero
615  this%conciflw(n) = dzero
616  this%vnew(n) = dzero
617  this%vold(n) = dzero
618  end do
619  end subroutine sft_allocate_arrays
620 
621  !> @brief Advance sft package routine
622  !<
623  subroutine sft_ad(this)
624  ! modules
625  ! dummy
626  class(gwtsfttype) :: this
627  ! local
628  integer(I4B) :: n
629 
630  ! call base bnd_ad
631  call this%TspAptType%bnd_ad()
632 
633  ! update vold
634  do n = 1, this%ncv
635  this%vold(n) = this%vnew(n)
636  end do
637 
638  end subroutine sft_ad
639 
640  !> @brief Deallocate memory
641  !<
642  subroutine sft_da(this)
643  ! -- modules
645  ! -- dummy
646  class(gwtsfttype) :: this
647  ! -- local
648  !
649  ! -- deallocate scalars
650  call mem_deallocate(this%idxbudrain)
651  call mem_deallocate(this%idxbudevap)
652  call mem_deallocate(this%idxbudroff)
653  call mem_deallocate(this%idxbudiflw)
654  call mem_deallocate(this%idxbudoutf)
655  !
656  ! -- deallocate time series
657  call mem_deallocate(this%concrain)
658  call mem_deallocate(this%concevap)
659  call mem_deallocate(this%concroff)
660  call mem_deallocate(this%conciflw)
661 
662  call mem_deallocate(this%vnew)
663  call mem_deallocate(this%vold)
664  !
665  ! -- deallocate scalars in TspAptType
666  call this%TspAptType%bnd_da()
667  end subroutine sft_da
668 
669  !> @brief Rain term
670  !<
671  subroutine sft_rain_term(this, ientry, n1, n2, rrate, &
672  rhsval, hcofval)
673  ! -- dummy
674  class(gwtsfttype) :: this
675  integer(I4B), intent(in) :: ientry
676  integer(I4B), intent(inout) :: n1
677  integer(I4B), intent(inout) :: n2
678  real(DP), intent(inout), optional :: rrate
679  real(DP), intent(inout), optional :: rhsval
680  real(DP), intent(inout), optional :: hcofval
681  ! -- local
682  real(DP) :: qbnd
683  real(DP) :: ctmp
684  !
685  n1 = this%flowbudptr%budterm(this%idxbudrain)%id1(ientry)
686  n2 = this%flowbudptr%budterm(this%idxbudrain)%id2(ientry)
687  qbnd = this%flowbudptr%budterm(this%idxbudrain)%flow(ientry)
688  ctmp = this%concrain(n1)
689  if (present(rrate)) rrate = ctmp * qbnd
690  if (present(rhsval)) rhsval = -rrate
691  if (present(hcofval)) hcofval = dzero
692  end subroutine sft_rain_term
693 
694  !> @brief Evaporative term
695  !<
696  subroutine sft_evap_term(this, ientry, n1, n2, rrate, &
697  rhsval, hcofval)
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  end subroutine sft_evap_term
727 
728  !> @brief Runoff term
729  !<
730  subroutine sft_roff_term(this, ientry, n1, n2, rrate, &
731  rhsval, hcofval)
732  ! -- dummy
733  class(gwtsfttype) :: this
734  integer(I4B), intent(in) :: ientry
735  integer(I4B), intent(inout) :: n1
736  integer(I4B), intent(inout) :: n2
737  real(DP), intent(inout), optional :: rrate
738  real(DP), intent(inout), optional :: rhsval
739  real(DP), intent(inout), optional :: hcofval
740  ! -- local
741  real(DP) :: qbnd
742  real(DP) :: ctmp
743  !
744  n1 = this%flowbudptr%budterm(this%idxbudroff)%id1(ientry)
745  n2 = this%flowbudptr%budterm(this%idxbudroff)%id2(ientry)
746  qbnd = this%flowbudptr%budterm(this%idxbudroff)%flow(ientry)
747  ctmp = this%concroff(n1)
748  if (present(rrate)) rrate = ctmp * qbnd
749  if (present(rhsval)) rhsval = -rrate
750  if (present(hcofval)) hcofval = dzero
751  end subroutine sft_roff_term
752 
753  !> @brief Inflow Term
754  !!
755  !! Accounts for mass added via streamflow entering into a stream channel;
756  !! for example, energy entering the model domain via a specified flow in a
757  !! stream channel.
758  !<
759  subroutine sft_iflw_term(this, ientry, n1, n2, rrate, &
760  rhsval, hcofval)
761  ! -- dummy
762  class(gwtsfttype) :: this
763  integer(I4B), intent(in) :: ientry
764  integer(I4B), intent(inout) :: n1
765  integer(I4B), intent(inout) :: n2
766  real(DP), intent(inout), optional :: rrate
767  real(DP), intent(inout), optional :: rhsval
768  real(DP), intent(inout), optional :: hcofval
769  ! -- local
770  real(DP) :: qbnd
771  real(DP) :: ctmp
772  !
773  n1 = this%flowbudptr%budterm(this%idxbudiflw)%id1(ientry)
774  n2 = this%flowbudptr%budterm(this%idxbudiflw)%id2(ientry)
775  qbnd = this%flowbudptr%budterm(this%idxbudiflw)%flow(ientry)
776  ctmp = this%conciflw(n1)
777  if (present(rrate)) rrate = ctmp * qbnd
778  if (present(rhsval)) rhsval = -rrate
779  if (present(hcofval)) hcofval = dzero
780  end subroutine sft_iflw_term
781 
782  !> @brief Outflow term
783  !!
784  !! Accounts for the mass leaving a stream channel; for example, mass exiting the
785  !! model domain via a flow in a stream channel flowing out of the active domain.
786  !<
787  subroutine sft_outf_term(this, ientry, n1, n2, rrate, &
788  rhsval, hcofval)
789  ! -- dummy
790  class(gwtsfttype) :: this
791  integer(I4B), intent(in) :: ientry
792  integer(I4B), intent(inout) :: n1
793  integer(I4B), intent(inout) :: n2
794  real(DP), intent(inout), optional :: rrate
795  real(DP), intent(inout), optional :: rhsval
796  real(DP), intent(inout), optional :: hcofval
797  ! -- local
798  real(DP) :: qbnd
799  real(DP) :: ctmp
800  !
801  n1 = this%flowbudptr%budterm(this%idxbudoutf)%id1(ientry)
802  n2 = this%flowbudptr%budterm(this%idxbudoutf)%id2(ientry)
803  qbnd = this%flowbudptr%budterm(this%idxbudoutf)%flow(ientry)
804  ctmp = this%xnewpak(n1)
805  if (present(rrate)) rrate = ctmp * qbnd
806  if (present(rhsval)) rhsval = dzero
807  if (present(hcofval)) hcofval = qbnd
808  end subroutine sft_outf_term
809 
810  !> @brief Observations
811  !!
812  !! Store the observation type supported by the APT package and override
813  !! BndType%bnd_df_obs
814  !<
815  subroutine sft_df_obs(this)
816  ! -- modules
817  ! -- dummy
818  class(gwtsfttype) :: this
819  ! -- local
820  integer(I4B) :: indx
821  !
822  ! -- Store obs type and assign procedure pointer
823  ! for concentration observation type.
824  call this%obs%StoreObsType('concentration', .false., indx)
825  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
826  !
827  ! -- Store obs type and assign procedure pointer
828  ! for flow between reaches.
829  call this%obs%StoreObsType('flow-ja-face', .true., indx)
830  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid12
831  !
832  ! -- Store obs type and assign procedure pointer
833  ! for from-mvr observation type.
834  call this%obs%StoreObsType('from-mvr', .true., indx)
835  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
836  !
837  ! -- Store obs type and assign procedure pointer
838  ! for to-mvr observation type.
839  call this%obs%StoreObsType('to-mvr', .true., indx)
840  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
841  !
842  ! -- Store obs type and assign procedure pointer
843  ! for storage observation type.
844  call this%obs%StoreObsType('storage', .true., indx)
845  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
846  !
847  ! -- Store obs type and assign procedure pointer
848  ! for constant observation type.
849  call this%obs%StoreObsType('constant', .true., indx)
850  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
851  !
852  ! -- Store obs type and assign procedure pointer
853  ! for observation type: sft
854  call this%obs%StoreObsType('sft', .true., indx)
855  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
856  !
857  ! -- Store obs type and assign procedure pointer
858  ! for rainfall observation type.
859  call this%obs%StoreObsType('rainfall', .true., indx)
860  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
861  !
862  ! -- Store obs type and assign procedure pointer
863  ! for evaporation observation type.
864  call this%obs%StoreObsType('evaporation', .true., indx)
865  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
866  !
867  ! -- Store obs type and assign procedure pointer
868  ! for runoff observation type.
869  call this%obs%StoreObsType('runoff', .true., indx)
870  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
871  !
872  ! -- Store obs type and assign procedure pointer
873  ! for inflow observation type.
874  call this%obs%StoreObsType('ext-inflow', .true., indx)
875  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
876  !
877  ! -- Store obs type and assign procedure pointer
878  ! for ext-outflow observation type.
879  call this%obs%StoreObsType('ext-outflow', .true., indx)
880  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
881  end subroutine sft_df_obs
882 
883  !> @brief Process package specific obs
884  !!
885  !! Method to process specific observations for this package.
886  !<
887  subroutine sft_rp_obs(this, obsrv, found)
888  ! -- dummy
889  class(gwtsfttype), intent(inout) :: this !< package class
890  type(observetype), intent(inout) :: obsrv !< observation object
891  logical, intent(inout) :: found !< indicate whether observation was found
892  ! -- local
893  !
894  found = .true.
895  select case (obsrv%ObsTypeId)
896  case ('RAINFALL')
897  call this%rp_obs_byfeature(obsrv)
898  case ('EVAPORATION')
899  call this%rp_obs_byfeature(obsrv)
900  case ('RUNOFF')
901  call this%rp_obs_byfeature(obsrv)
902  case ('EXT-INFLOW')
903  call this%rp_obs_byfeature(obsrv)
904  case ('EXT-OUTFLOW')
905  call this%rp_obs_byfeature(obsrv)
906  case ('TO-MVR')
907  call this%rp_obs_byfeature(obsrv)
908  case default
909  found = .false.
910  end select
911  end subroutine sft_rp_obs
912 
913  !> @brief Calculate observation value and pass it back to APT
914  !<
915  subroutine sft_bd_obs(this, obstypeid, jj, v, found)
916  ! -- dummy
917  class(gwtsfttype), intent(inout) :: this
918  character(len=*), intent(in) :: obstypeid
919  real(DP), intent(inout) :: v
920  integer(I4B), intent(in) :: jj
921  logical, intent(inout) :: found
922  ! -- local
923  integer(I4B) :: n1, n2
924  !
925  found = .true.
926  select case (obstypeid)
927  case ('RAINFALL')
928  if (this%iboundpak(jj) /= 0) then
929  call this%sft_rain_term(jj, n1, n2, v)
930  end if
931  case ('EVAPORATION')
932  if (this%iboundpak(jj) /= 0) then
933  call this%sft_evap_term(jj, n1, n2, v)
934  end if
935  case ('RUNOFF')
936  if (this%iboundpak(jj) /= 0) then
937  call this%sft_roff_term(jj, n1, n2, v)
938  end if
939  case ('EXT-INFLOW')
940  if (this%iboundpak(jj) /= 0) then
941  call this%sft_iflw_term(jj, n1, n2, v)
942  end if
943  case ('EXT-OUTFLOW')
944  if (this%iboundpak(jj) /= 0) then
945  call this%sft_outf_term(jj, n1, n2, v)
946  end if
947  case default
948  found = .false.
949  end select
950  end subroutine sft_bd_obs
951 
952  !> @brief Sets the stress period attributes for keyword use.
953  !<
954  subroutine sft_set_stressperiod(this, itemno, keyword, found)
956  ! -- dummy
957  class(gwtsfttype), intent(inout) :: this
958  integer(I4B), intent(in) :: itemno
959  character(len=*), intent(in) :: keyword
960  logical, intent(inout) :: found
961  ! -- local
962  character(len=LINELENGTH) :: text
963  integer(I4B) :: ierr
964  integer(I4B) :: jj
965  real(DP), pointer :: bndElem => null()
966  ! -- formats
967  !
968  ! RAINFALL <rainfall>
969  ! EVAPORATION <evaporation>
970  ! RUNOFF <runoff>
971  ! INFLOW <inflow>
972  ! WITHDRAWAL <withdrawal>
973  !
974  found = .true.
975  select case (keyword)
976  case ('RAINFALL')
977  ierr = this%apt_check_valid(itemno)
978  if (ierr /= 0) then
979  goto 999
980  end if
981  call this%parser%GetString(text)
982  jj = 1
983  bndelem => this%concrain(itemno)
984  call read_value_or_time_series_adv(text, itemno, jj, bndelem, &
985  this%packName, 'BND', this%tsManager, &
986  this%iprpak, 'RAINFALL')
987  case ('EVAPORATION')
988  ierr = this%apt_check_valid(itemno)
989  if (ierr /= 0) then
990  goto 999
991  end if
992  call this%parser%GetString(text)
993  jj = 1
994  bndelem => this%concevap(itemno)
995  call read_value_or_time_series_adv(text, itemno, jj, bndelem, &
996  this%packName, 'BND', this%tsManager, &
997  this%iprpak, 'EVAPORATION')
998  case ('RUNOFF')
999  ierr = this%apt_check_valid(itemno)
1000  if (ierr /= 0) then
1001  goto 999
1002  end if
1003  call this%parser%GetString(text)
1004  jj = 1
1005  bndelem => this%concroff(itemno)
1006  call read_value_or_time_series_adv(text, itemno, jj, bndelem, &
1007  this%packName, 'BND', this%tsManager, &
1008  this%iprpak, 'RUNOFF')
1009  case ('INFLOW')
1010  ierr = this%apt_check_valid(itemno)
1011  if (ierr /= 0) then
1012  goto 999
1013  end if
1014  call this%parser%GetString(text)
1015  jj = 1
1016  bndelem => this%conciflw(itemno)
1017  call read_value_or_time_series_adv(text, itemno, jj, bndelem, &
1018  this%packName, 'BND', this%tsManager, &
1019  this%iprpak, 'INFLOW')
1020  case default
1021  !
1022  ! -- keyword not recognized so return to caller with found = .false.
1023  found = .false.
1024  end select
1025  !
1026 999 continue
1027  end subroutine sft_set_stressperiod
1028 
1029  !> @brief Return the sfr new volume and old volume
1030  !<
1031  subroutine sft_get_volumes(this, icv, vnew, vold, delt)
1032  ! modules
1033  ! dummy
1034  class(gwtsfttype) :: this
1035  integer(I4B), intent(in) :: icv
1036  real(DP), intent(inout) :: vnew, vold
1037  real(DP), intent(in) :: delt
1038  ! local
1039  real(DP) :: qss
1040  !
1041  ! -- get volumes
1042  vold = dzero
1043  vnew = vold
1044  if (this%idxbudsto /= 0) then
1045  qss = this%flowbudptr%budterm(this%idxbudsto)%flow(icv)
1046  vnew = this%flowbudptr%budterm(this%idxbudsto)%auxvar(1, icv)
1047  this%vnew(icv) = vnew
1048  if (qss /= dzero) then
1049  vold = vnew + qss * delt
1050  else
1051  if (vnew == dzero) then
1052  vold = dzero
1053  else
1054  vold = this%vold(icv)
1055  end if
1056  end if
1057  end if
1058  end subroutine sft_get_volumes
1059 
1060 end module gwtsftmodule
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.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
integer(i4b), parameter lenbudtxt
maximum length of a budget component names
Definition: Constants.f90:37
real(dp), parameter done
real constant 1
Definition: Constants.f90:76
subroutine sft_solve(this)
Add terms specific to sft to the explicit sft solve.
Definition: gwt-sft.f90:348
character(len=16) text
Definition: gwt-sft.f90:52
subroutine sft_iflw_term(this, ientry, n1, n2, rrate, rhsval, hcofval)
Inflow Term.
Definition: gwt-sft.f90:761
subroutine allocate_scalars(this)
Allocate scalars specific to the streamflow energy transport (SFE) package.
Definition: gwt-sft.f90:562
character(len= *), parameter flowtype
Definition: gwt-sft.f90:51
subroutine sft_outf_term(this, ientry, n1, n2, rrate, rhsval, hcofval)
Outflow term.
Definition: gwt-sft.f90:789
subroutine sft_roff_term(this, ientry, n1, n2, rrate, rhsval, hcofval)
Runoff term.
Definition: gwt-sft.f90:732
subroutine find_sft_package(this)
Find corresponding sft package.
Definition: gwt-sft.f90:155
subroutine sft_bd_obs(this, obstypeid, jj, v, found)
Calculate observation value and pass it back to APT.
Definition: gwt-sft.f90:916
subroutine sft_rp_obs(this, obsrv, found)
Process package specific obs.
Definition: gwt-sft.f90:888
subroutine sft_ad(this)
Advance sft package routine.
Definition: gwt-sft.f90:624
subroutine sft_da(this)
Deallocate memory.
Definition: gwt-sft.f90:643
subroutine sft_fill_budobj(this, idx, x, flowja, ccratin, ccratout)
Copy flow terms into thisbudobj.
Definition: gwt-sft.f90:493
subroutine sft_set_stressperiod(this, itemno, keyword, found)
Sets the stress period attributes for keyword use.
Definition: gwt-sft.f90:955
subroutine sft_fc_expanded(this, rhs, ia, idxglo, matrix_sln)
Add matrix terms related to SFT.
Definition: gwt-sft.f90:274
subroutine sft_get_volumes(this, icv, vnew, vold, delt)
Return the sfr new volume and old volume.
Definition: gwt-sft.f90:1032
subroutine, public sft_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, fmi, eqnsclfac, dvt, dvu, dvua)
Create a new sft package.
Definition: gwt-sft.f90:101
character(len= *), parameter ftype
Definition: gwt-sft.f90:50
subroutine sft_setup_budobj(this, idx)
Set up the budget object that stores all the sft flows.
Definition: gwt-sft.f90:415
integer(i4b) function sft_get_nbudterms(this)
Function to return the number of budget terms just for this package.
Definition: gwt-sft.f90:401
subroutine sft_evap_term(this, ientry, n1, n2, rrate, rhsval, hcofval)
Evaporative term.
Definition: gwt-sft.f90:698
subroutine sft_allocate_arrays(this)
Allocate arrays specific to the streamflow energy transport (SFE) package.
Definition: gwt-sft.f90:590
subroutine sft_df_obs(this)
Observations.
Definition: gwt-sft.f90:816
subroutine sft_rain_term(this, ientry, n1, n2, rrate, rhsval, hcofval)
Rain term.
Definition: gwt-sft.f90:673
This module defines variable data types.
Definition: kind.f90:8
This module contains the derived types ObserveType and ObsDataType.
Definition: Observe.f90:15
This module contains the SFR package methods.
Definition: gwf-sfr.f90:7
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
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.
Definition: tsp-apt.f90:2828
subroutine, public apt_process_obsid12(obsrv, dis, inunitobs, iout)
Process observation IDs for a package.
Definition: tsp-apt.f90:2871
@ brief BndType