MODFLOW 6  version 6.7.0.dev3
USGS Modular Hydrologic Model
gwt-ist.f90
Go to the documentation of this file.
1 !> -- @ brief Immobile Storage and Transfer (IST) Module
2 !!
3 !! The GwtIstModule is contains the GwtIstType, which is the
4 !! derived type responsible for adding the effects of an
5 !! immobile domain. In addition to representing transfer
6 !! of mass between the mobile and immobile domain, the IST
7 !! Package also represents the following processes within
8 !! the immobile domain
9 !! 1. Changes in dissolved solute mass
10 !! 2. Decay of dissolved solute mass
11 !! 3. Sorption
12 !! 4. Decay of sorbed solute mass
13 !<
15 
16  use kindmodule, only: dp, i4b
17  use constantsmodule, only: done, dzero, dhalf, lenftype, &
20  use bndmodule, only: bndtype
21  use budgetmodule, only: budgettype
22  use tspfmimodule, only: tspfmitype
29  !
30  implicit none
31  !
32  private
33  public :: ist_create
34  !
35  character(len=LENFTYPE) :: ftype = 'IST'
36  character(len=LENPACKAGENAME) :: text = ' IMMOBILE DOMAIN'
37  integer(I4B), parameter :: nbditems = 5
38  character(len=LENBUDTXT), dimension(NBDITEMS) :: budtxt
39  data budtxt/' STORAGE-AQUEOUS', ' STORAGE-SORBED', &
40  ' DECAY-AQUEOUS', ' DECAY-SORBED', &
41  ' MOBILE-DOMAIN'/
42 
43  !> @ brief Immobile storage and transfer
44  !!
45  !! Data and methods for handling the effects of an
46  !! immobile domain. Note that there can be as many of these
47  !! domains as necessary. Each immobile domain represents
48  !! changes in immobile solute storage, decay of dissolved
49  !! immobile solute mass, sorption within the immobile domain,
50  !! and decay of immobile domain sorbed mass. The immobile
51  !! domain also includes exchange with the mobile domain.
52  !<
53  type, extends(bndtype) :: gwtisttype
54 
55  type(tspfmitype), pointer :: fmi => null() !< flow model interface
56  type(gwtmsttype), pointer :: mst => null() !< mobile storage and transfer
57  type(budgettype), pointer :: budget => null() !< budget
58  type(outputcontroldatatype), pointer :: ocd => null() !< output control data
59  character(len=LINELENGTH) :: lstfmt !< lst file CIM print format
60  integer(I4B), pointer :: icimout => null() !< unit number for binary cim output
61  integer(I4B), pointer :: ibudgetout => null() !< binary budget output file
62  integer(I4B), pointer :: ibudcsv => null() !< unit number for csv budget output file
63  integer(I4B), pointer :: ioutsorbate => null() !< unit number for sorbate concentration output
64  integer(I4B), pointer :: idcy => null() !< order of decay rate (0:none, 1:first, 2:zero)
65  integer(I4B), pointer :: isrb => null() !< sorption active flag (0:off, 1:on); only linear is supported in ist
66  integer(I4B), pointer :: kiter => null() !< picard iteration counter
67  real(dp), pointer, contiguous :: cim(:) => null() !< concentration for immobile domain
68  real(dp), pointer, contiguous :: cimnew(:) => null() !< immobile concentration at end of current time step
69  real(dp), pointer, contiguous :: cimold(:) => null() !< immobile concentration at end of last time step
70  real(dp), pointer, contiguous :: cimsrb(:) => null() !< sorbate concentration in immobile domain
71  real(dp), pointer, contiguous :: zetaim(:) => null() !< mass transfer rate to immobile domain
72  real(dp), pointer, contiguous :: porosity(:) => null() !< immobile domain porosity defined as volume of immobile voids per volume of immobile domain
73  real(dp), pointer, contiguous :: volfrac(:) => null() !< volume fraction of the immobile domain defined as volume of immobile domain per aquifer volume
74  real(dp), pointer, contiguous :: bulk_density(:) => null() !< bulk density of immobile domain defined as mass of solids in immobile domain per volume of immobile domain
75  real(dp), pointer, contiguous :: distcoef(:) => null() !< distribution coefficient
76  real(dp), pointer, contiguous :: sp2(:) => null() !< second sorption parameter
77  real(dp), pointer, contiguous :: decay(:) => null() !< first or zero order rate constant for liquid
78  real(dp), pointer, contiguous :: decaylast(:) => null() !< decay rate used for last iteration (needed for zero order decay)
79  real(dp), pointer, contiguous :: decayslast(:) => null() !< sorbed decay rate used for last iteration (needed for zero order decay)
80  real(dp), pointer, contiguous :: decay_sorbed(:) => null() !< first or zero order rate constant for sorbed mass
81  real(dp), pointer, contiguous :: strg(:) => null() !< mass transfer rate
82  real(dp) :: budterm(2, nbditems) !< immmobile domain mass summaries
83 
84  contains
85 
86  procedure :: bnd_ar => ist_ar
87  procedure :: bnd_rp => ist_rp
88  procedure :: bnd_ad => ist_ad
89  procedure :: bnd_fc => ist_fc
90  procedure :: bnd_cq => ist_cq
91  procedure :: bnd_bd => ist_bd
92  procedure :: bnd_ot_model_flows => ist_ot_model_flows
93  procedure :: bnd_ot_dv => ist_ot_dv
96  procedure :: bnd_ot_bdsummary => ist_ot_bdsummary
97  procedure :: bnd_da => ist_da
98  procedure :: allocate_scalars
99  procedure :: read_options
100  procedure :: read_dimensions => ist_read_dimensions
101  procedure :: source_options
102  procedure :: source_data
103  procedure :: log_options
104  procedure :: log_data
105  procedure :: get_thetaim
106  procedure :: ist_calc_csrb
107  procedure, private :: ist_allocate_arrays
108 
109  end type gwtisttype
110 
111 contains
112 
113  !> @ brief Create a new package object
114  !!
115  !! Create a new IST object
116  !!
117  !<
118  subroutine ist_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, &
119  mempath, fmi, mst)
120  ! -- dummy
121  class(bndtype), pointer :: packobj !< BndType pointer that will point to new IST Package
122  integer(I4B), intent(in) :: id !< name of the model
123  integer(I4B), intent(in) :: ibcnum !< consecutive package number
124  integer(I4B), intent(in) :: inunit !< unit number of package input file
125  integer(I4B), intent(in) :: iout !< unit number of model listing file
126  character(len=*), intent(in) :: namemodel !< name of the model
127  character(len=*), intent(in) :: pakname !< name of the package
128  character(len=*), intent(in) :: mempath
129  type(tspfmitype), pointer, intent(in) :: fmi
130  type(gwtmsttype), pointer, intent(in) :: mst
131  ! -- local
132  type(gwtisttype), pointer :: istobj
133  !
134  ! -- allocate the object and assign values to object variables
135  allocate (istobj)
136  packobj => istobj
137  !
138  ! -- create name and memory path
139  call packobj%set_names(ibcnum, namemodel, pakname, ftype, mempath)
140  packobj%text = text
141  !
142  ! -- allocate scalars
143  call packobj%allocate_scalars()
144  !
145  ! -- initialize package
146  call packobj%pack_initialize()
147  !
148  ! -- store values
149  packobj%inunit = inunit
150  packobj%iout = iout
151  packobj%id = id
152  packobj%ibcnum = ibcnum
153  packobj%ncolbnd = 1
154  packobj%iscloc = 1
155  !
156  ! -- Point IST specific variables
157  istobj%fmi => fmi
158  istobj%mst => mst
159  end subroutine ist_create
160 
161  !> @ brief Allocate and read method for package
162  !!
163  !! Method to allocate and read static data for the package.
164  !!
165  !<
166  subroutine ist_ar(this)
167  ! -- modules
169  use budgetmodule, only: budget_cr
170  ! -- dummy
171  class(gwtisttype), intent(inout) :: this !< GwtIstType object
172  ! -- local
173  integer(I4B) :: n
174  !
175  ! -- Allocate arrays
176  call this%ist_allocate_arrays()
177  !
178  ! -- Now that arrays are allocated, check in the cimnew array to
179  ! the output control manager for subsequent printing/saving
180  call this%ocd%init_dbl('CIM', this%cimnew, this%dis, 'PRINT LAST ', &
181  'COLUMNS 10 WIDTH 11 DIGITS 4 GENERAL ', &
182  this%iout, dhnoflo)
183 
184  ! -- apply user override if provided
185  if (this%lstfmt /= '') then
186  call this%ocd%set_prnfmt(trim(this%lstfmt)//" ", 0)
187  end if
188  !
189  ! -- source the data block
190  call this%source_data()
191  !
192  ! -- set cimnew to the cim start values read from input
193  do n = 1, this%dis%nodes
194  this%cimnew(n) = this%cim(n)
195  end do
196  !
197  ! -- add volfrac to the volfracim accumulator in mst package
198  call this%mst%addto_volfracim(this%volfrac)
199  !
200  ! -- setup the immobile domain budget
201  call budget_cr(this%budget, this%memoryPath)
202  call this%budget%budget_df(nbditems, 'MASS', 'M', bdzone=this%packName)
203  call this%budget%set_ibudcsv(this%ibudcsv)
204  !
205  ! -- Perform a check to ensure that sorption and decay are set
206  ! consistently between the MST and IST packages.
207  if (this%idcy /= this%mst%idcy) then
208  call store_error('DECAY must be activated consistently between the &
209  &MST and IST Packages. Activate or deactivate DECAY for both &
210  &Packages.')
211  end if
212  if (this%isrb /= this%mst%isrb) then
213  call store_error('SORPTION must be activated consistently between the &
214  &MST and IST Packages. Activate or deactivate SORPTION for both &
215  &Packages. If activated, the same type of sorption (LINEAR, &
216  &FREUNDLICH, or LANGMUIR) must be specified in the options block of &
217  &both the MST and IST Packages.')
218  end if
219  if (count_errors() > 0) then
220  call store_error_filename(this%input_fname)
221  end if
222  end subroutine ist_ar
223 
224  !> @ brief Read and prepare method for package
225  !!
226  !! Method to read and prepare package data
227  !!
228  !<
229  subroutine ist_rp(this)
230  ! -- dummy
231  class(gwtisttype), intent(inout) :: this !< GwtIstType object
232  ! -- local
233  ! -- format
234  end subroutine ist_rp
235 
236  !> @ brief Advance the ist package
237  !!
238  !! Advance the IST Package and handle the adaptive time stepping
239  !! feature by copying from new to old or old to new accordingly
240  !!
241  !<
242  subroutine ist_ad(this)
243  ! -- modules
245  ! -- dummy variables
246  class(gwtisttype) :: this !< GwtIstType object
247  ! -- local variables
248  integer(I4B) :: n
249  !
250  ! -- Call parent advance
251  call this%BndType%bnd_ad()
252  !
253  ! -- set independent kiter counter to zero
254  this%kiter = 0
255  !
256  ! -- copy cimnew into cimold or vice versa if this is a repeat of
257  ! a failed time step
258  if (ifailedstepretry == 0) then
259  do n = 1, this%dis%nodes
260  this%cimold(n) = this%cimnew(n)
261  end do
262  else
263  do n = 1, this%dis%nodes
264  this%cimnew(n) = this%cimold(n)
265  end do
266  end if
267  end subroutine ist_ad
268 
269  !> @ brief Fill coefficient method for package
270  !<
271  subroutine ist_fc(this, rhs, ia, idxglo, matrix_sln)
272  ! modules
273  use tdismodule, only: delt
274  ! dummy
275  class(gwtisttype) :: this !< GwtIstType object
276  real(DP), dimension(:), intent(inout) :: rhs !< right-hand side vector for model
277  integer(I4B), dimension(:), intent(in) :: ia !< solution CRS row pointers
278  integer(I4B), dimension(:), intent(in) :: idxglo !< mapping vector for model (local) to solution (global)
279  class(matrixbasetype), pointer :: matrix_sln !< solution coefficient matrix
280  ! local
281  integer(I4B) :: n, idiag
282  real(DP) :: tled
283  real(DP) :: hhcof, rrhs
284  real(DP) :: swt, swtpdt
285  real(DP) :: vcell
286  real(DP) :: thetaim
287  real(DP) :: zetaim
288  real(DP) :: kdnew
289  real(DP) :: kdold
290  real(DP) :: volfracim
291  real(DP) :: rhobim
292  real(DP) :: lambda1im
293  real(DP) :: lambda2im
294  real(DP) :: gamma1im
295  real(DP) :: gamma2im
296  real(DP) :: cimold
297  real(DP) :: f
298  real(DP) :: cimsrbold
299  real(DP) :: cimsrbnew
300  real(DP), dimension(9) :: ddterm
301 
302  ! set variables
303  tled = done / delt
304  this%kiter = this%kiter + 1
305 
306  ! loop through each node and calculate immobile domain contribution
307  ! to hcof and rhs
308  do n = 1, this%dis%nodes
309 
310  ! skip if transport inactive
311  if (this%ibound(n) <= 0) cycle
312 
313  ! calculate new and old water volumes
314  vcell = this%dis%area(n) * (this%dis%top(n) - this%dis%bot(n))
315  swtpdt = this%fmi%gwfsat(n)
316  swt = this%fmi%gwfsatold(n, delt)
317  thetaim = this%get_thetaim(n)
318  idiag = ia(n)
319 
320  ! set exchange coefficient
321  zetaim = this%zetaim(n)
322 
323  ! Add dual domain mass transfer contributions to rhs and hcof
324  ! dcimsrbdc = DZERO
325  kdnew = dzero
326  kdold = dzero
327  volfracim = dzero
328  rhobim = dzero
329  lambda1im = dzero
330  lambda2im = dzero
331  gamma1im = dzero
332  gamma2im = dzero
333 
334  ! set variables for decay of aqueous solute
335  if (this%idcy == 1) lambda1im = this%decay(n)
336  if (this%idcy == 2) then
337  gamma1im = get_zero_order_decay(this%decay(n), this%decaylast(n), &
338  this%kiter, this%cimold(n), &
339  this%cimnew(n), delt)
340  this%decaylast(n) = gamma1im
341  end if
342 
343  ! setup sorption variables
344  if (this%isrb > 0) then
345 
346  ! initialize sorption variables
347  volfracim = this%volfrac(n)
348  rhobim = this%bulk_density(n)
349 
350  ! set isotherm dependent sorption variables
351  select case (this%isrb)
352  case (1)
353  ! linear
354  kdnew = this%distcoef(n)
355  kdold = this%distcoef(n)
356  cimsrbnew = this%cimnew(n) * kdnew
357  cimsrbold = this%cimold(n) * kdold
358  case (2)
359  ! freundlich
360  kdnew = get_freundlich_kd(this%cimnew(n), this%distcoef(n), &
361  this%sp2(n))
362  kdold = get_freundlich_kd(this%cimold(n), this%distcoef(n), &
363  this%sp2(n))
364  cimsrbnew = get_freundlich_conc(this%cimnew(n), this%distcoef(n), &
365  this%sp2(n))
366  cimsrbold = get_freundlich_conc(this%cimold(n), this%distcoef(n), &
367  this%sp2(n))
368  case (3)
369  ! langmuir
370  kdnew = get_langmuir_kd(this%cimnew(n), this%distcoef(n), &
371  this%sp2(n))
372  kdold = get_langmuir_kd(this%cimold(n), this%distcoef(n), &
373  this%sp2(n))
374  cimsrbnew = get_langmuir_conc(this%cimnew(n), this%distcoef(n), &
375  this%sp2(n))
376  cimsrbold = get_langmuir_conc(this%cimold(n), this%distcoef(n), &
377  this%sp2(n))
378  end select
379 
380  ! set decay of sorbed solute parameters
381  if (this%idcy == 1) then
382  lambda2im = this%decay_sorbed(n)
383  else if (this%idcy == 2) then
384  gamma2im = get_zero_order_decay(this%decay_sorbed(n), &
385  this%decayslast(n), &
386  this%kiter, cimsrbold, &
387  cimsrbnew, delt)
388  this%decayslast(n) = gamma2im
389  end if
390  end if
391 
392  ! calculate dual domain terms and get the hcof and rhs contributions
393  call get_ddterm(thetaim, vcell, delt, swtpdt, &
394  volfracim, rhobim, kdnew, kdold, lambda1im, lambda2im, &
395  gamma1im, gamma2im, zetaim, ddterm, f)
396  cimold = this%cimold(n)
397  call get_hcofrhs(ddterm, f, cimold, hhcof, rrhs)
398 
399  ! update solution accumulators
400  call matrix_sln%add_value_pos(idxglo(idiag), hhcof)
401  rhs(n) = rhs(n) + rrhs
402 
403  end do
404 
405  end subroutine ist_fc
406 
407  !> @ brief Calculate package flows.
408  !<
409  subroutine ist_cq(this, x, flowja, iadv)
410  ! modules
411  use tdismodule, only: delt
412  use constantsmodule, only: dzero
413  ! dummy
414  class(gwtisttype), intent(inout) :: this !< GwtIstType object
415  real(DP), dimension(:), intent(in) :: x !< current dependent-variable value
416  real(DP), dimension(:), contiguous, intent(inout) :: flowja !< flow between two connected control volumes
417  integer(I4B), optional, intent(in) :: iadv !< flag that indicates if this is an advance package
418  ! local
419  integer(I4B) :: idiag
420  integer(I4B) :: n
421  real(DP) :: rate
422  real(DP) :: swt, swtpdt
423  real(DP) :: hhcof, rrhs
424  real(DP) :: vcell
425  real(DP) :: thetaim
426  real(DP) :: zetaim
427  real(DP) :: kdnew
428  real(DP) :: kdold
429  real(DP) :: volfracim
430  real(DP) :: rhobim
431  real(DP) :: lambda1im
432  real(DP) :: lambda2im
433  real(DP) :: gamma1im
434  real(DP) :: gamma2im
435  real(DP) :: cimnew
436  real(DP) :: cimold
437  real(DP) :: f
438  real(DP) :: cimsrbold
439  real(DP) :: cimsrbnew
440  real(DP), dimension(9) :: ddterm
441  ! formats
442 
443  ! initialize
444  this%budterm(:, :) = dzero
445 
446  ! Calculate immobile domain transfer rate
447  do n = 1, this%dis%nodes
448 
449  ! skip if transport inactive
450  rate = dzero
451  cimnew = dzero
452  if (this%ibound(n) > 0) then
453 
454  ! calculate new and old water volumes
455  vcell = this%dis%area(n) * (this%dis%top(n) - this%dis%bot(n))
456  swtpdt = this%fmi%gwfsat(n)
457  swt = this%fmi%gwfsatold(n, delt)
458  thetaim = this%get_thetaim(n)
459 
460  ! set exchange coefficient
461  zetaim = this%zetaim(n)
462 
463  ! Calculate exchange with immobile domain
464  rate = dzero
465  hhcof = dzero
466  rrhs = dzero
467  kdnew = dzero
468  kdold = dzero
469  volfracim = dzero
470  rhobim = dzero
471  lambda1im = dzero
472  lambda2im = dzero
473  gamma1im = dzero
474  gamma2im = dzero
475  if (this%idcy == 1) lambda1im = this%decay(n)
476  if (this%idcy == 2) then
477  gamma1im = get_zero_order_decay(this%decay(n), this%decaylast(n), 0, &
478  this%cimold(n), this%cimnew(n), delt)
479  end if
480 
481  ! setup sorption variables
482  if (this%isrb > 0) then
483 
484  ! initialize sorption variables
485  volfracim = this%volfrac(n)
486  rhobim = this%bulk_density(n)
487 
488  ! set isotherm dependent sorption variables
489  select case (this%isrb)
490  case (1)
491  ! linear
492  kdnew = this%distcoef(n)
493  kdold = this%distcoef(n)
494  cimsrbnew = this%cimnew(n) * kdnew
495  cimsrbold = this%cimold(n) * kdold
496  case (2)
497  ! freundlich
498  kdnew = get_freundlich_kd(this%cimnew(n), this%distcoef(n), &
499  this%sp2(n))
500  kdold = get_freundlich_kd(this%cimold(n), this%distcoef(n), &
501  this%sp2(n))
502  cimsrbnew = get_freundlich_conc(this%cimnew(n), this%distcoef(n), &
503  this%sp2(n))
504  cimsrbold = get_freundlich_conc(this%cimold(n), this%distcoef(n), &
505  this%sp2(n))
506  case (3)
507  ! langmuir
508  kdnew = get_langmuir_kd(this%cimnew(n), this%distcoef(n), &
509  this%sp2(n))
510  kdold = get_langmuir_kd(this%cimold(n), this%distcoef(n), &
511  this%sp2(n))
512  cimsrbnew = get_langmuir_conc(this%cimnew(n), this%distcoef(n), &
513  this%sp2(n))
514  cimsrbold = get_langmuir_conc(this%cimold(n), this%distcoef(n), &
515  this%sp2(n))
516  end select
517 
518  ! set decay of sorbed solute parameters
519  if (this%idcy == 1) then
520  lambda2im = this%decay_sorbed(n)
521  else if (this%idcy == 2) then
522  gamma2im = get_zero_order_decay(this%decay_sorbed(n), &
523  this%decayslast(n), &
524  0, cimsrbold, &
525  cimsrbnew, delt)
526  end if
527  end if
528 
529  ! calculate the terms and then get the hcof and rhs contributions
530  call get_ddterm(thetaim, vcell, delt, swtpdt, &
531  volfracim, rhobim, kdnew, kdold, lambda1im, lambda2im, &
532  gamma1im, gamma2im, zetaim, ddterm, f)
533  cimold = this%cimold(n)
534  call get_hcofrhs(ddterm, f, cimold, hhcof, rrhs)
535 
536  ! calculate rate from hcof and rhs
537  rate = hhcof * x(n) - rrhs
538 
539  ! calculate immobile domain concentration
540  cimnew = get_ddconc(ddterm, f, cimold, x(n))
541 
542  ! accumulate the budget terms
543  call accumulate_budterm(this%budterm, ddterm, cimnew, cimold, x(n), &
544  this%idcy)
545  end if
546 
547  ! store rate and add to flowja
548  this%strg(n) = rate
549  idiag = this%dis%con%ia(n)
550  flowja(idiag) = flowja(idiag) + rate
551 
552  ! store immobile domain concentration
553  this%cimnew(n) = cimnew
554 
555  end do
556 
557  ! calculate csrb
558  if (this%isrb /= 0) then
559  call this%ist_calc_csrb(this%cimnew)
560  end if
561 
562  end subroutine ist_cq
563 
564  !> @ brief Calculate immobile sorbed concentration
565  !<
566  subroutine ist_calc_csrb(this, cim)
567  ! -- dummy
568  class(gwtisttype) :: this !< GwtMstType object
569  real(DP), intent(in), dimension(:) :: cim !< immobile domain aqueous concentration at end of this time step
570  ! -- local
571  integer(I4B) :: n
572  real(DP) :: distcoef
573  real(DP) :: csrb
574 
575  ! Calculate sorbed concentration
576  do n = 1, size(cim)
577  csrb = dzero
578  if (this%ibound(n) > 0) then
579  distcoef = this%distcoef(n)
580  if (this%isrb == 1) then
581  csrb = cim(n) * distcoef
582  else if (this%isrb == 2) then
583  csrb = get_freundlich_conc(cim(n), distcoef, this%sp2(n))
584  else if (this%isrb == 3) then
585  csrb = get_langmuir_conc(cim(n), distcoef, this%sp2(n))
586  end if
587  end if
588  this%cimsrb(n) = csrb
589  end do
590 
591  end subroutine ist_calc_csrb
592 
593  !> @ brief Add package flows to model budget.
594  !!
595  !! Add the flow between IST package and the model (ratin and ratout) to the
596  !! model budget.
597  !!
598  !<
599  subroutine ist_bd(this, model_budget)
600  ! -- modules
601  use tdismodule, only: delt
603  ! -- dummy
604  class(gwtisttype) :: this !< GwtIstType object
605  type(budgettype), intent(inout) :: model_budget !< model budget object
606  ! -- local
607  real(DP) :: ratin
608  real(DP) :: ratout
609  integer(I4B) :: isuppress_output
610  isuppress_output = 0
611  call rate_accumulator(this%strg(:), ratin, ratout)
612  call model_budget%addentry(ratin, ratout, delt, this%text, &
613  isuppress_output, this%packName)
614  end subroutine ist_bd
615 
616  !> @ brief Output model flow terms.
617  !!
618  !! Output flow terms between the IST package and model to a binary file and/or
619  !! print flows to the model listing file.
620  !!
621  !<
622  subroutine ist_ot_model_flows(this, icbcfl, ibudfl, icbcun, imap)
623  ! -- modules
624  use constantsmodule, only: dzero
625  ! -- dummy
626  class(gwtisttype) :: this !< GwtIstType object
627  integer(I4B), intent(in) :: icbcfl !< flag for cell-by-cell output
628  integer(I4B), intent(in) :: ibudfl !< flag indication if cell-by-cell data should be saved
629  integer(I4B), intent(in) :: icbcun !< unit number for cell-by-cell output
630  integer(I4B), dimension(:), optional, intent(in) :: imap !< mapping vector
631  ! -- local
632  integer(I4B) :: n
633  integer(I4B) :: ibinun
634  integer(I4B) :: nbound
635  integer(I4B) :: naux
636  real(DP) :: rate
637  real(DP), dimension(0) :: auxrow
638  !
639  ! -- Set unit number for binary output
640  if (this%ipakcb < 0) then
641  ibinun = icbcun
642  elseif (this%ipakcb == 0) then
643  ibinun = 0
644  else
645  ibinun = this%ipakcb
646  end if
647  if (icbcfl == 0) ibinun = 0
648  !
649  ! -- Record the storage rate if requested
650  !
651  ! -- If cell-by-cell flows will be saved as a list, write header.
652  if (ibinun /= 0) then
653  nbound = this%dis%nodes
654  naux = 0
655  call this%dis%record_srcdst_list_header(this%text, this%name_model, &
656  this%name_model, this%name_model, &
657  this%packName, naux, this%auxname, &
658  ibinun, nbound, this%iout)
659  end if
660  !
661  ! -- Calculate immobile domain rhs and hcof
662  do n = 1, this%dis%nodes
663  !
664  ! -- skip if transport inactive
665  rate = dzero
666  if (this%ibound(n) > 0) then
667  !
668  ! -- set rate from this%strg
669  rate = this%strg(n)
670  end if
671  !
672  ! -- If saving cell-by-cell flows in list, write flow
673  if (ibinun /= 0) then
674  call this%dis%record_mf6_list_entry(ibinun, n, n, rate, &
675  naux, auxrow, &
676  olconv=.true., &
677  olconv2=.true.)
678  end if
679  !
680  end do
681  end subroutine ist_ot_model_flows
682 
683  !> @ brief Output dependent variables.
684  !<
685  subroutine ist_ot_dv(this, idvsave, idvprint)
686  ! dummy variables
687  class(gwtisttype) :: this !< BndType object
688  integer(I4B), intent(in) :: idvsave !< flag and unit number for dependent-variable output
689  integer(I4B), intent(in) :: idvprint !< flag indicating if dependent-variable should be written to the model listing file
690 
691  call this%output_immobile_concentration(idvsave, idvprint)
692  call this%output_immobile_sorbate_concentration(idvsave, idvprint)
693 
694  end subroutine ist_ot_dv
695 
696  !> @ brief Output immobile domain aqueous concentration.
697  !<
698  subroutine output_immobile_concentration(this, idvsave, idvprint)
699  ! modules
700  use tdismodule, only: kstp, endofperiod
701  ! dummy variables
702  class(gwtisttype) :: this !< BndType object
703  integer(I4B), intent(in) :: idvsave !< flag and unit number for dependent-variable output
704  integer(I4B), intent(in) :: idvprint !< flag indicating if dependent-variable should be written to the model listing file
705  ! local
706  integer(I4B) :: ipflg
707  integer(I4B) :: ibinun
708  !
709  ! Save cim to a binary file. ibinun is a flag where 1 indicates that
710  ! cim should be written to a binary file if a binary file is open for it.
711  ipflg = 0
712  ibinun = 1
713  if (idvsave == 0) ibinun = 0
714  if (ibinun /= 0) then
715  call this%ocd%ocd_ot(ipflg, kstp, endofperiod, this%iout, &
716  iprint_opt=0, isav_opt=ibinun)
717  end if
718  !
719  ! Print immobile domain concentrations to listing file
720  if (idvprint /= 0) then
721  call this%ocd%ocd_ot(ipflg, kstp, endofperiod, this%iout, &
722  iprint_opt=idvprint, isav_opt=0)
723  end if
724 
725  end subroutine output_immobile_concentration
726 
727  !> @ brief Output immobile domain sorbate concentration.
728  !<
729  subroutine output_immobile_sorbate_concentration(this, idvsave, idvprint)
730  ! modules
731  ! dummy
732  class(gwtisttype) :: this !< BndType object
733  integer(I4B), intent(in) :: idvsave !< flag and unit number for dependent-variable output
734  integer(I4B), intent(in) :: idvprint !< flag indicating if dependent-variable should be written to the model listing file
735  ! local
736  character(len=1) :: cdatafmp = ' ', editdesc = ' '
737  integer(I4B) :: ibinun
738  integer(I4B) :: iprint, nvaluesp, nwidthp
739  real(DP) :: dinact
740 
741  ! Save cimsrb to a binary file. ibinun is a flag where 1 indicates that
742  ! cim should be written to a binary file if a binary file is open for it.
743  ! Set unit number for sorbate output
744  if (this%ioutsorbate /= 0) then
745  ibinun = 1
746  else
747  ibinun = 0
748  end if
749  if (idvsave == 0) ibinun = 0
750 
751  ! save sorbate concentration array
752  if (ibinun /= 0) then
753  iprint = 0
754  dinact = dhnoflo
755  if (this%ioutsorbate /= 0) then
756  ibinun = this%ioutsorbate
757  call this%dis%record_array(this%cimsrb, this%iout, iprint, ibinun, &
758  ' SORBATE', cdatafmp, nvaluesp, &
759  nwidthp, editdesc, dinact)
760  end if
761  end if
762 
764 
765  !> @ brief Output IST package budget summary.
766  !!
767  !! Output advanced boundary package budget summary. This method only needs
768  !! to be overridden for advanced packages that save budget summaries
769  !! to the model listing file.
770  !!
771  !<
772  subroutine ist_ot_bdsummary(this, kstp, kper, iout, ibudfl)
773  ! -- modules
774  use tdismodule, only: delt, totim
775  ! -- dummy variables
776  class(gwtisttype) :: this !< GwtIstType object
777  integer(I4B), intent(in) :: kstp !< time step number
778  integer(I4B), intent(in) :: kper !< period number
779  integer(I4B), intent(in) :: iout !< flag and unit number for the model listing file
780  integer(I4B), intent(in) :: ibudfl !< flag indicating budget should be written
781  ! -- local
782  integer(I4B) :: isuppress_output = 0
783  !
784  ! -- Fill budget terms
785  call this%budget%reset()
786  call this%budget%addentry(this%budterm, delt, budtxt, isuppress_output)
787  !
788  ! -- Write budget to list file
789  call this%budget%finalize_step(delt)
790  if (ibudfl /= 0) then
791  call this%budget%budget_ot(kstp, kper, iout)
792  end if
793  !
794  ! -- Write budget csv
795  call this%budget%writecsv(totim)
796  end subroutine ist_ot_bdsummary
797 
798  !> @ brief Deallocate package memory
799  !!
800  !! Deallocate package scalars and arrays.
801  !!
802  !<
803  subroutine ist_da(this)
804  ! -- modules
806  ! -- dummy
807  class(gwtisttype) :: this !< GwtIstType object
808  !
809  ! -- Deallocate arrays if package was active
810  if (this%inunit > 0) then
811  call mem_deallocate(this%icimout)
812  call mem_deallocate(this%ibudgetout)
813  call mem_deallocate(this%ibudcsv)
814  call mem_deallocate(this%ioutsorbate)
815  call mem_deallocate(this%idcy)
816  call mem_deallocate(this%isrb)
817  call mem_deallocate(this%kiter)
818  call mem_deallocate(this%cim)
819  call mem_deallocate(this%cimnew)
820  call mem_deallocate(this%cimold)
821  call mem_deallocate(this%cimsrb)
822  call mem_deallocate(this%zetaim)
823  call mem_deallocate(this%porosity)
824  call mem_deallocate(this%volfrac)
825  call mem_deallocate(this%bulk_density)
826  call mem_deallocate(this%distcoef)
827  call mem_deallocate(this%sp2)
828  call mem_deallocate(this%decay)
829  call mem_deallocate(this%decaylast)
830  call mem_deallocate(this%decayslast)
831  call mem_deallocate(this%decay_sorbed)
832  call mem_deallocate(this%strg)
833  this%fmi => null()
834  this%mst => null()
835  end if
836  !
837  ! -- Scalars
838  !
839  ! -- Objects
840  call this%budget%budget_da()
841  deallocate (this%budget)
842  call this%ocd%ocd_da()
843  deallocate (this%ocd)
844  !
845  ! -- deallocate parent
846  call this%BndType%bnd_da()
847  end subroutine ist_da
848 
849  !> @ brief Allocate package scalars
850  !!
851  !! Allocate and initialize package scalars.
852  !!
853  !<
854  subroutine allocate_scalars(this)
855  ! -- modules
858  ! -- dummy
859  class(gwtisttype) :: this !< GwtIstType object
860  ! -- local
861  !
862  ! -- call standard BndType allocate scalars
863  call this%BndType%allocate_scalars()
864  !
865  ! -- Allocate
866  call mem_allocate(this%icimout, 'ICIMOUT', this%memoryPath)
867  call mem_allocate(this%ibudgetout, 'IBUDGETOUT', this%memoryPath)
868  call mem_allocate(this%ibudcsv, 'IBUDCSV', this%memoryPath)
869  call mem_allocate(this%ioutsorbate, 'IOUTSORBATE', this%memoryPath)
870  call mem_allocate(this%isrb, 'ISRB', this%memoryPath)
871  call mem_allocate(this%idcy, 'IDCY', this%memoryPath)
872  call mem_allocate(this%kiter, 'KITER', this%memoryPath)
873  !
874  ! -- Initialize
875  this%lstfmt = ''
876  this%icimout = 0
877  this%ibudgetout = 0
878  this%ibudcsv = 0
879  this%ioutsorbate = 0
880  this%isrb = 0
881  this%idcy = 0
882  this%kiter = 0
883  !
884  ! -- Create the ocd object, which is used to manage printing and saving
885  ! of the immobile domain concentrations
886  call ocd_cr(this%ocd)
887  end subroutine allocate_scalars
888 
889  !> @ brief Allocate package arrays
890  !!
891  !! Allocate and initialize package arrays.
892  !!
893  !<
894  subroutine ist_allocate_arrays(this)
895  ! -- modules
897  ! -- dummy
898  class(gwtisttype), intent(inout) :: this !< GwtIstType object
899  ! -- local
900  integer(I4B) :: n
901  !
902  ! -- call standard BndType allocate scalars
903  ! nbound and maxbound are 0 in order to keep memory footprint low
904  call this%BndType%allocate_arrays()
905  !
906  ! -- allocate ist arrays of size nodes
907  call mem_allocate(this%strg, this%dis%nodes, 'STRG', this%memoryPath)
908  call mem_allocate(this%cim, this%dis%nodes, 'CIM', this%memoryPath)
909  call mem_allocate(this%cimnew, this%dis%nodes, 'CIMNEW', this%memoryPath)
910  call mem_allocate(this%cimold, this%dis%nodes, 'CIMOLD', this%memoryPath)
911  call mem_allocate(this%porosity, this%dis%nodes, 'POROSITY', this%memoryPath)
912  call mem_allocate(this%zetaim, this%dis%nodes, 'ZETAIM', this%memoryPath)
913  call mem_allocate(this%volfrac, this%dis%nodes, 'VOLFRAC', this%memoryPath)
914  if (this%isrb == 0) then
915  call mem_allocate(this%bulk_density, 1, 'BULK_DENSITY', this%memoryPath)
916  call mem_allocate(this%distcoef, 1, 'DISTCOEF', this%memoryPath)
917  call mem_allocate(this%sp2, 1, 'SP2', this%memoryPath)
918  call mem_allocate(this%cimsrb, 1, 'SORBATE', this%memoryPath)
919  else
920  call mem_allocate(this%bulk_density, this%dis%nodes, 'BULK_DENSITY', &
921  this%memoryPath)
922  call mem_allocate(this%distcoef, this%dis%nodes, 'DISTCOEF', &
923  this%memoryPath)
924  call mem_allocate(this%cimsrb, this%dis%nodes, 'SORBATE', &
925  this%memoryPath)
926  if (this%isrb == 1) then
927  call mem_allocate(this%sp2, 1, 'SP2', this%memoryPath)
928  else
929  call mem_allocate(this%sp2, this%dis%nodes, 'SP2', this%memoryPath)
930  end if
931  end if
932  if (this%idcy == 0) then
933  call mem_allocate(this%decay, 1, 'DECAY', this%memoryPath)
934  call mem_allocate(this%decaylast, 1, 'DECAYLAST', this%memoryPath)
935  else
936  call mem_allocate(this%decay, this%dis%nodes, 'DECAY', this%memoryPath)
937  call mem_allocate(this%decaylast, this%dis%nodes, 'DECAYLAST', &
938  this%memoryPath)
939  end if
940  if (this%isrb == 0 .and. this%idcy == 0) then
941  call mem_allocate(this%decayslast, 1, 'DECAYSLAST', this%memoryPath)
942  else
943  call mem_allocate(this%decayslast, this%dis%nodes, 'DECAYSLAST', &
944  this%memoryPath)
945  end if
946  call mem_allocate(this%decay_sorbed, 1, 'DECAY_SORBED', this%memoryPath)
947  !
948  ! -- initialize
949  do n = 1, this%dis%nodes
950  this%strg(n) = dzero
951  this%cim(n) = dzero
952  this%cimnew(n) = dzero
953  this%cimold(n) = dzero
954  this%porosity(n) = dzero
955  this%zetaim(n) = dzero
956  this%volfrac(n) = dzero
957  end do
958  do n = 1, size(this%bulk_density)
959  this%bulk_density(n) = dzero
960  this%distcoef(n) = dzero
961  this%cimsrb(n) = dzero
962  end do
963  do n = 1, size(this%sp2)
964  this%sp2(n) = dzero
965  end do
966  do n = 1, size(this%decay)
967  this%decay(n) = dzero
968  this%decaylast(n) = dzero
969  end do
970  do n = 1, size(this%decayslast)
971  this%decayslast(n) = dzero
972  end do
973  !
974  ! -- Set pointers
975  this%ocd%dis => this%dis
976  end subroutine ist_allocate_arrays
977 
978  !> @ brief Source options for package
979  !!
980  !! Method to source options for the package.
981  !<
982  subroutine source_options(this)
983  ! -- modules
986  use openspecmodule, only: access, form
990  ! -- dummy
991  class(gwtisttype), intent(inout) :: this
992  ! -- locals
993  character(len=LINELENGTH) :: prnfmt
994  integer(I4B), pointer :: columns, width, digits
995  type(gwtistparamfoundtype) :: found
996  character(len=LENVARNAME), dimension(3) :: sorption_method = &
997  &[character(len=LENVARNAME) :: 'LINEAR', 'FREUNDLICH', 'LANGMUIR']
998  character(len=linelength) :: sorbate_fname, cim6_fname, budget_fname, &
999  budgetcsv_fname
1000  allocate (columns)
1001  allocate (width)
1002  allocate (digits)
1003  !
1004  ! -- update defaults with memory sourced values
1005  call mem_set_value(this%ipakcb, 'SAVE_FLOWS', this%input_mempath, &
1006  found%save_flows)
1007  call mem_set_value(budget_fname, 'BUDGETFILE', this%input_mempath, &
1008  found%budgetfile)
1009  call mem_set_value(budgetcsv_fname, 'BUDGETCSVFILE', this%input_mempath, &
1010  found%budgetcsvfile)
1011  call mem_set_value(this%isrb, 'SORPTION', this%input_mempath, &
1012  sorption_method, found%sorption)
1013  call mem_set_value(this%idcy, 'ORDER1_DECAY', this%input_mempath, &
1014  found%order1_decay)
1015  call mem_set_value(this%idcy, 'ORDER0_DECAY', this%input_mempath, &
1016  found%order0_decay)
1017  call mem_set_value(cim6_fname, 'CIMFILE', this%input_mempath, &
1018  found%cimfile)
1019  call mem_set_value(sorbate_fname, 'SORBATEFILE', this%input_mempath, &
1020  found%sorbatefile)
1021  call mem_set_value(columns, 'COLUMNS', this%input_mempath, &
1022  found%columns)
1023  call mem_set_value(width, 'WIDTH', this%input_mempath, &
1024  found%width)
1025  call mem_set_value(digits, 'DIGITS', this%input_mempath, &
1026  found%digits)
1027  call mem_set_value(prnfmt, 'FORMAT', this%input_mempath, &
1028  found%format)
1029 
1030  ! -- found side effects
1031  if (found%save_flows) this%ipakcb = -1
1032  if (found%budgetfile) then
1033  call assign_iounit(this%ibudgetout, this%inunit, "BUDGET fileout")
1034  call openfile(this%ibudgetout, this%iout, budget_fname, 'DATA(BINARY)', &
1035  form, access, 'REPLACE', mode_opt=mnormal)
1036  end if
1037  if (found%budgetcsvfile) then
1038  call assign_iounit(this%ibudcsv, this%inunit, "BUDGETCSV fileout")
1039  call openfile(this%ibudcsv, this%iout, budgetcsv_fname, 'CSV', &
1040  filstat_opt='REPLACE')
1041  end if
1042  if (found%sorption) then
1043  if (this%isrb == 0) then
1044  call store_error('Unknown sorption type was specified. &
1045  &Sorption must be specified as LINEAR, &
1046  &FREUNDLICH, or LANGMUIR.')
1047  call store_error_filename(this%input_fname)
1048  end if
1049  end if
1050  if (found%order1_decay) this%idcy = 1
1051  if (found%order0_decay) this%idcy = 2
1052  if (found%cimfile) then
1053  call this%ocd%set_ocfile(cim6_fname, this%iout)
1054  end if
1055  if (found%columns .and. found%width .and. &
1056  found%digits .and. found%format) then
1057  write (this%lstfmt, '(a,i0,a,i0,a,i0,a)') 'COLUMNS ', columns, &
1058  ' WIDTH ', width, ' DIGITS ', digits, ' '//trim(prnfmt)
1059  end if
1060  if (found%sorbatefile) then
1061  this%ioutsorbate = getunit()
1062  call openfile(this%ioutsorbate, this%iout, sorbate_fname, &
1063  'DATA(BINARY)', form, access, 'REPLACE', mode_opt=mnormal)
1064  end if
1065  !
1066  ! -- log options
1067  if (this%iout > 0) then
1068  call this%log_options(found, cim6_fname, budget_fname, &
1069  budgetcsv_fname, sorbate_fname)
1070  end if
1071 
1072  deallocate (columns)
1073  deallocate (width)
1074  deallocate (digits)
1075  end subroutine source_options
1076 
1077  !> @brief Log user options to list file
1078  !<
1079  subroutine log_options(this, found, cim6_fname, budget_fname, &
1080  budgetcsv_fname, sorbate_fname)
1082  class(gwtisttype), intent(inout) :: this
1083  type(gwtistparamfoundtype), intent(in) :: found
1084  character(len=*), intent(in) :: cim6_fname
1085  character(len=*), intent(in) :: budget_fname
1086  character(len=*), intent(in) :: budgetcsv_fname
1087  character(len=*), intent(in) :: sorbate_fname
1088  ! -- formats
1089  character(len=*), parameter :: fmtisvflow = &
1090  "(4x,'CELL-BY-CELL FLOW INFORMATION WILL BE SAVED TO BINARY FILE &
1091  &WHENEVER ICBCFL IS NOT ZERO.')"
1092  character(len=*), parameter :: fmtlinear = &
1093  &"(4x,'LINEAR SORPTION IS SELECTED. ')"
1094  character(len=*), parameter :: fmtfreundlich = &
1095  &"(4x,'FREUNDLICH SORPTION IS ACTIVE. ')"
1096  character(len=*), parameter :: fmtlangmuir = &
1097  &"(4x,'LANGMUIR SORPTION IS ACTIVE. ')"
1098  character(len=*), parameter :: fmtidcy1 = &
1099  &"(4x,'FIRST-ORDER DECAY IS ACTIVE. ')"
1100  character(len=*), parameter :: fmtidcy2 = &
1101  &"(4x,'ZERO-ORDER DECAY IS ACTIVE. ')"
1102  character(len=*), parameter :: fmtistbin = &
1103  "(4x, 'IST ', 1x, a, 1x, ' WILL BE SAVED TO FILE: ', a, &
1104  &/4x, 'OPENED ON UNIT: ', I0)"
1105 
1106  write (this%iout, '(1x,a)') 'PROCESSING IMMOBILE STORAGE AND TRANSFER &
1107  &OPTIONS'
1108  if (found%save_flows) then
1109  write (this%iout, fmtisvflow)
1110  end if
1111  if (found%budgetfile) then
1112  write (this%iout, fmtistbin) 'BUDGET', trim(adjustl(budget_fname)), &
1113  this%ibudgetout
1114  end if
1115  if (found%budgetcsvfile) then
1116  write (this%iout, fmtistbin) 'BUDGET CSV', trim(adjustl(budgetcsv_fname)), &
1117  this%ibudcsv
1118  end if
1119  if (found%sorption) then
1120  select case (this%isrb)
1121  case (1)
1122  write (this%iout, fmtlinear)
1123  case (2)
1124  write (this%iout, fmtfreundlich)
1125  case (3)
1126  write (this%iout, fmtlangmuir)
1127  end select
1128  end if
1129  if (found%order1_decay) then
1130  write (this%iout, fmtidcy1)
1131  end if
1132  if (found%order0_decay) then
1133  write (this%iout, fmtidcy2)
1134  end if
1135  if (found%sorbatefile) then
1136  write (this%iout, fmtistbin) &
1137  'SORBATE', sorbate_fname, this%ioutsorbate
1138  end if
1139  write (this%iout, '(1x,a)') 'END OF IMMOBILE STORAGE AND TRANSFER &
1140  &OPTIONS'
1141  end subroutine log_options
1142 
1143  !> @ brief Read options for package
1144  !!
1145  !! Read options for boundary packages.
1146  !!
1147  !<
1148  subroutine read_options(this)
1149  ! -- modules
1150  ! -- dummy
1151  class(gwtisttype), intent(inout) :: this !< GwtIstType object
1152 
1153  ! -- source options
1154  call this%source_options()
1155  end subroutine read_options
1156 
1157  !> @ brief Source data for package
1158  !!
1159  !! Method to source data for the package.
1160  !<
1161  subroutine source_data(this)
1162  ! -- modules
1163  use constantsmodule, only: linelength
1164  use simvariablesmodule, only: errmsg, warnmsg
1170  ! -- dummy
1171  class(gwtisttype) :: this
1172  ! -- locals
1173  !character(len=LINELENGTH) :: errmsg
1174  type(gwtistparamfoundtype) :: found
1175  integer(I4B) :: asize
1176  integer(I4B), dimension(:), pointer, contiguous :: map
1177  !
1178  ! -- set map to convert user input data into reduced data
1179  map => null()
1180  if (this%dis%nodes < this%dis%nodesuser) map => this%dis%nodeuser
1181  !
1182  ! -- reallocate
1183  if (this%isrb == 0) then
1184  call get_isize('BULK_DENSITY', this%input_mempath, asize)
1185  if (asize > 0) &
1186  call mem_reallocate(this%bulk_density, this%dis%nodes, &
1187  'BULK_DENSITY', this%memoryPath)
1188  call get_isize('DISTCOEF', this%input_mempath, asize)
1189  if (asize > 0) &
1190  call mem_reallocate(this%distcoef, this%dis%nodes, 'DISTCOEF', &
1191  this%memoryPath)
1192  end if
1193  if (this%idcy == 0) then
1194  call get_isize('DECAY', this%input_mempath, asize)
1195  if (asize > 0) &
1196  call mem_reallocate(this%decay, this%dis%nodes, 'DECAY', this%memoryPath)
1197  end if
1198  call get_isize('DECAY_SORBED', this%input_mempath, asize)
1199  if (asize > 0) then
1200  call mem_reallocate(this%decay_sorbed, this%dis%nodes, &
1201  'DECAY_SORBED', this%memoryPath)
1202  end if
1203  if (this%isrb < 2) then
1204  call get_isize('SP2', this%input_mempath, asize)
1205  if (asize > 0) &
1206  call mem_reallocate(this%sp2, this%dis%nodes, 'SP2', this%memoryPath)
1207  end if
1208  !
1209  ! -- update defaults with memory sourced values
1210  call mem_set_value(this%porosity, 'POROSITY', this%input_mempath, map, &
1211  found%porosity)
1212  call mem_set_value(this%volfrac, 'VOLFRAC', this%input_mempath, map, &
1213  found%volfrac)
1214  call mem_set_value(this%zetaim, 'ZETAIM', this%input_mempath, map, &
1215  found%zetaim)
1216  call mem_set_value(this%cim, 'CIM', this%input_mempath, map, &
1217  found%cim)
1218  call mem_set_value(this%decay, 'DECAY', this%input_mempath, map, &
1219  found%decay)
1220  call mem_set_value(this%decay_sorbed, 'DECAY_SORBED', this%input_mempath, &
1221  map, found%decay_sorbed)
1222  call mem_set_value(this%bulk_density, 'BULK_DENSITY', this%input_mempath, &
1223  map, found%bulk_density)
1224  call mem_set_value(this%distcoef, 'DISTCOEF', this%input_mempath, map, &
1225  found%distcoef)
1226  call mem_set_value(this%sp2, 'SP2', this%input_mempath, map, &
1227  found%sp2)
1228 
1229  ! -- log options
1230  if (this%iout > 0) then
1231  call this%log_data(found)
1232  end if
1233 
1234  ! -- Check for required sorption variables
1235  if (this%isrb > 0) then
1236  if (.not. found%bulk_density) then
1237  write (errmsg, '(a)') 'Sorption is active but BULK_DENSITY &
1238  &not specified. BULK_DENSITY must be specified in GRIDDATA block.'
1239  call store_error(errmsg)
1240  end if
1241  if (.not. found%distcoef) then
1242  write (errmsg, '(a)') 'Sorption is active but distribution &
1243  &coefficient not specified. DISTCOEF must be specified in &
1244  &GRIDDATA block.'
1245  call store_error(errmsg)
1246  end if
1247  if (this%isrb > 1) then
1248  if (.not. found%sp2) then
1249  write (errmsg, '(a)') 'Freundlich or langmuir sorption is active &
1250  &but SP2 not specified. SP2 must be specified in &
1251  &GRIDDATA block.'
1252  call store_error(errmsg)
1253  end if
1254  end if
1255  else
1256  if (found%bulk_density) then
1257  write (warnmsg, '(a)') 'Sorption is not active but &
1258  &BULK_DENSITY was specified. BULK_DENSITY will have no affect on &
1259  &simulation results.'
1260  call store_warning(warnmsg)
1261  write (this%iout, '(1x,a)') 'WARNING. '//warnmsg
1262  end if
1263  if (found%distcoef) then
1264  write (warnmsg, '(a)') 'Sorption is not active but &
1265  &distribution coefficient was specified. DISTCOEF will have &
1266  &no affect on simulation results.'
1267  call store_warning(warnmsg)
1268  write (this%iout, '(1x,a)') 'WARNING. '//warnmsg
1269  end if
1270  if (found%sp2) then
1271  write (warnmsg, '(a)') 'Sorption is not active but &
1272  &SP2 was specified. SP2 will have &
1273  &no affect on simulation results.'
1274  call store_warning(warnmsg)
1275  write (this%iout, '(1x,a)') 'WARNING. '//warnmsg
1276  end if
1277  end if
1278 
1279  ! -- Check for required decay/production rate coefficients
1280  if (this%idcy > 0) then
1281  if (.not. found%decay) then
1282  write (errmsg, '(a)') 'First or zero order decay is &
1283  &active but the first rate coefficient is not specified. DECAY &
1284  &must be specified in GRIDDATA block.'
1285  call store_error(errmsg)
1286  end if
1287  if (.not. found%decay_sorbed) then
1288  !
1289  ! -- If DECAY_SORBED not specified and sorption is active, then
1290  ! terminate with an error
1291  write (errmsg, '(a)') 'DECAY_SORBED not provided in GRIDDATA &
1292  &block but decay and sorption are active. Specify DECAY_SORBED &
1293  &in GRIDDATA block.'
1294  call store_error(errmsg)
1295  end if
1296  else
1297  if (found%decay) then
1298  write (warnmsg, '(a)') 'First- or zero-order decay &
1299  &is not active but decay was specified. DECAY will &
1300  &have no affect on simulation results.'
1301  call store_warning(warnmsg)
1302  write (this%iout, '(1x,a)') 'WARNING. '//warnmsg
1303  end if
1304  if (found%decay_sorbed) then
1305  write (warnmsg, '(a)') 'First- or zero-order decay &
1306  &is not active but DECAY_SORBED was specified. &
1307  &DECAY_SORBED will have no affect on simulation results.'
1308  call store_warning(warnmsg)
1309  write (this%iout, '(1x,a)') 'WARNING. '//warnmsg
1310  end if
1311  end if
1312 
1313  ! -- Check for required dual domain arrays or warn if they are specified
1314  ! but won't be used.
1315  if (.not. found%cim) then
1316  write (this%iout, '(1x,a)') 'Warning. Dual domain is active but &
1317  &initial immobile domain concentration was not specified. &
1318  &Setting CIM to zero.'
1319  end if
1320  if (.not. found%zetaim) then
1321  write (errmsg, '(a)') 'Dual domain is active but dual &
1322  &domain mass transfer rate (ZETAIM) was not specified. ZETAIM &
1323  &must be specified in GRIDDATA block.'
1324  call store_error(errmsg)
1325  end if
1326  if (.not. found%porosity) then
1327  write (errmsg, '(a)') 'Dual domain is active but &
1328  &immobile domain POROSITY was not specified. POROSITY &
1329  &must be specified in GRIDDATA block.'
1330  call store_error(errmsg)
1331  end if
1332  if (.not. found%volfrac) then
1333  write (errmsg, '(a)') 'Dual domain is active but &
1334  &immobile domain VOLFRAC was not specified. VOLFRAC &
1335  &must be specified in GRIDDATA block. This is a new &
1336  &requirement for MODFLOW versions later than version &
1337  &6.4.1.'
1338  call store_error(errmsg)
1339  end if
1340 
1341  ! -- terminate if errors
1342  if (count_errors() > 0) then
1343  call store_error_filename(this%input_fname)
1344  end if
1345  end subroutine source_data
1346 
1347  !> @brief Log user data to list file
1348  !<
1349  subroutine log_data(this, found)
1351  class(gwtisttype), intent(inout) :: this
1352  type(gwtistparamfoundtype), intent(in) :: found
1353 
1354  write (this%iout, '(1x,a)') 'PROCESSING GRIDDATA'
1355  if (found%porosity) then
1356  write (this%iout, '(4x,a)') 'MOBILE DOMAIN POROSITY set from input file'
1357  end if
1358  if (found%volfrac) then
1359  write (this%iout, '(4x,a)') 'VOLFRAC set from input file'
1360  end if
1361  if (found%zetaim) then
1362  write (this%iout, '(4x,a)') 'ZETAIM set from input file'
1363  end if
1364  if (found%cim) then
1365  write (this%iout, '(4x,a)') 'CIM set from input file'
1366  end if
1367  if (found%decay) then
1368  write (this%iout, '(4x,a)') 'DECAY RATE set from input file'
1369  end if
1370  if (found%decay_sorbed) then
1371  write (this%iout, '(4x,a)') 'DECAY SORBED RATE set from input file'
1372  end if
1373  if (found%bulk_density) then
1374  write (this%iout, '(4x,a)') 'BULK DENSITY set from input file'
1375  end if
1376  if (found%distcoef) then
1377  write (this%iout, '(4x,a)') 'DISTRIBUTION COEFFICIENT set from input file'
1378  end if
1379  if (found%sp2) then
1380  write (this%iout, '(4x,a)') 'SECOND SORPTION PARAM set from input file'
1381  end if
1382  write (this%iout, '(1x,a)') 'END PROCESSING GRIDDATA'
1383  end subroutine log_data
1384 
1385  !> @ brief Read dimensions for package
1386  !!
1387  !! Read dimensions for package.
1388  !!
1389  !<
1390  subroutine ist_read_dimensions(this)
1391  ! -- dummy
1392  class(gwtisttype), intent(inout) :: this !< GwtIstType object
1393  ! -- local
1394  ! -- format
1395  end subroutine ist_read_dimensions
1396 
1397  !> @ brief Return thetaim
1398  !!
1399  !! Calculate and return thetaim, volume of immobile voids per aquifer volume
1400  !!
1401  !<
1402  function get_thetaim(this, node) result(thetaim)
1403  ! -- modules
1404  ! -- dummy
1405  class(gwtisttype) :: this !< GwtIstType object
1406  integer(I4B), intent(in) :: node !< node number
1407  ! -- return
1408  real(dp) :: thetaim
1409  !
1410  thetaim = this%volfrac(node) * this%porosity(node)
1411  end function get_thetaim
1412 
1413  !> @ brief Calculate immobile domain equation terms
1414  !!
1415  !! This subroutine calculates the immobile domain (or dual domain) terms.
1416  !! The resulting ddterm and f terms are described in the GWT model report.
1417  !! The terms are concentration coefficients used in the balance equation
1418  !! for the immobile domain.
1419  !!
1420  !<
1421  subroutine get_ddterm(thetaim, vcell, delt, swtpdt, &
1422  volfracim, rhobim, kdnew, kdold, &
1423  lambda1im, lambda2im, &
1424  gamma1im, gamma2im, zetaim, ddterm, f)
1425  ! -- dummy
1426  real(DP), intent(in) :: thetaim !< immobile domain porosity
1427  real(DP), intent(in) :: vcell !< volume of cell
1428  real(DP), intent(in) :: delt !< length of time step
1429  real(DP), intent(in) :: swtpdt !< cell saturation at end of time step
1430  real(DP), intent(in) :: volfracim !< volume fraction of immobile domain
1431  real(DP), intent(in) :: rhobim !< bulk density for the immobile domain (fim * rhob)
1432  real(DP), intent(in) :: kdnew !< effective distribution coefficient for new time
1433  real(DP), intent(in) :: kdold !< effective distribution coefficient for old time
1434  real(DP), intent(in) :: lambda1im !< first-order decay rate in aqueous phase
1435  real(DP), intent(in) :: lambda2im !< first-order decay rate in sorbed phase
1436  real(DP), intent(in) :: gamma1im !< zero-order decay rate in aqueous phase
1437  real(DP), intent(in) :: gamma2im !< zero-order decay rate in sorbed phase
1438  real(DP), intent(in) :: zetaim !< transfer coefficient between mobile and immobile domains
1439  real(DP), dimension(:), intent(inout) :: ddterm !< nine terms comprising the balance equation of the immobile domain
1440  real(DP), intent(inout) :: f !< the f term used to calculate the immobile domain concentration
1441  ! -- local
1442  real(DP) :: tled
1443  !
1444  ! -- initialize
1445  tled = done / delt
1446  !
1447  ! -- Calculate terms. These terms correspond to the concentration
1448  ! coefficients in equation 7-4 of the GWT model report. However,
1449  ! an updated equation is presented as 9-9 in the supplemental technical
1450  ! information guide (mf6suptechinfo.pdf)
1451  ddterm(1) = thetaim * vcell * tled
1452  ddterm(2) = thetaim * vcell * tled
1453  ddterm(3) = volfracim * rhobim * vcell * kdnew * tled
1454  ddterm(4) = volfracim * rhobim * vcell * kdold * tled
1455  ddterm(5) = thetaim * lambda1im * vcell
1456  ddterm(6) = lambda2im * volfracim * rhobim * kdnew * vcell
1457  ddterm(7) = thetaim * gamma1im * vcell
1458  ddterm(8) = gamma2im * volfracim * rhobim * vcell
1459  ddterm(9) = vcell * swtpdt * zetaim
1460  !
1461  ! -- calculate denominator term, f
1462  f = ddterm(1) + ddterm(3) + ddterm(5) + ddterm(6) + ddterm(9)
1463  end subroutine get_ddterm
1464 
1465  !> @ brief Calculate the hcof and rhs terms for immobile domain
1466  !!
1467  !! This subroutine calculates the hcof and rhs terms that must
1468  !! be added to the solution system of equations
1469  !!
1470  !<
1471  subroutine get_hcofrhs(ddterm, f, cimold, hcof, rhs)
1472  ! -- dummy
1473  real(DP), dimension(:), intent(in) :: ddterm !< terms comprising the balance equation of the immobile domain
1474  real(DP), intent(in) :: f !< the f term used to calculate the immobile domain concentration
1475  real(DP), intent(in) :: cimold !< immobile domain concentration at end of last time step
1476  real(DP), intent(inout) :: hcof !< calculated contribution for the a-matrix diagonal position
1477  real(DP), intent(inout) :: rhs !< calculated contribution for the solution right-hand side
1478  !
1479  ! -- calculate hcof
1480  hcof = ddterm(9)**2 / f - ddterm(9)
1481  !
1482  ! -- calculate rhs, and switch the sign because this term needs to
1483  ! be moved to the left hand side
1484  rhs = (ddterm(2) + ddterm(4)) * cimold - ddterm(7) - ddterm(8)
1485  rhs = rhs * ddterm(9) / f
1486  rhs = -rhs
1487  end subroutine get_hcofrhs
1488 
1489  !> @ brief Calculate the immobile domain concentration
1490  !!
1491  !! This function calculates the concentration of the immobile domain.
1492  !!
1493  !<
1494  function get_ddconc(ddterm, f, cimold, cnew) result(cimnew)
1495  ! -- dummy
1496  real(dp), dimension(:), intent(in) :: ddterm !< terms comprising the balance equation of the immobile domain
1497  real(dp), intent(in) :: f !< the f term used to calculate the immobile domain concentration
1498  real(dp), intent(in) :: cimold !< immobile domain concentration at end of last time step
1499  real(dp), intent(in) :: cnew !< concentration of the mobile domain at the end of the time step
1500  ! -- result
1501  real(dp) :: cimnew !< calculated concentration of the immobile domain
1502  ! -- local
1503  !
1504  ! -- calculate ddconc
1505  cimnew = (ddterm(2) + ddterm(4)) * cimold + ddterm(9) * cnew - ddterm(7) &
1506  - ddterm(8)
1507  cimnew = cimnew / f
1508  end function get_ddconc
1509 
1510  !> @ brief Calculate the immobile domain budget terms
1511  !!
1512  !! This subroutine calculates and accumulates the immobile domain
1513  !! budget terms into the budterm accumulator
1514  !!
1515  !<
1516  subroutine accumulate_budterm(budterm, ddterm, cimnew, cimold, cnew, idcy)
1517  ! -- modules
1518  ! -- dummy
1519  real(DP), dimension(:, :), intent(inout) :: budterm !<
1520  real(DP), dimension(:), intent(in) :: ddterm !< terms comprising the balance equation of the immobile domain
1521  real(DP), intent(in) :: cimnew !< immobile domain concenration at the end of this time step
1522  real(DP), intent(in) :: cimold !< immobile domain concentration at end of last time step
1523  real(DP), intent(in) :: cnew !< mobile domain concentration at the end of this time step
1524  integer(I4B), intent(in) :: idcy !< order of decay rate (0:none, 1:first, 2:zero)
1525  ! -- local
1526  real(DP) :: rate
1527  integer(I4B) :: i
1528  !
1529  ! -- calculate STORAGE-AQUEOUS
1530  i = 1
1531  rate = -ddterm(1) * cimnew + ddterm(2) * cimold
1532  if (rate > dzero) then
1533  budterm(1, i) = budterm(1, i) + rate
1534  else
1535  budterm(2, i) = budterm(2, i) - rate
1536  end if
1537  !
1538  ! -- calculate STORAGE-SORBED
1539  i = 2
1540  rate = -ddterm(3) * cimnew + ddterm(4) * cimold
1541  if (rate > dzero) then
1542  budterm(1, i) = budterm(1, i) + rate
1543  else
1544  budterm(2, i) = budterm(2, i) - rate
1545  end if
1546  !
1547  ! -- calculate DECAY-AQUEOUS
1548  i = 3
1549  rate = dzero
1550  if (idcy == 1) then
1551  rate = -ddterm(5) * cimnew
1552  else if (idcy == 2) then
1553  rate = -ddterm(7)
1554  else
1555  rate = dzero
1556  end if
1557  if (rate > dzero) then
1558  budterm(1, i) = budterm(1, i) + rate
1559  else
1560  budterm(2, i) = budterm(2, i) - rate
1561  end if
1562  !
1563  ! -- calculate DECAY-SORBED
1564  i = 4
1565  if (idcy == 1) then
1566  rate = -ddterm(6) * cimnew
1567  else if (idcy == 2) then
1568  rate = -ddterm(8)
1569  else
1570  rate = dzero
1571  end if
1572  if (rate > dzero) then
1573  budterm(1, i) = budterm(1, i) + rate
1574  else
1575  budterm(2, i) = budterm(2, i) - rate
1576  end if
1577  !
1578  ! -- calculate MOBILE-DOMAIN
1579  i = 5
1580  rate = ddterm(9) * cnew - ddterm(9) * cimnew
1581  if (rate > dzero) then
1582  budterm(1, i) = budterm(1, i) + rate
1583  else
1584  budterm(2, i) = budterm(2, i) - rate
1585  end if
1586  !
1587  end subroutine accumulate_budterm
1588 
1589 end module gwtistmodule
This module contains the base boundary package.
This module contains the BudgetModule.
Definition: Budget.f90:20
subroutine, public budget_cr(this, name_model)
@ brief Create a new budget object
Definition: Budget.f90:84
subroutine, public rate_accumulator(flow, rin, rout)
@ brief Rate accumulator subroutine
Definition: Budget.f90:632
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
@ mnormal
normal output mode
Definition: Constants.f90:206
integer(i4b), parameter lenpackagename
maximum length of the package name
Definition: Constants.f90:23
integer(i4b), parameter lenbigline
maximum length of a big line
Definition: Constants.f90:15
real(dp), parameter dhnoflo
real no flow constant
Definition: Constants.f90:93
integer(i4b), parameter lenvarname
maximum length of a variable name
Definition: Constants.f90:17
real(dp), parameter dhalf
real constant 1/2
Definition: Constants.f90:68
integer(i4b), parameter lenftype
maximum length of a package type (DIS, WEL, OC, etc.)
Definition: Constants.f90:39
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
– @ brief Immobile Storage and Transfer (IST) Module
Definition: gwt-ist.f90:14
subroutine ist_da(this)
@ brief Deallocate package memory
Definition: gwt-ist.f90:804
subroutine log_data(this, found)
Log user data to list file.
Definition: gwt-ist.f90:1350
subroutine ist_calc_csrb(this, cim)
@ brief Calculate immobile sorbed concentration
Definition: gwt-ist.f90:567
subroutine ist_rp(this)
@ brief Read and prepare method for package
Definition: gwt-ist.f90:230
real(dp) function get_ddconc(ddterm, f, cimold, cnew)
@ brief Calculate the immobile domain concentration
Definition: gwt-ist.f90:1495
real(dp) function get_thetaim(this, node)
@ brief Return thetaim
Definition: gwt-ist.f90:1403
subroutine source_data(this)
@ brief Source data for package
Definition: gwt-ist.f90:1162
subroutine get_hcofrhs(ddterm, f, cimold, hcof, rhs)
@ brief Calculate the hcof and rhs terms for immobile domain
Definition: gwt-ist.f90:1472
subroutine get_ddterm(thetaim, vcell, delt, swtpdt, volfracim, rhobim, kdnew, kdold, lambda1im, lambda2im, gamma1im, gamma2im, zetaim, ddterm, f)
@ brief Calculate immobile domain equation terms
Definition: gwt-ist.f90:1425
integer(i4b), parameter nbditems
Definition: gwt-ist.f90:37
subroutine output_immobile_sorbate_concentration(this, idvsave, idvprint)
@ brief Output immobile domain sorbate concentration.
Definition: gwt-ist.f90:730
subroutine source_options(this)
@ brief Source options for package
Definition: gwt-ist.f90:983
subroutine ist_ot_model_flows(this, icbcfl, ibudfl, icbcun, imap)
@ brief Output model flow terms.
Definition: gwt-ist.f90:623
subroutine ist_read_dimensions(this)
@ brief Read dimensions for package
Definition: gwt-ist.f90:1391
subroutine log_options(this, found, cim6_fname, budget_fname, budgetcsv_fname, sorbate_fname)
Log user options to list file.
Definition: gwt-ist.f90:1081
subroutine allocate_scalars(this)
@ brief Allocate package scalars
Definition: gwt-ist.f90:855
character(len=lenftype) ftype
Definition: gwt-ist.f90:35
subroutine ist_ar(this)
@ brief Allocate and read method for package
Definition: gwt-ist.f90:167
subroutine ist_ot_bdsummary(this, kstp, kper, iout, ibudfl)
@ brief Output IST package budget summary.
Definition: gwt-ist.f90:773
subroutine ist_ot_dv(this, idvsave, idvprint)
@ brief Output dependent variables.
Definition: gwt-ist.f90:686
subroutine ist_allocate_arrays(this)
@ brief Allocate package arrays
Definition: gwt-ist.f90:895
subroutine ist_cq(this, x, flowja, iadv)
@ brief Calculate package flows.
Definition: gwt-ist.f90:410
subroutine ist_ad(this)
@ brief Advance the ist package
Definition: gwt-ist.f90:243
subroutine accumulate_budterm(budterm, ddterm, cimnew, cimold, cnew, idcy)
@ brief Calculate the immobile domain budget terms
Definition: gwt-ist.f90:1517
subroutine ist_bd(this, model_budget)
@ brief Add package flows to model budget.
Definition: gwt-ist.f90:600
subroutine ist_fc(this, rhs, ia, idxglo, matrix_sln)
@ brief Fill coefficient method for package
Definition: gwt-ist.f90:272
character(len=lenbudtxt), dimension(nbditems) budtxt
Definition: gwt-ist.f90:38
subroutine read_options(this)
@ brief Read options for package
Definition: gwt-ist.f90:1149
subroutine, public ist_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, mempath, fmi, mst)
@ brief Create a new package object
Definition: gwt-ist.f90:120
character(len=lenpackagename) text
Definition: gwt-ist.f90:36
subroutine output_immobile_concentration(this, idvsave, idvprint)
@ brief Output immobile domain aqueous concentration.
Definition: gwt-ist.f90:699
– @ brief Mobile Storage and Transfer (MST) Module
Definition: gwt-mst.f90:10
real(dp) function get_zero_order_decay(decay_rate_usr, decay_rate_last, kiter, cold, cnew, delt)
@ brief Calculate zero-order decay rate and constrain if necessary
Definition: gwt-mst.f90:1632
real(dp) function get_freundlich_derivative(conc, kf, a)
@ brief Calculate sorption derivative using Freundlich
Definition: gwt-mst.f90:1555
real(dp) function get_langmuir_kd(conc, kl, sbar)
@ brief Get effective Langmuir distribution coefficient
Definition: gwt-mst.f90:1608
real(dp) function get_freundlich_conc(conc, kf, a)
@ brief Calculate sorption concentration using Freundlich
Definition: gwt-mst.f90:1517
real(dp) function get_freundlich_kd(conc, kf, a)
@ brief Get effective Freundlich distribution coefficient
Definition: gwt-mst.f90:1591
real(dp) function get_langmuir_derivative(conc, kl, sbar)
@ brief Calculate sorption derivative using Langmuir
Definition: gwt-mst.f90:1574
real(dp) function get_langmuir_conc(conc, kl, sbar)
@ brief Calculate sorption concentration using Langmuir
Definition: gwt-mst.f90:1536
subroutine, public assign_iounit(iounit, errunit, description)
@ brief assign io unit number
integer(i4b) function, public getunit()
Get a free unit number.
subroutine, public openfile(iu, iout, fname, ftype, fmtarg_opt, accarg_opt, filstat_opt, mode_opt)
Open a file.
Definition: InputOutput.f90:30
This module defines variable data types.
Definition: kind.f90:8
subroutine, public get_isize(name, mem_path, isize)
@ brief Get the number of elements for this variable
character(len=20) access
Definition: OpenSpec.f90:7
character(len=20) form
Definition: OpenSpec.f90:7
Output control data module.
subroutine, public ocd_cr(ocdobj)
@ brief Create a new output control data type.
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_warning(msg, substring)
Store warning message.
Definition: Sim.f90:236
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
integer(i4b) function, public count_errors()
Return number of errors.
Definition: Sim.f90:59
subroutine, public store_error_filename(filename, terminate)
Store the erroring file name.
Definition: Sim.f90:203
This module contains simulation variables.
Definition: SimVariables.f90:9
character(len=maxcharlen) errmsg
error message string
integer(i4b) ifailedstepretry
current retry for this time step
character(len=maxcharlen) warnmsg
warning message string
logical(lgp), pointer, public endofperiod
flag indicating end of stress period
Definition: tdis.f90:27
real(dp), pointer, public totim
time relative to start of simulation
Definition: tdis.f90:32
integer(i4b), pointer, public kstp
current time step number
Definition: tdis.f90:24
real(dp), pointer, public delt
length of the current time step
Definition: tdis.f90:29
@ brief BndType
Derived type for the Budget object.
Definition: Budget.f90:39
@ brief Immobile storage and transfer
Definition: gwt-ist.f90:53
@ brief Mobile storage and transfer
Definition: gwt-mst.f90:50