MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
swf-zdg.f90
Go to the documentation of this file.
1 !> @brief This module contains the ZDG package methods
2 !!
3 !! This module can be used to represent outflow from streams using
4 !! a zero-depth-gradient boundary.
5 !!
6 !<
8  ! -- modules
9  use kindmodule, only: dp, i4b
10  use constantsmodule, only: dzero, dem1, done, lenftype, dnodata, &
12  use simvariablesmodule, only: errmsg
15  use bndmodule, only: bndtype
16  use bndextmodule, only: bndexttype
19  use observemodule, only: observetype
25  use basedismodule, only: disbasetype
26  use disv1dmodule, only: disv1dtype
27  use swfcxsmodule, only: swfcxstype
28  !
29  implicit none
30  !
31  private
32  public :: zdg_create
33  !
34  character(len=LENFTYPE) :: ftype = 'ZDG' !< package ftype
35  character(len=16) :: text = ' ZDG' !< package flow text string
36  !
37  type, extends(bndexttype) :: swfzdgtype
38 
39  integer(I4B), dimension(:), pointer, contiguous :: idcxs => null() !< cross section id
40  real(dp), dimension(:), pointer, contiguous :: width => null() !< channel width
41  real(dp), dimension(:), pointer, contiguous :: slope => null() !< channel slope
42  real(dp), dimension(:), pointer, contiguous :: rough => null() !< channel roughness
43  real(dp), pointer :: unitconv => null() !< conversion factor for roughness to length and time units of meters and seconds
44 
45  ! -- pointers other objects
46  type(disv1dtype), pointer :: disv1d
47  type(swfcxstype), pointer :: cxs
48 
49  contains
50  procedure :: allocate_scalars => zdg_allocate_scalars
51  procedure :: allocate_arrays => zdg_allocate_arrays
52  procedure :: source_options => zdg_options
53  procedure :: log_zdg_options
54  procedure :: bnd_rp => zdg_rp
55  procedure :: bnd_cf => zdg_cf
56  procedure :: bnd_fc => zdg_fc
57  procedure :: bnd_da => zdg_da
58  procedure :: define_listlabel
59  procedure :: bound_value => zdg_bound_value
60  ! -- methods for observations
61  procedure, public :: bnd_obs_supported => zdg_obs_supported
62  procedure, public :: bnd_df_obs => zdg_df_obs
63  procedure, public :: bnd_bd_obs => zdg_bd_obs
64  ! -- methods for time series
65  procedure, public :: bnd_rp_ts => zdg_rp_ts
66  ! -- private
67  procedure, private :: qcalc
68  end type swfzdgtype
69 
70 contains
71 
72  !> @ brief Create a new package object
73  !!
74  !! Create a new ZDG Package object
75  !!
76  !<
77  subroutine zdg_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, &
78  mempath, dis, cxs, unitconv)
79  ! -- dummy variables
80  class(bndtype), pointer :: packobj !< pointer to default package type
81  integer(I4B), intent(in) :: id !< package id
82  integer(I4B), intent(in) :: ibcnum !< boundary condition number
83  integer(I4B), intent(in) :: inunit !< unit number of ZDG package input file
84  integer(I4B), intent(in) :: iout !< unit number of model listing file
85  character(len=*), intent(in) :: namemodel !< model name
86  character(len=*), intent(in) :: pakname !< package name
87  character(len=*), intent(in) :: mempath !< input mempath
88  class(disbasetype), pointer, intent(inout) :: dis !< the pointer to the discretization
89  type(swfcxstype), pointer, intent(in) :: cxs !< the pointer to the cxs package
90  real(dp), intent(in) :: unitconv !< unit conversion for roughness
91  ! -- local variables
92  type(swfzdgtype), pointer :: zdgobj
93  !
94  ! -- allocate the object and assign values to object variables
95  allocate (zdgobj)
96  packobj => zdgobj
97  !
98  ! -- create name and memory path
99  call packobj%set_names(ibcnum, namemodel, pakname, ftype, mempath)
100  packobj%text = text
101  !
102  ! -- allocate scalars
103  call zdgobj%allocate_scalars()
104  !
105  ! -- initialize package
106  call packobj%pack_initialize()
107 
108  packobj%inunit = inunit
109  packobj%iout = iout
110  packobj%id = id
111  packobj%ibcnum = ibcnum
112  packobj%ncolbnd = 1
113  packobj%iscloc = 1
114  packobj%ictMemPath = create_mem_path(namemodel, 'DFW')
115  !
116  ! -- store pointer to disv1d
117  select type (dis)
118  type is (disv1dtype)
119  zdgobj%disv1d => dis
120  end select
121  !
122  ! -- store pointer to cxs
123  zdgobj%cxs => cxs
124  !
125  ! -- store unit conversion
126  zdgobj%unitconv = unitconv
127  end subroutine zdg_create
128 
129  !> @ brief Allocate scalars
130  !!
131  !! Allocate and initialize scalars for the ZDG package. The base model
132  !! allocate scalars method is also called.
133  !!
134  !<
135  subroutine zdg_allocate_scalars(this)
136  ! -- modules
138  ! -- dummy variables
139  class(swfzdgtype) :: this !< SwfZdgType object
140  !
141  ! -- call base type allocate scalars
142  call this%BndExtType%allocate_scalars()
143  !
144  ! -- allocate the object and assign values to object variables
145  call mem_allocate(this%unitconv, 'UNITCONV', this%memoryPath)
146  !
147  ! -- Set values
148  this%unitconv = dzero
149  end subroutine zdg_allocate_scalars
150 
151  !> @ brief Allocate arrays
152  !!
153  !! Allocate and initialize arrays for the SWF package
154  !!
155  !<
156  subroutine zdg_allocate_arrays(this, nodelist, auxvar)
157  ! -- modules
159  ! -- dummy
160  class(swfzdgtype) :: this
161  integer(I4B), dimension(:), pointer, contiguous, optional :: nodelist
162  real(DP), dimension(:, :), pointer, contiguous, optional :: auxvar
163  ! -- local
164  !
165  ! -- call BndExtType allocate scalars
166  call this%BndExtType%allocate_arrays(nodelist, auxvar)
167  !
168  ! -- set array input context pointer
169  call mem_setptr(this%idcxs, 'IDCXS', this%input_mempath)
170  call mem_setptr(this%width, 'WIDTH', this%input_mempath)
171  call mem_setptr(this%slope, 'SLOPE', this%input_mempath)
172  call mem_setptr(this%rough, 'ROUGH', this%input_mempath)
173  !
174  ! -- checkin array input context pointer
175  call mem_checkin(this%idcxs, 'IDCXS', this%memoryPath, &
176  'IDCXS', this%input_mempath)
177  call mem_checkin(this%width, 'WIDTH', this%memoryPath, &
178  'WIDTH', this%input_mempath)
179  call mem_checkin(this%slope, 'SLOPE', this%memoryPath, &
180  'SLOPE', this%input_mempath)
181  call mem_checkin(this%rough, 'ROUGH', this%memoryPath, &
182  'ROUGH', this%input_mempath)
183  end subroutine zdg_allocate_arrays
184 
185  !> @ brief Deallocate package memory
186  !!
187  !! Deallocate SWF package scalars and arrays.
188  !!
189  !<
190  subroutine zdg_da(this)
191  ! -- modules
193  ! -- dummy variables
194  class(swfzdgtype) :: this !< SwfZdgType object
195  !
196  ! -- Deallocate parent package
197  call this%BndExtType%bnd_da()
198  !
199  ! -- arrays
200  call mem_deallocate(this%idcxs, 'IDCXS', this%memoryPath)
201  call mem_deallocate(this%width, 'WIDTH', this%memoryPath)
202  call mem_deallocate(this%slope, 'SLOPE', this%memoryPath)
203  call mem_deallocate(this%rough, 'ROUGH', this%memoryPath)
204  !
205  ! -- scalars
206  call mem_deallocate(this%unitconv)
207  end subroutine zdg_da
208 
209  !> @ brief Source additional options for package
210  !!
211  !! Source additional options for SWF package.
212  !!
213  !<
214  subroutine zdg_options(this)
215  ! -- modules
216  use inputoutputmodule, only: urword
219  ! -- dummy variables
220  class(swfzdgtype), intent(inout) :: this !< SwfZdgType object
221  ! -- local variables
222  type(swfzdgparamfoundtype) :: found
223  ! -- formats
224  !
225  ! -- source base BndExtType options
226  call this%BndExtType%source_options()
227  !
228  ! -- source options from input context
229  ! none
230  !
231  ! -- log SWF specific options
232  call this%log_zdg_options(found)
233  end subroutine zdg_options
234 
235  !> @ brief Log SWF specific package options
236  !<
237  subroutine log_zdg_options(this, found)
238  ! -- modules
240  ! -- dummy variables
241  class(swfzdgtype), intent(inout) :: this !< BndExtType object
242  type(swfzdgparamfoundtype), intent(in) :: found
243  ! -- local variables
244  ! -- format
245  !
246  ! -- log found options
247  write (this%iout, '(/1x,a)') 'PROCESSING '//trim(adjustl(this%text)) &
248  //' OPTIONS'
249  !
250  ! if (found%mover) then
251  ! write (this%iout, '(4x,A)') 'MOVER OPTION ENABLED'
252  ! end if
253  !
254  ! -- close logging block
255  write (this%iout, '(1x,a)') &
256  'END OF '//trim(adjustl(this%text))//' OPTIONS'
257  end subroutine log_zdg_options
258 
259  !> @ brief SWF read and prepare
260  !!
261  !<
262  subroutine zdg_rp(this)
263  use tdismodule, only: kper
264  ! -- dummy
265  class(swfzdgtype), intent(inout) :: this
266  ! -- local
267  !
268  if (this%iper /= kper) return
269  !
270  ! -- Call the parent class read and prepare
271  call this%BndExtType%bnd_rp()
272  !
273  ! -- Write the list to iout if requested
274  if (this%iprpak /= 0) then
275  call this%write_list()
276  end if
277  end subroutine zdg_rp
278 
279  !> @ brief Formulate the package hcof and rhs terms.
280  !!
281  !! Formulate the hcof and rhs terms for the ZDG package that will be
282  !! added to the coefficient matrix and right-hand side vector.
283  !!
284  !<
285  subroutine zdg_cf(this)
286  ! modules
288  use smoothingmodule, only: squadratic
289  ! dummy variables
290  class(swfzdgtype) :: this !< SwfZdgType object
291  ! local variables
292  integer(I4B) :: i, node
293  real(DP) :: q
294  real(DP) :: qeps
295  real(DP) :: absdhdxsq
296  real(DP) :: depth
297  real(DP) :: derv
298  real(DP) :: eps
299  real(DP) :: range = 1.d-6
300  real(DP) :: dydx
301  real(DP) :: smooth_factor
302  !
303  ! -- Return if no inflows
304  if (this%nbound == 0) return
305  !
306  ! -- Calculate hcof and rhs for each zdg entry
307  do i = 1, this%nbound
308 
309  node = this%nodelist(i)
310  if (this%ibound(node) <= 0) then
311  this%hcof(i) = dzero
312  this%rhs(i) = dzero
313  cycle
314  end if
315 
316  ! -- calculate terms and add to hcof and rhs
317  absdhdxsq = this%slope(i)**dhalf
318  depth = this%xnew(node) - this%dis%bot(node)
319 
320  ! smooth the depth
321  call squadratic(depth, range, dydx, smooth_factor)
322  depth = depth * smooth_factor
323 
324  ! -- calculate unperturbed q
325  q = -this%qcalc(i, depth, this%unitconv)
326 
327  ! -- calculate perturbed q
328  eps = get_perturbation(depth)
329  qeps = -this%qcalc(i, depth + eps, this%unitconv)
330 
331  ! -- calculate derivative
332  derv = (qeps - q) / eps
333 
334  ! -- add terms to hcof and rhs
335  this%hcof(i) = derv
336  this%rhs(i) = -q + derv * this%xnew(node)
337 
338  end do
339  end subroutine zdg_cf
340 
341  ! !> @brief Calculate flow
342  !!
343  !! Calculate volumetric flow rate for the zero-depth gradient
344  !! condition. Flow is positive.
345  ! !<
346  function qcalc(this, i, depth, unitconv) result(q)
347  ! dummy
348  class(swfzdgtype) :: this
349  integer(I4B), intent(in) :: i !< boundary number
350  real(dp), intent(in) :: depth !< simulated depth (stage - elevation) in reach n for this iteration
351  real(dp), intent(in) :: unitconv !< conversion factor for roughness to length and time units of meters and seconds
352  ! return
353  real(dp) :: q
354  ! local
355  integer(I4B) :: idcxs
356  real(dp) :: width
357  real(dp) :: rough
358  real(dp) :: slope
359  real(dp) :: conveyance
360 
361  idcxs = this%idcxs(i)
362  width = this%width(i)
363  rough = this%rough(i)
364  slope = this%slope(i)
365  conveyance = this%cxs%get_conveyance(idcxs, width, depth, rough)
366  q = conveyance * slope**dhalf * unitconv
367 
368  end function qcalc
369 
370  !> @ brief Copy hcof and rhs terms into solution.
371  !!
372  !! Add the hcof and rhs terms for the ZDG package to the
373  !! coefficient matrix and right-hand side vector.
374  !!
375  !<
376  subroutine zdg_fc(this, rhs, ia, idxglo, matrix_sln)
377  ! -- dummy variables
378  class(swfzdgtype) :: this !< SwfZdgType object
379  real(DP), dimension(:), intent(inout) :: rhs !< right-hand side vector for model
380  integer(I4B), dimension(:), intent(in) :: ia !< solution CRS row pointers
381  integer(I4B), dimension(:), intent(in) :: idxglo !< mapping vector for model (local) to solution (global)
382  class(matrixbasetype), pointer :: matrix_sln !< solution coefficient matrix
383  ! -- local variables
384  integer(I4B) :: i
385  integer(I4B) :: n
386  integer(I4B) :: ipos
387  !
388  ! -- pakmvrobj fc
389  if (this%imover == 1) then
390  call this%pakmvrobj%fc()
391  end if
392  !
393  ! -- Copy package rhs and hcof into solution rhs and amat
394  do i = 1, this%nbound
395  n = this%nodelist(i)
396  rhs(n) = rhs(n) + this%rhs(i)
397  ipos = ia(n)
398  call matrix_sln%add_value_pos(idxglo(ipos), this%hcof(i))
399  !
400  ! -- If mover is active and this zdg item is discharging,
401  ! store available water (as positive value).
402  if (this%imover == 1 .and. this%rhs(i) > dzero) then
403  call this%pakmvrobj%accumulate_qformvr(i, this%rhs(i))
404  end if
405  end do
406  end subroutine zdg_fc
407 
408  !> @ brief Define the list label for the package
409  !!
410  !! Method defined the list label for the ZDG package. The list label is
411  !! the heading that is written to iout when PRINT_INPUT option is used.
412  !!
413  !<
414  subroutine define_listlabel(this)
415  ! -- dummy variables
416  class(swfzdgtype), intent(inout) :: this !< SwfZdgType object
417  !
418  ! -- create the header list label
419  this%listlabel = trim(this%filtyp)//' NO.'
420  if (this%dis%ndim == 3) then
421  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'LAYER'
422  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'ROW'
423  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'COL'
424  elseif (this%dis%ndim == 2) then
425  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'LAYER'
426  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'CELL2D'
427  else
428  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'NODE'
429  end if
430  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'FLOW RATE'
431  if (this%inamedbound == 1) then
432  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'BOUNDARY NAME'
433  end if
434  end subroutine define_listlabel
435 
436  ! -- Procedures related to observations
437 
438  !> @brief Determine if observations are supported.
439  !!
440  !! Function to determine if observations are supported by the ZDG package.
441  !! Observations are supported by the ZDG package.
442  !!
443  !! @return zdg_obs_supported boolean indicating if observations are supported
444  !!
445  !<
446  logical function zdg_obs_supported(this)
447  ! -- dummy variables
448  class(swfzdgtype) :: this !< SwfZdgType object
449  !
450  ! -- set boolean
451  zdg_obs_supported = .true.
452  end function zdg_obs_supported
453 
454  !> @brief Define the observation types available in the package
455  !!
456  !! Method to define the observation types available in the ZDG package.
457  !!
458  !<
459  subroutine zdg_df_obs(this)
460  ! -- dummy variables
461  class(swfzdgtype) :: this !< SwfZdgType object
462  ! -- local variables
463  integer(I4B) :: indx
464  !
465  ! -- initialize observations
466  call this%obs%StoreObsType('zdg', .true., indx)
467  this%obs%obsData(indx)%ProcessIdPtr => defaultobsidprocessor
468  !
469  ! -- Store obs type and assign procedure pointer
470  ! for to-mvr observation type.
471  call this%obs%StoreObsType('to-mvr', .true., indx)
472  this%obs%obsData(indx)%ProcessIdPtr => defaultobsidprocessor
473  end subroutine zdg_df_obs
474 
475  !> @brief Save observations for the package
476  !!
477  !! Method to save simulated values for the ZDG package.
478  !!
479  !<
480  subroutine zdg_bd_obs(this)
481  ! -- dummy variables
482  class(swfzdgtype) :: this !< SwfZdgType object
483  ! -- local variables
484  integer(I4B) :: i
485  integer(I4B) :: n
486  integer(I4B) :: jj
487  real(DP) :: v
488  type(observetype), pointer :: obsrv => null()
489  !
490  ! -- clear the observations
491  call this%obs%obs_bd_clear()
492  !
493  ! -- Save simulated values for all of package's observations.
494  do i = 1, this%obs%npakobs
495  obsrv => this%obs%pakobs(i)%obsrv
496  if (obsrv%BndFound) then
497  do n = 1, obsrv%indxbnds_count
498  v = dnodata
499  jj = obsrv%indxbnds(n)
500  select case (obsrv%ObsTypeId)
501  case ('TO-MVR')
502  if (this%imover == 1) then
503  v = this%pakmvrobj%get_qtomvr(jj)
504  if (v > dzero) then
505  v = -v
506  end if
507  end if
508  case ('ZDG')
509  v = this%simvals(jj)
510  case default
511  errmsg = 'Unrecognized observation type: '//trim(obsrv%ObsTypeId)
512  call store_error(errmsg)
513  end select
514  call this%obs%SaveOneSimval(obsrv, v)
515  end do
516  else
517  call this%obs%SaveOneSimval(obsrv, dnodata)
518  end if
519  end do
520  end subroutine zdg_bd_obs
521 
522  ! -- Procedure related to time series
523 
524  !> @brief Assign time series links for the package
525  !!
526  !! Assign the time series links for the ZDG package. Only
527  !! the Q variable can be defined with time series.
528  !!
529  !<
530  subroutine zdg_rp_ts(this)
531  ! -- dummy variables
532  class(swfzdgtype), intent(inout) :: this !< SwfZdgType object
533  ! -- local variables
534  integer(I4B) :: i, nlinks
535  type(timeserieslinktype), pointer :: tslink => null()
536  !
537  ! -- set up the time series links
538  nlinks = this%TsManager%boundtslinks%Count()
539  do i = 1, nlinks
540  tslink => gettimeserieslinkfromlist(this%TsManager%boundtslinks, i)
541  if (associated(tslink)) then
542  if (tslink%JCol == 1) then
543  tslink%Text = 'Q'
544  end if
545  end if
546  end do
547  end subroutine zdg_rp_ts
548 
549  !> @ brief Return a bound value
550  !!
551  !! Return a bound value associated with an ncolbnd index
552  !! and row.
553  !!
554  !<
555  function zdg_bound_value(this, col, row) result(bndval)
556  ! -- modules
557  use constantsmodule, only: dzero
558  ! -- dummy variables
559  class(swfzdgtype), intent(inout) :: this !< BndExtType object
560  integer(I4B), intent(in) :: col
561  integer(I4B), intent(in) :: row
562  ! -- result
563  real(dp) :: bndval
564  !
565  select case (col)
566  case (1)
567  bndval = this%idcxs(row)
568  case (2)
569  bndval = this%width(row)
570  case (3)
571  bndval = this%slope(row)
572  case (4)
573  bndval = this%rough(row)
574  case default
575  errmsg = 'Programming error. ZDG bound value requested column '&
576  &'outside range of ncolbnd (1).'
577  call store_error(errmsg)
578  call store_error_filename(this%input_fname)
579  end select
580  end function zdg_bound_value
581 
582 end module swfzdgmodule
This module contains block parser methods.
Definition: BlockParser.f90:7
This module contains the extended boundary package.
This module contains the base boundary package.
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
real(dp), parameter dtwothirds
real constant 2/3
Definition: Constants.f90:70
real(dp), parameter dnodata
real no data constant
Definition: Constants.f90:95
real(dp), parameter dem1
real constant 1e-1
Definition: Constants.f90:103
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
real(dp), parameter done
real constant 1
Definition: Constants.f90:76
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
subroutine, public urword(line, icol, istart, istop, ncode, n, r, iout, in)
Extract a word from a string.
This module defines variable data types.
Definition: kind.f90:8
real(dp) function, public get_perturbation(x)
Calculate a numerical perturbation given the value of x.
Definition: MathUtil.f90:372
character(len=lenmempath) function create_mem_path(component, subcomponent, context)
returns the path to the memory object
This module contains the derived types ObserveType and ObsDataType.
Definition: Observe.f90:15
This module contains the derived type ObsType.
Definition: Obs.f90:127
subroutine, public defaultobsidprocessor(obsrv, dis, inunitobs, iout)
@ brief Process IDstring provided for each observation
Definition: Obs.f90:246
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
subroutine, public 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
subroutine squadratic(x, range, dydx, y)
@ brief sQuadratic
real(dp) function sqsaturationderivative(top, bot, x, c1, c2)
@ brief sQSaturationDerivative
real(dp) function sqsaturation(top, bot, x, c1, c2)
@ brief sQSaturation
This module contains the ZDG package methods.
Definition: swf-zdg.f90:7
subroutine zdg_allocate_scalars(this)
@ brief Allocate scalars
Definition: swf-zdg.f90:136
subroutine define_listlabel(this)
@ brief Define the list label for the package
Definition: swf-zdg.f90:415
logical function zdg_obs_supported(this)
Determine if observations are supported.
Definition: swf-zdg.f90:447
subroutine zdg_cf(this)
@ brief Formulate the package hcof and rhs terms.
Definition: swf-zdg.f90:286
subroutine zdg_fc(this, rhs, ia, idxglo, matrix_sln)
@ brief Copy hcof and rhs terms into solution.
Definition: swf-zdg.f90:377
real(dp) function zdg_bound_value(this, col, row)
@ brief Return a bound value
Definition: swf-zdg.f90:556
subroutine log_zdg_options(this, found)
@ brief Log SWF specific package options
Definition: swf-zdg.f90:238
subroutine, public zdg_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, mempath, dis, cxs, unitconv)
@ brief Create a new package object
Definition: swf-zdg.f90:79
subroutine zdg_rp_ts(this)
Assign time series links for the package.
Definition: swf-zdg.f90:531
character(len=16) text
package flow text string
Definition: swf-zdg.f90:35
subroutine zdg_da(this)
@ brief Deallocate package memory
Definition: swf-zdg.f90:191
subroutine zdg_options(this)
@ brief Source additional options for package
Definition: swf-zdg.f90:215
subroutine zdg_rp(this)
@ brief SWF read and prepare
Definition: swf-zdg.f90:263
character(len=lenftype) ftype
package ftype
Definition: swf-zdg.f90:34
subroutine zdg_allocate_arrays(this, nodelist, auxvar)
@ brief Allocate arrays
Definition: swf-zdg.f90:157
subroutine zdg_bd_obs(this)
Save observations for the package.
Definition: swf-zdg.f90:481
real(dp) function qcalc(this, i, depth, unitconv)
Definition: swf-zdg.f90:347
subroutine zdg_df_obs(this)
Define the observation types available in the package.
Definition: swf-zdg.f90:460
integer(i4b), pointer, public kper
current stress period number
Definition: tdis.f90:23
type(timeserieslinktype) function, pointer, public gettimeserieslinkfromlist(list, indx)
Get time series link from a list.
@ brief BndType