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