MODFLOW 6  version 6.6.0.dev0
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  contains
68 
69  procedure :: bnd_da => sft_da
70  procedure :: allocate_scalars
71  procedure :: apt_allocate_arrays => sft_allocate_arrays
72  procedure :: find_apt_package => find_sft_package
73  procedure :: pak_fc_expanded => sft_fc_expanded
74  procedure :: pak_solve => sft_solve
75  procedure :: pak_get_nbudterms => sft_get_nbudterms
76  procedure :: pak_setup_budobj => sft_setup_budobj
77  procedure :: pak_fill_budobj => sft_fill_budobj
78  procedure :: sft_rain_term
79  procedure :: sft_evap_term
80  procedure :: sft_roff_term
81  procedure :: sft_iflw_term
82  procedure :: sft_outf_term
83  procedure :: pak_df_obs => sft_df_obs
84  procedure :: pak_rp_obs => sft_rp_obs
85  procedure :: pak_bd_obs => sft_bd_obs
86  procedure :: pak_set_stressperiod => sft_set_stressperiod
87 
88  end type gwtsfttype
89 
90 contains
91 
92  !> @brief Create a new sft package
93  !<
94  subroutine sft_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, &
95  fmi, eqnsclfac, dvt, dvu, dvua)
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  end subroutine sft_create
146 
147  !> @brief Find corresponding sft package
148  !<
149  subroutine find_sft_package(this)
150  ! -- modules
152  ! -- dummy
153  class(gwtsfttype) :: this
154  ! -- local
155  character(len=LINELENGTH) :: errmsg
156  class(bndtype), pointer :: packobj
157  integer(I4B) :: ip, icount
158  integer(I4B) :: nbudterm
159  logical :: found
160  !
161  ! -- Initialize found to false, and error later if flow package cannot
162  ! be found
163  found = .false.
164  !
165  ! -- If user is specifying flows in a binary budget file, then set up
166  ! the budget file reader, otherwise set a pointer to the flow package
167  ! budobj
168  if (this%fmi%flows_from_file) then
169  call this%fmi%set_aptbudobj_pointer(this%flowpackagename, this%flowbudptr)
170  if (associated(this%flowbudptr)) found = .true.
171  !
172  else
173  if (associated(this%fmi%gwfbndlist)) then
174  ! -- Look through gwfbndlist for a flow package with the same name as
175  ! this transport package name
176  do ip = 1, this%fmi%gwfbndlist%Count()
177  packobj => getbndfromlist(this%fmi%gwfbndlist, ip)
178  if (packobj%packName == this%flowpackagename) then
179  found = .true.
180  !
181  ! -- store BndType pointer to packobj, and then
182  ! use the select type to point to the budobj in flow package
183  this%flowpackagebnd => packobj
184  select type (packobj)
185  type is (sfrtype)
186  this%flowbudptr => packobj%budobj
187  end select
188  end if
189  if (found) exit
190  end do
191  end if
192  end if
193  !
194  ! -- error if flow package not found
195  if (.not. found) then
196  write (errmsg, '(a)') 'Could not find flow package with name '&
197  &//trim(adjustl(this%flowpackagename))//'.'
198  call store_error(errmsg)
199  call this%parser%StoreErrorUnit()
200  end if
201  !
202  ! -- allocate space for idxbudssm, which indicates whether this is a
203  ! special budget term or one that is a general source and sink
204  nbudterm = this%flowbudptr%nbudterm
205  call mem_allocate(this%idxbudssm, nbudterm, 'IDXBUDSSM', this%memoryPath)
206  !
207  ! -- Process budget terms and identify special budget terms
208  write (this%iout, '(/, a, a)') &
209  'PROCESSING '//ftype//' INFORMATION FOR ', this%packName
210  write (this%iout, '(a)') ' IDENTIFYING FLOW TERMS IN '//flowtype//' PACKAGE'
211  write (this%iout, '(a, i0)') &
212  ' NUMBER OF '//flowtype//' = ', this%flowbudptr%ncv
213  icount = 1
214  do ip = 1, this%flowbudptr%nbudterm
215  select case (trim(adjustl(this%flowbudptr%budterm(ip)%flowtype)))
216  case ('FLOW-JA-FACE')
217  this%idxbudfjf = ip
218  this%idxbudssm(ip) = 0
219  case ('GWF')
220  this%idxbudgwf = ip
221  this%idxbudssm(ip) = 0
222  case ('STORAGE')
223  this%idxbudsto = ip
224  this%idxbudssm(ip) = 0
225  case ('RAINFALL')
226  this%idxbudrain = ip
227  this%idxbudssm(ip) = 0
228  case ('EVAPORATION')
229  this%idxbudevap = ip
230  this%idxbudssm(ip) = 0
231  case ('RUNOFF')
232  this%idxbudroff = ip
233  this%idxbudssm(ip) = 0
234  case ('EXT-INFLOW')
235  this%idxbudiflw = ip
236  this%idxbudssm(ip) = 0
237  case ('EXT-OUTFLOW')
238  this%idxbudoutf = ip
239  this%idxbudssm(ip) = 0
240  case ('TO-MVR')
241  this%idxbudtmvr = ip
242  this%idxbudssm(ip) = 0
243  case ('FROM-MVR')
244  this%idxbudfmvr = ip
245  this%idxbudssm(ip) = 0
246  case ('AUXILIARY')
247  this%idxbudaux = ip
248  this%idxbudssm(ip) = 0
249  case default
250  !
251  ! -- set idxbudssm equal to a column index for where the concentrations
252  ! are stored in the concbud(nbudssm, ncv) array
253  this%idxbudssm(ip) = icount
254  icount = icount + 1
255  end select
256  write (this%iout, '(a, i0, " = ", a,/, a, i0)') &
257  ' TERM ', ip, trim(adjustl(this%flowbudptr%budterm(ip)%flowtype)), &
258  ' MAX NO. OF ENTRIES = ', this%flowbudptr%budterm(ip)%maxlist
259  end do
260  write (this%iout, '(a, //)') 'DONE PROCESSING '//ftype//' INFORMATION'
261  end subroutine find_sft_package
262 
263  !> @brief Add matrix terms related to SFT
264  !!
265  !! This will be called from TspAptType%apt_fc_expanded()
266  !! in order to add matrix terms specifically for SFT
267  !<
268  subroutine sft_fc_expanded(this, rhs, ia, idxglo, matrix_sln)
269  ! -- modules
270  ! -- dummy
271  class(gwtsfttype) :: this
272  real(DP), dimension(:), intent(inout) :: rhs
273  integer(I4B), dimension(:), intent(in) :: ia
274  integer(I4B), dimension(:), intent(in) :: idxglo
275  class(matrixbasetype), pointer :: matrix_sln
276  ! -- local
277  integer(I4B) :: j, n1, n2
278  integer(I4B) :: iloc
279  integer(I4B) :: iposd
280  real(DP) :: rrate
281  real(DP) :: rhsval
282  real(DP) :: hcofval
283  !
284  ! -- add rainfall contribution
285  if (this%idxbudrain /= 0) then
286  do j = 1, this%flowbudptr%budterm(this%idxbudrain)%nlist
287  call this%sft_rain_term(j, n1, n2, rrate, rhsval, hcofval)
288  iloc = this%idxlocnode(n1)
289  iposd = this%idxpakdiag(n1)
290  call matrix_sln%add_value_pos(iposd, hcofval)
291  rhs(iloc) = rhs(iloc) + rhsval
292  end do
293  end if
294  !
295  ! -- add evaporation contribution
296  if (this%idxbudevap /= 0) then
297  do j = 1, this%flowbudptr%budterm(this%idxbudevap)%nlist
298  call this%sft_evap_term(j, n1, n2, rrate, rhsval, hcofval)
299  iloc = this%idxlocnode(n1)
300  iposd = this%idxpakdiag(n1)
301  call matrix_sln%add_value_pos(iposd, hcofval)
302  rhs(iloc) = rhs(iloc) + rhsval
303  end do
304  end if
305  !
306  ! -- add runoff contribution
307  if (this%idxbudroff /= 0) then
308  do j = 1, this%flowbudptr%budterm(this%idxbudroff)%nlist
309  call this%sft_roff_term(j, n1, n2, rrate, rhsval, hcofval)
310  iloc = this%idxlocnode(n1)
311  iposd = this%idxpakdiag(n1)
312  call matrix_sln%add_value_pos(iposd, hcofval)
313  rhs(iloc) = rhs(iloc) + rhsval
314  end do
315  end if
316  !
317  ! -- add inflow contribution
318  if (this%idxbudiflw /= 0) then
319  do j = 1, this%flowbudptr%budterm(this%idxbudiflw)%nlist
320  call this%sft_iflw_term(j, n1, n2, rrate, rhsval, hcofval)
321  iloc = this%idxlocnode(n1)
322  iposd = this%idxpakdiag(n1)
323  call matrix_sln%add_value_pos(iposd, hcofval)
324  rhs(iloc) = rhs(iloc) + rhsval
325  end do
326  end if
327  !
328  ! -- add outflow contribution
329  if (this%idxbudoutf /= 0) then
330  do j = 1, this%flowbudptr%budterm(this%idxbudoutf)%nlist
331  call this%sft_outf_term(j, n1, n2, rrate, rhsval, hcofval)
332  iloc = this%idxlocnode(n1)
333  iposd = this%idxpakdiag(n1)
334  call matrix_sln%add_value_pos(iposd, hcofval)
335  rhs(iloc) = rhs(iloc) + rhsval
336  end do
337  end if
338  end subroutine sft_fc_expanded
339 
340  !> @brief Add terms specific to sft to the explicit sft solve
341  !<
342  subroutine sft_solve(this)
343  ! -- dummy
344  class(gwtsfttype) :: this
345  ! -- local
346  integer(I4B) :: j
347  integer(I4B) :: n1, n2
348  real(DP) :: rrate
349  !
350  ! -- add rainfall contribution
351  if (this%idxbudrain /= 0) then
352  do j = 1, this%flowbudptr%budterm(this%idxbudrain)%nlist
353  call this%sft_rain_term(j, n1, n2, rrate)
354  this%dbuff(n1) = this%dbuff(n1) + rrate
355  end do
356  end if
357  !
358  ! -- add evaporation contribution
359  if (this%idxbudevap /= 0) then
360  do j = 1, this%flowbudptr%budterm(this%idxbudevap)%nlist
361  call this%sft_evap_term(j, n1, n2, rrate)
362  this%dbuff(n1) = this%dbuff(n1) + rrate
363  end do
364  end if
365  !
366  ! -- add runoff contribution
367  if (this%idxbudroff /= 0) then
368  do j = 1, this%flowbudptr%budterm(this%idxbudroff)%nlist
369  call this%sft_roff_term(j, n1, n2, rrate)
370  this%dbuff(n1) = this%dbuff(n1) + rrate
371  end do
372  end if
373  !
374  ! -- add inflow contribution
375  if (this%idxbudiflw /= 0) then
376  do j = 1, this%flowbudptr%budterm(this%idxbudiflw)%nlist
377  call this%sft_iflw_term(j, n1, n2, rrate)
378  this%dbuff(n1) = this%dbuff(n1) + rrate
379  end do
380  end if
381  !
382  ! -- add outflow contribution
383  if (this%idxbudoutf /= 0) then
384  do j = 1, this%flowbudptr%budterm(this%idxbudoutf)%nlist
385  call this%sft_outf_term(j, n1, n2, rrate)
386  this%dbuff(n1) = this%dbuff(n1) + rrate
387  end do
388  end if
389  end subroutine sft_solve
390 
391  !> @brief Function to return the number of budget terms just for this package.
392  !!
393  !! This overrides a function in the parent class.
394  !<
395  function sft_get_nbudterms(this) result(nbudterms)
396  ! -- modules
397  ! -- dummy
398  class(gwtsfttype) :: this
399  ! -- return
400  integer(I4B) :: nbudterms
401  ! -- local
402  !
403  ! -- Number of budget terms is 5
404  nbudterms = 5
405  end function sft_get_nbudterms
406 
407  !> @brief Set up the budget object that stores all the sft flows
408  !<
409  subroutine sft_setup_budobj(this, idx)
410  ! -- modules
411  use constantsmodule, only: lenbudtxt
412  ! -- dummy
413  class(gwtsfttype) :: this
414  integer(I4B), intent(inout) :: idx
415  ! -- local
416  integer(I4B) :: maxlist, naux
417  character(len=LENBUDTXT) :: text
418  !
419  ! --
420  text = ' RAINFALL'
421  idx = idx + 1
422  maxlist = this%flowbudptr%budterm(this%idxbudrain)%maxlist
423  naux = 0
424  call this%budobj%budterm(idx)%initialize(text, &
425  this%name_model, &
426  this%packName, &
427  this%name_model, &
428  this%packName, &
429  maxlist, .false., .false., &
430  naux)
431  !
432  ! --
433  text = ' EVAPORATION'
434  idx = idx + 1
435  maxlist = this%flowbudptr%budterm(this%idxbudevap)%maxlist
436  naux = 0
437  call this%budobj%budterm(idx)%initialize(text, &
438  this%name_model, &
439  this%packName, &
440  this%name_model, &
441  this%packName, &
442  maxlist, .false., .false., &
443  naux)
444  !
445  ! --
446  text = ' RUNOFF'
447  idx = idx + 1
448  maxlist = this%flowbudptr%budterm(this%idxbudroff)%maxlist
449  naux = 0
450  call this%budobj%budterm(idx)%initialize(text, &
451  this%name_model, &
452  this%packName, &
453  this%name_model, &
454  this%packName, &
455  maxlist, .false., .false., &
456  naux)
457  !
458  ! --
459  text = ' EXT-INFLOW'
460  idx = idx + 1
461  maxlist = this%flowbudptr%budterm(this%idxbudiflw)%maxlist
462  naux = 0
463  call this%budobj%budterm(idx)%initialize(text, &
464  this%name_model, &
465  this%packName, &
466  this%name_model, &
467  this%packName, &
468  maxlist, .false., .false., &
469  naux)
470  !
471  ! --
472  text = ' EXT-OUTFLOW'
473  idx = idx + 1
474  maxlist = this%flowbudptr%budterm(this%idxbudoutf)%maxlist
475  naux = 0
476  call this%budobj%budterm(idx)%initialize(text, &
477  this%name_model, &
478  this%packName, &
479  this%name_model, &
480  this%packName, &
481  maxlist, .false., .false., &
482  naux)
483  end subroutine sft_setup_budobj
484 
485  !> @brief Copy flow terms into this%budobj
486  !<
487  subroutine sft_fill_budobj(this, idx, x, flowja, ccratin, ccratout)
488  ! -- modules
489  ! -- dummy
490  class(gwtsfttype) :: this
491  integer(I4B), intent(inout) :: idx
492  real(DP), dimension(:), intent(in) :: x
493  real(DP), dimension(:), contiguous, intent(inout) :: flowja
494  real(DP), intent(inout) :: ccratin
495  real(DP), intent(inout) :: ccratout
496  ! -- local
497  integer(I4B) :: j, n1, n2
498  integer(I4B) :: nlist
499  real(DP) :: q
500  ! -- formats
501  !
502  ! -- RAIN
503  idx = idx + 1
504  nlist = this%flowbudptr%budterm(this%idxbudrain)%nlist
505  call this%budobj%budterm(idx)%reset(nlist)
506  do j = 1, nlist
507  call this%sft_rain_term(j, n1, n2, q)
508  call this%budobj%budterm(idx)%update_term(n1, n2, q)
509  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
510  end do
511  !
512  ! -- EVAPORATION
513  idx = idx + 1
514  nlist = this%flowbudptr%budterm(this%idxbudevap)%nlist
515  call this%budobj%budterm(idx)%reset(nlist)
516  do j = 1, nlist
517  call this%sft_evap_term(j, n1, n2, q)
518  call this%budobj%budterm(idx)%update_term(n1, n2, q)
519  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
520  end do
521  !
522  ! -- RUNOFF
523  idx = idx + 1
524  nlist = this%flowbudptr%budterm(this%idxbudroff)%nlist
525  call this%budobj%budterm(idx)%reset(nlist)
526  do j = 1, nlist
527  call this%sft_roff_term(j, n1, n2, q)
528  call this%budobj%budterm(idx)%update_term(n1, n2, q)
529  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
530  end do
531  !
532  ! -- EXT-INFLOW
533  idx = idx + 1
534  nlist = this%flowbudptr%budterm(this%idxbudiflw)%nlist
535  call this%budobj%budterm(idx)%reset(nlist)
536  do j = 1, nlist
537  call this%sft_iflw_term(j, n1, n2, q)
538  call this%budobj%budterm(idx)%update_term(n1, n2, q)
539  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
540  end do
541  !
542  ! -- EXT-OUTFLOW
543  idx = idx + 1
544  nlist = this%flowbudptr%budterm(this%idxbudoutf)%nlist
545  call this%budobj%budterm(idx)%reset(nlist)
546  do j = 1, nlist
547  call this%sft_outf_term(j, n1, n2, q)
548  call this%budobj%budterm(idx)%update_term(n1, n2, q)
549  call this%apt_accumulate_ccterm(n1, q, ccratin, ccratout)
550  end do
551  end subroutine sft_fill_budobj
552 
553  !> @brief Allocate scalars specific to the streamflow energy transport (SFE)
554  !! package.
555  !<
556  subroutine allocate_scalars(this)
557  ! -- modules
559  ! -- dummy
560  class(gwtsfttype) :: this
561  ! -- local
562  !
563  ! -- allocate scalars in TspAptType
564  call this%TspAptType%allocate_scalars()
565  !
566  ! -- Allocate
567  call mem_allocate(this%idxbudrain, 'IDXBUDRAIN', this%memoryPath)
568  call mem_allocate(this%idxbudevap, 'IDXBUDEVAP', this%memoryPath)
569  call mem_allocate(this%idxbudroff, 'IDXBUDROFF', this%memoryPath)
570  call mem_allocate(this%idxbudiflw, 'IDXBUDIFLW', this%memoryPath)
571  call mem_allocate(this%idxbudoutf, 'IDXBUDOUTF', this%memoryPath)
572  !
573  ! -- Initialize
574  this%idxbudrain = 0
575  this%idxbudevap = 0
576  this%idxbudroff = 0
577  this%idxbudiflw = 0
578  this%idxbudoutf = 0
579  end subroutine allocate_scalars
580 
581  !> @brief Allocate arrays specific to the streamflow energy transport (SFE)
582  !! package.
583  !<
584  subroutine sft_allocate_arrays(this)
585  ! -- modules
587  ! -- dummy
588  class(gwtsfttype), intent(inout) :: this
589  ! -- local
590  integer(I4B) :: n
591  !
592  ! -- time series
593  call mem_allocate(this%concrain, this%ncv, 'CONCRAIN', this%memoryPath)
594  call mem_allocate(this%concevap, this%ncv, 'CONCEVAP', this%memoryPath)
595  call mem_allocate(this%concroff, this%ncv, 'CONCROFF', this%memoryPath)
596  call mem_allocate(this%conciflw, this%ncv, 'CONCIFLW', this%memoryPath)
597  !
598  ! -- call standard TspAptType allocate arrays
599  call this%TspAptType%apt_allocate_arrays()
600  !
601  ! -- Initialize
602  do n = 1, this%ncv
603  this%concrain(n) = dzero
604  this%concevap(n) = dzero
605  this%concroff(n) = dzero
606  this%conciflw(n) = dzero
607  end do
608  end subroutine sft_allocate_arrays
609 
610  !> @brief Deallocate memory
611  !<
612  subroutine sft_da(this)
613  ! -- modules
615  ! -- dummy
616  class(gwtsfttype) :: this
617  ! -- local
618  !
619  ! -- deallocate scalars
620  call mem_deallocate(this%idxbudrain)
621  call mem_deallocate(this%idxbudevap)
622  call mem_deallocate(this%idxbudroff)
623  call mem_deallocate(this%idxbudiflw)
624  call mem_deallocate(this%idxbudoutf)
625  !
626  ! -- deallocate time series
627  call mem_deallocate(this%concrain)
628  call mem_deallocate(this%concevap)
629  call mem_deallocate(this%concroff)
630  call mem_deallocate(this%conciflw)
631  !
632  ! -- deallocate scalars in TspAptType
633  call this%TspAptType%bnd_da()
634  end subroutine sft_da
635 
636  !> @brief Rain term
637  !<
638  subroutine sft_rain_term(this, ientry, n1, n2, rrate, &
639  rhsval, hcofval)
640  ! -- dummy
641  class(gwtsfttype) :: this
642  integer(I4B), intent(in) :: ientry
643  integer(I4B), intent(inout) :: n1
644  integer(I4B), intent(inout) :: n2
645  real(DP), intent(inout), optional :: rrate
646  real(DP), intent(inout), optional :: rhsval
647  real(DP), intent(inout), optional :: hcofval
648  ! -- local
649  real(DP) :: qbnd
650  real(DP) :: ctmp
651  !
652  n1 = this%flowbudptr%budterm(this%idxbudrain)%id1(ientry)
653  n2 = this%flowbudptr%budterm(this%idxbudrain)%id2(ientry)
654  qbnd = this%flowbudptr%budterm(this%idxbudrain)%flow(ientry)
655  ctmp = this%concrain(n1)
656  if (present(rrate)) rrate = ctmp * qbnd
657  if (present(rhsval)) rhsval = -rrate
658  if (present(hcofval)) hcofval = dzero
659  end subroutine sft_rain_term
660 
661  !> @brief Evaporative term
662  !<
663  subroutine sft_evap_term(this, ientry, n1, n2, rrate, &
664  rhsval, hcofval)
665  ! -- dummy
666  class(gwtsfttype) :: this
667  integer(I4B), intent(in) :: ientry
668  integer(I4B), intent(inout) :: n1
669  integer(I4B), intent(inout) :: n2
670  real(DP), intent(inout), optional :: rrate
671  real(DP), intent(inout), optional :: rhsval
672  real(DP), intent(inout), optional :: hcofval
673  ! -- local
674  real(DP) :: qbnd
675  real(DP) :: ctmp
676  real(DP) :: omega
677  !
678  n1 = this%flowbudptr%budterm(this%idxbudevap)%id1(ientry)
679  n2 = this%flowbudptr%budterm(this%idxbudevap)%id2(ientry)
680  ! -- note that qbnd is negative for evap
681  qbnd = this%flowbudptr%budterm(this%idxbudevap)%flow(ientry)
682  ctmp = this%concevap(n1)
683  if (this%xnewpak(n1) < ctmp) then
684  omega = done
685  else
686  omega = dzero
687  end if
688  if (present(rrate)) &
689  rrate = omega * qbnd * this%xnewpak(n1) + &
690  (done - omega) * qbnd * ctmp
691  if (present(rhsval)) rhsval = -(done - omega) * qbnd * ctmp
692  if (present(hcofval)) hcofval = omega * qbnd
693  end subroutine sft_evap_term
694 
695  !> @brief Runoff term
696  !<
697  subroutine sft_roff_term(this, ientry, n1, n2, rrate, &
698  rhsval, hcofval)
699  ! -- dummy
700  class(gwtsfttype) :: this
701  integer(I4B), intent(in) :: ientry
702  integer(I4B), intent(inout) :: n1
703  integer(I4B), intent(inout) :: n2
704  real(DP), intent(inout), optional :: rrate
705  real(DP), intent(inout), optional :: rhsval
706  real(DP), intent(inout), optional :: hcofval
707  ! -- local
708  real(DP) :: qbnd
709  real(DP) :: ctmp
710  !
711  n1 = this%flowbudptr%budterm(this%idxbudroff)%id1(ientry)
712  n2 = this%flowbudptr%budterm(this%idxbudroff)%id2(ientry)
713  qbnd = this%flowbudptr%budterm(this%idxbudroff)%flow(ientry)
714  ctmp = this%concroff(n1)
715  if (present(rrate)) rrate = ctmp * qbnd
716  if (present(rhsval)) rhsval = -rrate
717  if (present(hcofval)) hcofval = dzero
718  end subroutine sft_roff_term
719 
720  !> @brief Inflow Term
721  !!
722  !! Accounts for mass added via streamflow entering into a stream channel;
723  !! for example, energy entering the model domain via a specified flow in a
724  !! stream channel.
725  !<
726  subroutine sft_iflw_term(this, ientry, n1, n2, rrate, &
727  rhsval, hcofval)
728  ! -- dummy
729  class(gwtsfttype) :: this
730  integer(I4B), intent(in) :: ientry
731  integer(I4B), intent(inout) :: n1
732  integer(I4B), intent(inout) :: n2
733  real(DP), intent(inout), optional :: rrate
734  real(DP), intent(inout), optional :: rhsval
735  real(DP), intent(inout), optional :: hcofval
736  ! -- local
737  real(DP) :: qbnd
738  real(DP) :: ctmp
739  !
740  n1 = this%flowbudptr%budterm(this%idxbudiflw)%id1(ientry)
741  n2 = this%flowbudptr%budterm(this%idxbudiflw)%id2(ientry)
742  qbnd = this%flowbudptr%budterm(this%idxbudiflw)%flow(ientry)
743  ctmp = this%conciflw(n1)
744  if (present(rrate)) rrate = ctmp * qbnd
745  if (present(rhsval)) rhsval = -rrate
746  if (present(hcofval)) hcofval = dzero
747  end subroutine sft_iflw_term
748 
749  !> @brief Outflow term
750  !!
751  !! Accounts for the mass leaving a stream channel; for example, mass exiting the
752  !! model domain via a flow in a stream channel flowing out of the active domain.
753  !<
754  subroutine sft_outf_term(this, ientry, n1, n2, rrate, &
755  rhsval, hcofval)
756  ! -- dummy
757  class(gwtsfttype) :: this
758  integer(I4B), intent(in) :: ientry
759  integer(I4B), intent(inout) :: n1
760  integer(I4B), intent(inout) :: n2
761  real(DP), intent(inout), optional :: rrate
762  real(DP), intent(inout), optional :: rhsval
763  real(DP), intent(inout), optional :: hcofval
764  ! -- local
765  real(DP) :: qbnd
766  real(DP) :: ctmp
767  !
768  n1 = this%flowbudptr%budterm(this%idxbudoutf)%id1(ientry)
769  n2 = this%flowbudptr%budterm(this%idxbudoutf)%id2(ientry)
770  qbnd = this%flowbudptr%budterm(this%idxbudoutf)%flow(ientry)
771  ctmp = this%xnewpak(n1)
772  if (present(rrate)) rrate = ctmp * qbnd
773  if (present(rhsval)) rhsval = dzero
774  if (present(hcofval)) hcofval = qbnd
775  end subroutine sft_outf_term
776 
777  !> @brief Observations
778  !!
779  !! Store the observation type supported by the APT package and override
780  !! BndType%bnd_df_obs
781  !<
782  subroutine sft_df_obs(this)
783  ! -- modules
784  ! -- dummy
785  class(gwtsfttype) :: this
786  ! -- local
787  integer(I4B) :: indx
788  !
789  ! -- Store obs type and assign procedure pointer
790  ! for concentration observation type.
791  call this%obs%StoreObsType('concentration', .false., indx)
792  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
793  !
794  ! -- Store obs type and assign procedure pointer
795  ! for flow between reaches.
796  call this%obs%StoreObsType('flow-ja-face', .true., indx)
797  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid12
798  !
799  ! -- Store obs type and assign procedure pointer
800  ! for from-mvr observation type.
801  call this%obs%StoreObsType('from-mvr', .true., indx)
802  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
803  !
804  ! -- Store obs type and assign procedure pointer
805  ! for to-mvr observation type.
806  call this%obs%StoreObsType('to-mvr', .true., indx)
807  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
808  !
809  ! -- Store obs type and assign procedure pointer
810  ! for storage observation type.
811  call this%obs%StoreObsType('storage', .true., indx)
812  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
813  !
814  ! -- Store obs type and assign procedure pointer
815  ! for constant observation type.
816  call this%obs%StoreObsType('constant', .true., indx)
817  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
818  !
819  ! -- Store obs type and assign procedure pointer
820  ! for observation type: sft
821  call this%obs%StoreObsType('sft', .true., indx)
822  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
823  !
824  ! -- Store obs type and assign procedure pointer
825  ! for rainfall observation type.
826  call this%obs%StoreObsType('rainfall', .true., indx)
827  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
828  !
829  ! -- Store obs type and assign procedure pointer
830  ! for evaporation observation type.
831  call this%obs%StoreObsType('evaporation', .true., indx)
832  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
833  !
834  ! -- Store obs type and assign procedure pointer
835  ! for runoff observation type.
836  call this%obs%StoreObsType('runoff', .true., indx)
837  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
838  !
839  ! -- Store obs type and assign procedure pointer
840  ! for inflow observation type.
841  call this%obs%StoreObsType('ext-inflow', .true., indx)
842  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
843  !
844  ! -- Store obs type and assign procedure pointer
845  ! for ext-outflow observation type.
846  call this%obs%StoreObsType('ext-outflow', .true., indx)
847  this%obs%obsData(indx)%ProcessIdPtr => apt_process_obsid
848  end subroutine sft_df_obs
849 
850  !> @brief Process package specific obs
851  !!
852  !! Method to process specific observations for this package.
853  !<
854  subroutine sft_rp_obs(this, obsrv, found)
855  ! -- dummy
856  class(gwtsfttype), intent(inout) :: this !< package class
857  type(observetype), intent(inout) :: obsrv !< observation object
858  logical, intent(inout) :: found !< indicate whether observation was found
859  ! -- local
860  !
861  found = .true.
862  select case (obsrv%ObsTypeId)
863  case ('RAINFALL')
864  call this%rp_obs_byfeature(obsrv)
865  case ('EVAPORATION')
866  call this%rp_obs_byfeature(obsrv)
867  case ('RUNOFF')
868  call this%rp_obs_byfeature(obsrv)
869  case ('EXT-INFLOW')
870  call this%rp_obs_byfeature(obsrv)
871  case ('EXT-OUTFLOW')
872  call this%rp_obs_byfeature(obsrv)
873  case ('TO-MVR')
874  call this%rp_obs_byfeature(obsrv)
875  case default
876  found = .false.
877  end select
878  end subroutine sft_rp_obs
879 
880  !> @brief Calculate observation value and pass it back to APT
881  !<
882  subroutine sft_bd_obs(this, obstypeid, jj, v, found)
883  ! -- dummy
884  class(gwtsfttype), intent(inout) :: this
885  character(len=*), intent(in) :: obstypeid
886  real(DP), intent(inout) :: v
887  integer(I4B), intent(in) :: jj
888  logical, intent(inout) :: found
889  ! -- local
890  integer(I4B) :: n1, n2
891  !
892  found = .true.
893  select case (obstypeid)
894  case ('RAINFALL')
895  if (this%iboundpak(jj) /= 0) then
896  call this%sft_rain_term(jj, n1, n2, v)
897  end if
898  case ('EVAPORATION')
899  if (this%iboundpak(jj) /= 0) then
900  call this%sft_evap_term(jj, n1, n2, v)
901  end if
902  case ('RUNOFF')
903  if (this%iboundpak(jj) /= 0) then
904  call this%sft_roff_term(jj, n1, n2, v)
905  end if
906  case ('EXT-INFLOW')
907  if (this%iboundpak(jj) /= 0) then
908  call this%sft_iflw_term(jj, n1, n2, v)
909  end if
910  case ('EXT-OUTFLOW')
911  if (this%iboundpak(jj) /= 0) then
912  call this%sft_outf_term(jj, n1, n2, v)
913  end if
914  case default
915  found = .false.
916  end select
917  end subroutine sft_bd_obs
918 
919  !> @brief Sets the stress period attributes for keyword use.
920  !<
921  subroutine sft_set_stressperiod(this, itemno, keyword, found)
923  ! -- dummy
924  class(gwtsfttype), intent(inout) :: this
925  integer(I4B), intent(in) :: itemno
926  character(len=*), intent(in) :: keyword
927  logical, intent(inout) :: found
928  ! -- local
929  character(len=LINELENGTH) :: text
930  integer(I4B) :: ierr
931  integer(I4B) :: jj
932  real(DP), pointer :: bndElem => null()
933  ! -- formats
934  !
935  ! RAINFALL <rainfall>
936  ! EVAPORATION <evaporation>
937  ! RUNOFF <runoff>
938  ! INFLOW <inflow>
939  ! WITHDRAWAL <withdrawal>
940  !
941  found = .true.
942  select case (keyword)
943  case ('RAINFALL')
944  ierr = this%apt_check_valid(itemno)
945  if (ierr /= 0) then
946  goto 999
947  end if
948  call this%parser%GetString(text)
949  jj = 1
950  bndelem => this%concrain(itemno)
951  call read_value_or_time_series_adv(text, itemno, jj, bndelem, &
952  this%packName, 'BND', this%tsManager, &
953  this%iprpak, 'RAINFALL')
954  case ('EVAPORATION')
955  ierr = this%apt_check_valid(itemno)
956  if (ierr /= 0) then
957  goto 999
958  end if
959  call this%parser%GetString(text)
960  jj = 1
961  bndelem => this%concevap(itemno)
962  call read_value_or_time_series_adv(text, itemno, jj, bndelem, &
963  this%packName, 'BND', this%tsManager, &
964  this%iprpak, 'EVAPORATION')
965  case ('RUNOFF')
966  ierr = this%apt_check_valid(itemno)
967  if (ierr /= 0) then
968  goto 999
969  end if
970  call this%parser%GetString(text)
971  jj = 1
972  bndelem => this%concroff(itemno)
973  call read_value_or_time_series_adv(text, itemno, jj, bndelem, &
974  this%packName, 'BND', this%tsManager, &
975  this%iprpak, 'RUNOFF')
976  case ('INFLOW')
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%conciflw(itemno)
984  call read_value_or_time_series_adv(text, itemno, jj, bndelem, &
985  this%packName, 'BND', this%tsManager, &
986  this%iprpak, 'INFLOW')
987  case default
988  !
989  ! -- keyword not recognized so return to caller with found = .false.
990  found = .false.
991  end select
992  !
993 999 continue
994  end subroutine sft_set_stressperiod
995 
996 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:343
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:728
subroutine allocate_scalars(this)
Allocate scalars specific to the streamflow energy transport (SFE) package.
Definition: gwt-sft.f90:557
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:756
subroutine sft_roff_term(this, ientry, n1, n2, rrate, rhsval, hcofval)
Runoff term.
Definition: gwt-sft.f90:699
subroutine find_sft_package(this)
Find corresponding sft package.
Definition: gwt-sft.f90:150
subroutine sft_bd_obs(this, obstypeid, jj, v, found)
Calculate observation value and pass it back to APT.
Definition: gwt-sft.f90:883
subroutine sft_rp_obs(this, obsrv, found)
Process package specific obs.
Definition: gwt-sft.f90:855
subroutine sft_da(this)
Deallocate memory.
Definition: gwt-sft.f90:613
subroutine sft_fill_budobj(this, idx, x, flowja, ccratin, ccratout)
Copy flow terms into thisbudobj.
Definition: gwt-sft.f90:488
subroutine sft_set_stressperiod(this, itemno, keyword, found)
Sets the stress period attributes for keyword use.
Definition: gwt-sft.f90:922
subroutine sft_fc_expanded(this, rhs, ia, idxglo, matrix_sln)
Add matrix terms related to SFT.
Definition: gwt-sft.f90:269
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:96
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:410
integer(i4b) function sft_get_nbudterms(this)
Function to return the number of budget terms just for this package.
Definition: gwt-sft.f90:396
subroutine sft_evap_term(this, ientry, n1, n2, rrate, rhsval, hcofval)
Evaporative term.
Definition: gwt-sft.f90:665
subroutine sft_allocate_arrays(this)
Allocate arrays specific to the streamflow energy transport (SFE) package.
Definition: gwt-sft.f90:585
subroutine sft_df_obs(this)
Observations.
Definition: gwt-sft.f90:783
subroutine sft_rain_term(this, ientry, n1, n2, rrate, rhsval, hcofval)
Rain term.
Definition: gwt-sft.f90:640
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:2841
subroutine, public apt_process_obsid12(obsrv, dis, inunitobs, iout)
Process observation IDs for a package.
Definition: tsp-apt.f90:2884
@ brief BndType