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