MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
gwf-drn.f90
Go to the documentation of this file.
1 module drnmodule
2  use kindmodule, only: dp, i4b
3  use constantsmodule, only: dzero, done, dtwo, &
5  use simvariablesmodule, only: errmsg
10  use bndmodule, only: bndtype
11  use bndextmodule, only: bndexttype
14  !
15  implicit none
16  !
17  private
18  public :: drn_create
19  public :: drntype
20  !
21  character(len=LENFTYPE) :: ftype = 'DRN'
22  character(len=LENPACKAGENAME) :: text = ' DRN'
23  !
24  type, extends(bndexttype) :: drntype
25 
26  real(dp), dimension(:), pointer, contiguous :: elev => null() !< DRN elevation
27  real(dp), dimension(:), pointer, contiguous :: cond => null() !< DRN conductance at aquifer interface
28  integer(I4B), pointer :: iauxddrncol => null()
29  integer(I4B), pointer :: icubic_scaling => null()
30 
31  contains
32 
33  procedure :: allocate_scalars => drn_allocate_scalars
34  procedure :: allocate_arrays => drn_allocate_arrays
35  procedure :: source_options => drn_options
36  procedure :: log_drn_options
37  procedure :: bnd_rp => drn_rp
38  procedure :: bnd_ck => drn_ck
39  procedure :: bnd_cf => drn_cf
40  procedure :: bnd_fc => drn_fc
41  procedure :: bnd_fn => drn_fn
42  procedure :: bnd_da => drn_da
43  procedure :: define_listlabel
44  procedure :: get_drain_elevations
45  procedure :: get_drain_factor
46  procedure :: bound_value => drn_bound_value
47  procedure :: cond_mult
48  ! -- methods for observations
49  procedure, public :: bnd_obs_supported => drn_obs_supported
50  procedure, public :: bnd_df_obs => drn_df_obs
51  procedure, public :: drn_store_user_cond
52  end type drntype
53 
54 contains
55 
56  !> @brief Create a New Drn Package and point packobj to the new package
57  !<
58  subroutine drn_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, &
59  mempath)
60  ! -- dummy
61  class(bndtype), pointer :: packobj
62  integer(I4B), intent(in) :: id
63  integer(I4B), intent(in) :: ibcnum
64  integer(I4B), intent(in) :: inunit
65  integer(I4B), intent(in) :: iout
66  character(len=*), intent(in) :: namemodel
67  character(len=*), intent(in) :: pakname
68  character(len=*), intent(in) :: mempath
69  ! -- local
70  type(drntype), pointer :: drnobj
71  !
72  ! -- allocate the object and assign values to object variables
73  allocate (drnobj)
74  packobj => drnobj
75  !
76  ! -- create name and memory path
77  call packobj%set_names(ibcnum, namemodel, pakname, ftype, mempath)
78  packobj%text = text
79  !
80  ! -- allocate scalars
81  call drnobj%allocate_scalars()
82  !s
83  ! -- initialize package
84  call packobj%pack_initialize()
85  !
86  ! -- initialize
87  packobj%inunit = inunit
88  packobj%iout = iout
89  packobj%id = id
90  packobj%ibcnum = ibcnum
91  packobj%ictMemPath = create_mem_path(namemodel, 'NPF')
92  end subroutine drn_create
93 
94  !> @brief Deallocate memory
95  !<
96  subroutine drn_da(this)
97  ! -- modules
99  ! -- dummy
100  class(drntype) :: this
101  !
102  ! -- Deallocate parent package
103  call this%BndExtType%bnd_da()
104  !
105  ! -- scalars
106  call mem_deallocate(this%iauxddrncol)
107  call mem_deallocate(this%icubic_scaling)
108  !
109  ! -- arrays
110  call mem_deallocate(this%elev, 'ELEV', this%memoryPath)
111  call mem_deallocate(this%cond, 'COND', this%memoryPath)
112  end subroutine drn_da
113 
114  !> @brief Allocate package scalar members
115  !<
116  subroutine drn_allocate_scalars(this)
117  ! -- modules
119  ! -- dummy
120  class(drntype) :: this
121  !
122  ! -- call base type allocate scalars
123  call this%BndExtType%allocate_scalars()
124  !
125  ! -- allocate the object and assign values to object variables
126  call mem_allocate(this%iauxddrncol, 'IAUXDDRNCOL', this%memoryPath)
127  call mem_allocate(this%icubic_scaling, 'ICUBIC_SCALING', this%memoryPath)
128  !
129  ! -- Set values
130  this%iauxddrncol = 0
131  if (this%inewton /= 0) then
132  this%icubic_scaling = 1
133  else
134  this%icubic_scaling = 0
135  end if
136  end subroutine drn_allocate_scalars
137 
138  !> @brief Allocate package arrays
139  !<
140  subroutine drn_allocate_arrays(this, nodelist, auxvar)
141  ! -- modules
143  ! -- dummy
144  class(drntype) :: this
145  integer(I4B), dimension(:), pointer, contiguous, optional :: nodelist
146  real(DP), dimension(:, :), pointer, contiguous, optional :: auxvar
147  !
148  ! -- call base type allocate arrays
149  call this%BndExtType%allocate_arrays(nodelist, auxvar)
150  !
151  ! -- set drn input context pointers
152  call mem_setptr(this%elev, 'ELEV', this%input_mempath)
153  call mem_setptr(this%cond, 'COND', this%input_mempath)
154  !
155  ! --checkin drn input context pointers
156  call mem_checkin(this%elev, 'ELEV', this%memoryPath, &
157  'ELEV', this%input_mempath)
158  call mem_checkin(this%cond, 'COND', this%memoryPath, &
159  'COND', this%input_mempath)
160  end subroutine drn_allocate_arrays
161 
162  !> @brief Read and prepare
163  !<
164  subroutine drn_rp(this)
165  use tdismodule, only: kper
166  ! -- dummy
167  class(drntype), intent(inout) :: this
168  !
169  if (this%iper /= kper) return
170  !
171  ! -- Call the parent class read and prepare
172  call this%BndExtType%bnd_rp()
173  !
174  ! -- store user cond
175  if (this%ivsc == 1) then
176  call this%drn_store_user_cond()
177  end if
178  !
179  ! -- Write the list to iout if requested
180  if (this%iprpak /= 0) then
181  call this%write_list()
182  end if
183  end subroutine drn_rp
184 
185  !> @brief Source options specific to DrnType
186  !<
187  subroutine drn_options(this)
188  ! -- modules
189  use inputoutputmodule, only: urword
193  ! -- dummy
194  class(drntype), intent(inout) :: this
195  ! -- local
196  type(gwfdrnparamfoundtype) :: found
197  character(len=LENAUXNAME) :: ddrnauxname
198  integer(I4B) :: n
199  !
200  ! -- source base class options
201  call this%BndExtType%source_options()
202  !
203  ! -- source drain options
204  call mem_set_value(this%imover, 'MOVER', this%input_mempath, found%mover)
205  call mem_set_value(ddrnauxname, 'AUXDEPTHNAME', this%input_mempath, &
206  found%auxdepthname)
207  call mem_set_value(this%icubic_scaling, 'ICUBICSFAC', this%input_mempath, &
208  found%icubicsfac)
209  !
210  if (found%auxdepthname) then
211  this%iauxddrncol = -1
212  !
213  ! -- Error if no aux variable specified
214  if (this%naux == 0) then
215  write (errmsg, '(a,2(1x,a))') &
216  'AUXDEPTHNAME was specified as', trim(adjustl(ddrnauxname)), &
217  'but no AUX variables specified.'
218  call store_error(errmsg)
219  end if
220  !
221  ! -- Assign ddrn column
222  this%iauxddrncol = 0
223  do n = 1, this%naux
224  if (ddrnauxname == this%auxname(n)) then
225  this%iauxddrncol = n
226  exit
227  end if
228  end do
229  !
230  ! -- Error if aux variable cannot be found
231  if (this%iauxddrncol == 0) then
232  write (errmsg, '(a,2(1x,a))') &
233  'AUXDEPTHNAME was specified as', trim(adjustl(ddrnauxname)), &
234  'but no AUX variable found with this name.'
235  call store_error(errmsg)
236  end if
237  end if
238  !
239  ! -- log DRN specific options
240  call this%log_drn_options(found)
241  end subroutine drn_options
242 
243  !> @ brief Log DRN specific package options
244  !<
245  subroutine log_drn_options(this, found)
246  ! -- modules
248  ! -- dummy variables
249  class(drntype), intent(inout) :: this !< BndExtType object
250  type(gwfdrnparamfoundtype), intent(in) :: found
251  ! -- local variables
252  ! -- format
253  !
254  ! -- log found options
255  write (this%iout, '(/1x,a)') 'PROCESSING '//trim(adjustl(this%text)) &
256  //' OPTIONS'
257  !
258  if (found%mover) then
259  write (this%iout, '(4x,A)') 'MOVER OPTION ENABLED'
260  end if
261  !
262  if (found%icubicsfac) then
263  write (this%iout, '(4x,a,1x,a)') &
264  'CUBIC SCALING will be used for drains with non-zero DDRN values', &
265  'even if the NEWTON-RAPHSON method is not being used.'
266  end if
267  !
268  ! -- close logging block
269  write (this%iout, '(1x,a)') &
270  'END OF '//trim(adjustl(this%text))//' OPTIONS'
271  end subroutine log_drn_options
272 
273  !> @brief Check drain boundary condition data
274  !<
275  subroutine drn_ck(this)
276  ! -- dummy
277  class(drntype), intent(inout) :: this
278  ! -- local
279  integer(I4B) :: i
280  integer(I4B) :: node
281  real(DP) :: bt
282  real(DP) :: drndepth
283  real(DP) :: drntop
284  real(DP) :: drnbot
285  ! -- formats
286  character(len=*), parameter :: fmtddrnerr = &
287  "('SCALED-CONDUCTANCE DRN BOUNDARY (',i0,') BOTTOM ELEVATION &
288  &(',f10.3,') IS LESS THAN CELL BOTTOM (',f10.3,')')"
289  character(len=*), parameter :: fmtdrnerr = &
290  "('DRN BOUNDARY (',i0,') ELEVATION (',f10.3,') IS LESS THAN CELL &
291  &BOTTOM (',f10.3,')')"
292  character(len=*), parameter :: fmtcondmulterr = &
293  "('DRN BOUNDARY (',i0,') CONDUCTANCE MULTIPLIER (',g10.3,') IS &
294  &LESS THAN ZERO')"
295  character(len=*), parameter :: fmtconderr = &
296  "('DRN BOUNDARY (',i0,') CONDUCTANCE (',g10.3,') IS LESS THAN &
297  &ZERO')"
298  !
299  ! -- check stress period data
300  do i = 1, this%nbound
301  node = this%nodelist(i)
302  bt = this%dis%bot(node)
303  !
304  ! -- calculate the drainage depth and the top and bottom of
305  ! the conductance scaling elevations
306  call this%get_drain_elevations(i, drndepth, drntop, drnbot)
307  !
308  ! -- accumulate errors
309  if (drnbot < bt .and. this%icelltype(node) /= 0) then
310  if (drndepth /= dzero) then
311  write (errmsg, fmt=fmtddrnerr) i, drnbot, bt
312  else
313  write (errmsg, fmt=fmtdrnerr) i, drnbot, bt
314  end if
315  call store_error(errmsg)
316  end if
317  if (this%iauxmultcol > 0) then
318  if (this%auxvar(this%iauxmultcol, i) < dzero) then
319  write (errmsg, fmt=fmtcondmulterr) &
320  i, this%auxvar(this%iauxmultcol, i)
321  call store_error(errmsg)
322  end if
323  end if
324  if (this%cond(i) < dzero) then
325  write (errmsg, fmt=fmtconderr) i, this%cond(i)
326  call store_error(errmsg)
327  end if
328  end do
329  !
330  ! -- write summary of drain package error messages
331  if (count_errors() > 0) then
332  call store_error_filename(this%input_fname)
333  end if
334  end subroutine drn_ck
335 
336  !> @brief Formulate the HCOF and RHS terms
337  !!
338  !! Skip if no drains
339  !<
340  subroutine drn_cf(this)
341  ! -- dummy
342  class(drntype) :: this
343  ! -- local
344  integer(I4B) :: i
345  integer(I4B) :: node
346  real(DP) :: cdrn
347  real(DP) :: drnbot
348  real(DP) :: fact
349  !
350  ! -- Return if no drains
351  if (this%nbound == 0) return
352  !
353  ! -- Calculate hcof and rhs for each drn entry
354  do i = 1, this%nbound
355  node = this%nodelist(i)
356  if (this%ibound(node) <= 0) then
357  this%hcof(i) = dzero
358  this%rhs(i) = dzero
359  cycle
360  end if
361  !
362  ! -- set local variables for this drain
363  cdrn = this%cond_mult(i)
364 
365  !
366  ! -- calculate the drainage scaling factor
367  call this%get_drain_factor(i, fact, drnbot)
368  !
369  ! -- calculate rhs and hcof
370  this%rhs(i) = -fact * cdrn * drnbot
371  this%hcof(i) = -fact * cdrn
372  end do
373  end subroutine drn_cf
374 
375  !> @brief Copy rhs and hcof into solution rhs and amat
376  !<
377  subroutine drn_fc(this, rhs, ia, idxglo, matrix_sln)
378  ! -- dummy
379  class(drntype) :: this
380  real(DP), dimension(:), intent(inout) :: rhs
381  integer(I4B), dimension(:), intent(in) :: ia
382  integer(I4B), dimension(:), intent(in) :: idxglo
383  class(matrixbasetype), pointer :: matrix_sln
384  ! -- local
385  integer(I4B) :: i
386  integer(I4B) :: n
387  integer(I4B) :: ipos
388  real(DP) :: fact
389  real(DP) :: drnbot
390  real(DP) :: drncond
391  real(DP) :: qdrn
392  !
393  ! -- packmvrobj fc
394  if (this%imover == 1) then
395  call this%pakmvrobj%fc()
396  end if
397  !
398  ! -- Copy package rhs and hcof into solution rhs and amat
399  do i = 1, this%nbound
400  n = this%nodelist(i)
401  rhs(n) = rhs(n) + this%rhs(i)
402  ipos = ia(n)
403  call matrix_sln%add_value_pos(idxglo(ipos), this%hcof(i))
404  !
405  ! -- calculate the drainage scaling factor
406  call this%get_drain_factor(i, fact, drnbot)
407  !
408  ! -- If mover is active and this drain is discharging,
409  ! store available water (as positive value).
410  if (this%imover == 1 .and. fact > dzero) then
411  drncond = this%cond_mult(i)
412  qdrn = fact * drncond * (this%xnew(n) - drnbot)
413  call this%pakmvrobj%accumulate_qformvr(i, qdrn)
414  end if
415  end do
416  end subroutine drn_fc
417 
418  !> @brief Fill newton terms
419  !<
420  subroutine drn_fn(this, rhs, ia, idxglo, matrix_sln)
421  implicit none
422  ! -- dummy
423  class(drntype) :: this
424  real(DP), dimension(:), intent(inout) :: rhs
425  integer(I4B), dimension(:), intent(in) :: ia
426  integer(I4B), dimension(:), intent(in) :: idxglo
427  class(matrixbasetype), pointer :: matrix_sln
428  ! -- local
429  integer(I4B) :: i
430  integer(I4B) :: node
431  integer(I4B) :: ipos
432  real(DP) :: cdrn
433  real(DP) :: xnew
434  real(DP) :: drndepth
435  real(DP) :: drntop
436  real(DP) :: drnbot
437  real(DP) :: drterm
438  !
439  ! -- Copy package rhs and hcof into solution rhs and amat
440  if (this%iauxddrncol /= 0) then
441  do i = 1, this%nbound
442  node = this%nodelist(i)
443  !
444  ! -- test if node is constant or inactive
445  if (this%ibound(node) <= 0) then
446  cycle
447  end if
448  !
449  ! -- set local variables for this drain
450  cdrn = this%cond_mult(i)
451  xnew = this%xnew(node)
452  !
453  ! -- calculate the drainage depth and the top and bottom of
454  ! the conductance scaling elevations
455  call this%get_drain_elevations(i, drndepth, drntop, drnbot)
456  !
457  ! -- calculate scaling factor
458  if (drndepth /= dzero) then
459  drterm = sqsaturationderivative(drntop, drnbot, xnew, &
460  c1=-done, c2=dtwo)
461  drterm = drterm * cdrn * (drnbot - xnew)
462  !
463  ! -- fill amat and rhs with newton-raphson terms
464  ipos = ia(node)
465  call matrix_sln%add_value_pos(idxglo(ipos), drterm)
466  rhs(node) = rhs(node) + drterm * xnew
467  end if
468  end do
469  end if
470  end subroutine drn_fn
471 
472  !> @brief Define the list heading that is written to iout when PRINT_INPUT
473  !! option is used
474  !<
475  subroutine define_listlabel(this)
476  ! -- dummy
477  class(drntype), intent(inout) :: this
478  !
479  ! -- create the header list label
480  this%listlabel = trim(this%filtyp)//' NO.'
481  if (this%dis%ndim == 3) then
482  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'LAYER'
483  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'ROW'
484  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'COL'
485  elseif (this%dis%ndim == 2) then
486  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'LAYER'
487  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'CELL2D'
488  else
489  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'NODE'
490  end if
491  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'DRAIN EL.'
492  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'CONDUCTANCE'
493  if (this%inamedbound == 1) then
494  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'BOUNDARY NAME'
495  end if
496  end subroutine define_listlabel
497 
498  !> @brief Define drain depth and the top and bottom elevations used to scale
499  !! the drain conductance
500  !<
501  subroutine get_drain_elevations(this, i, drndepth, drntop, drnbot)
502  ! -- dummy
503  class(drntype), intent(inout) :: this
504  integer(I4B), intent(in) :: i
505  real(DP), intent(inout) :: drndepth
506  real(DP), intent(inout) :: drntop
507  real(DP), intent(inout) :: drnbot
508  ! -- local
509  real(DP) :: drnelev
510  real(DP) :: elev
511  !
512  ! -- initialize dummy and local variables
513  drndepth = dzero
514  drnelev = this%elev(i)
515  !
516  ! -- set the drain depth
517  if (this%iauxddrncol > 0) then
518  drndepth = this%auxvar(this%iauxddrncol, i)
519  end if
520  !
521  ! -- calculate the top and bottom drain elevations
522  if (drndepth /= dzero) then
523  elev = drnelev + drndepth
524  drntop = max(elev, drnelev)
525  drnbot = min(elev, drnelev)
526  else
527  drntop = drnelev
528  drnbot = drnelev
529  end if
530  end subroutine get_drain_elevations
531 
532  !> @brief Get the drain conductance scale factor
533  !<
534  subroutine get_drain_factor(this, i, factor, opt_drnbot)
535  ! -- dummy
536  class(drntype), intent(inout) :: this
537  integer(I4B), intent(in) :: i
538  real(DP), intent(inout) :: factor
539  real(DP), intent(inout), optional :: opt_drnbot
540  ! -- local
541  integer(I4B) :: node
542  real(DP) :: xnew
543  real(DP) :: drndepth
544  real(DP) :: drntop
545  real(DP) :: drnbot
546  !
547  ! -- set local variables for this drain
548  node = this%nodelist(i)
549  xnew = this%xnew(node)
550  !
551  ! -- calculate the drainage depth and the top and bottom of
552  ! the conductance scaling elevations
553  call this%get_drain_elevations(i, drndepth, drntop, drnbot)
554  !
555  ! -- set opt_drnbot to drnbot if passed as dummy variable
556  if (present(opt_drnbot)) then
557  opt_drnbot = drnbot
558  end if
559  !
560  ! -- calculate scaling factor
561  if (drndepth /= dzero) then
562  if (this%icubic_scaling /= 0) then
563  factor = sqsaturation(drntop, drnbot, xnew, c1=-done, c2=dtwo)
564  else
565  factor = squadraticsaturation(drntop, drnbot, xnew, eps=dzero)
566  end if
567  else
568  if (xnew <= drnbot) then
569  factor = dzero
570  else
571  factor = done
572  end if
573  end if
574  end subroutine get_drain_factor
575 
576  ! -- Procedures related to observations
577 
578  !> @brief Return true because DRN package supports observations
579  !!
580  !! Overrides BndType%bnd_obs_supported()
581  !<
582  logical function drn_obs_supported(this)
583  implicit none
584  ! -- dummy
585  class(drntype) :: this
586  !
587  drn_obs_supported = .true.
588  end function drn_obs_supported
589 
590  !> @brief Store observation type supported by DRN package
591  !!
592  !! Overrides BndType%bnd_df_obs
593  !<
594  subroutine drn_df_obs(this)
595  implicit none
596  ! -- dummy
597  class(drntype) :: this
598  ! -- local
599  integer(I4B) :: indx
600  !
601  call this%obs%StoreObsType('drn', .true., indx)
602  this%obs%obsData(indx)%ProcessIdPtr => defaultobsidprocessor
603  !
604  ! -- Store obs type and assign procedure pointer
605  ! for to-mvr observation type.
606  call this%obs%StoreObsType('to-mvr', .true., indx)
607  this%obs%obsData(indx)%ProcessIdPtr => defaultobsidprocessor
608  end subroutine drn_df_obs
609 
610  !> @brief Store user-specified drain conductance
611  !<
612  subroutine drn_store_user_cond(this)
613  ! -- dummy
614  class(drntype), intent(inout) :: this !< BndExtType object
615  ! -- local
616  integer(I4B) :: n
617  !
618  ! -- store backup copy of conductance values
619  do n = 1, this%nbound
620  this%condinput(n) = this%cond_mult(n)
621  end do
622  end subroutine drn_store_user_cond
623 
624  !> @brief Apply multiplier to conductance value depending on user-selected option
625  !<
626  function cond_mult(this, row) result(cond)
627  ! -- modules
628  use constantsmodule, only: dzero
629  ! -- dummy variables
630  class(drntype), intent(inout) :: this !< BndExtType object
631  integer(I4B), intent(in) :: row
632  ! -- result
633  real(dp) :: cond
634  !
635  if (this%iauxmultcol > 0) then
636  cond = this%cond(row) * this%auxvar(this%iauxmultcol, row)
637  else
638  cond = this%cond(row)
639  end if
640  end function cond_mult
641 
642  !> @brief Return requested boundary value
643  !<
644  function drn_bound_value(this, col, row) result(bndval)
645  ! -- modules
646  use constantsmodule, only: dzero
647  ! -- dummy variables
648  class(drntype), intent(inout) :: this !< BndExtType object
649  integer(I4B), intent(in) :: col
650  integer(I4B), intent(in) :: row
651  ! -- result
652  real(dp) :: bndval
653  !
654  select case (col)
655  case (1)
656  bndval = this%elev(row)
657  case (2)
658  bndval = this%cond_mult(row)
659  case default
660  errmsg = 'Programming error. DRN bound value requested column '&
661  &'outside range of ncolbnd (2).'
662  call store_error(errmsg)
663  call store_error_filename(this%input_fname)
664  end select
665  end function drn_bound_value
666 
667 end module drnmodule
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
integer(i4b), parameter lenpackagename
maximum length of the package name
Definition: Constants.f90:23
integer(i4b), parameter lenftype
maximum length of a package type (DIS, WEL, OC, etc.)
Definition: Constants.f90:39
integer(i4b), parameter lenauxname
maximum length of a aux variable
Definition: Constants.f90:35
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
real(dp), parameter dtwo
real constant 2
Definition: Constants.f90:79
real(dp), parameter done
real constant 1
Definition: Constants.f90:76
character(len=lenftype) ftype
Definition: gwf-drn.f90:21
subroutine drn_da(this)
Deallocate memory.
Definition: gwf-drn.f90:97
subroutine, public drn_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, mempath)
Create a New Drn Package and point packobj to the new package.
Definition: gwf-drn.f90:60
real(dp) function cond_mult(this, row)
Apply multiplier to conductance value depending on user-selected option.
Definition: gwf-drn.f90:627
subroutine drn_fn(this, rhs, ia, idxglo, matrix_sln)
Fill newton terms.
Definition: gwf-drn.f90:421
subroutine drn_allocate_arrays(this, nodelist, auxvar)
Allocate package arrays.
Definition: gwf-drn.f90:141
real(dp) function drn_bound_value(this, col, row)
Return requested boundary value.
Definition: gwf-drn.f90:645
subroutine define_listlabel(this)
Define the list heading that is written to iout when PRINT_INPUT option is used.
Definition: gwf-drn.f90:476
logical function drn_obs_supported(this)
Return true because DRN package supports observations.
Definition: gwf-drn.f90:583
subroutine get_drain_factor(this, i, factor, opt_drnbot)
Get the drain conductance scale factor.
Definition: gwf-drn.f90:535
subroutine drn_allocate_scalars(this)
Allocate package scalar members.
Definition: gwf-drn.f90:117
subroutine drn_cf(this)
Formulate the HCOF and RHS terms.
Definition: gwf-drn.f90:341
subroutine drn_ck(this)
Check drain boundary condition data.
Definition: gwf-drn.f90:276
subroutine drn_options(this)
Source options specific to DrnType.
Definition: gwf-drn.f90:188
subroutine drn_rp(this)
Read and prepare.
Definition: gwf-drn.f90:165
character(len=lenpackagename) text
Definition: gwf-drn.f90:22
subroutine get_drain_elevations(this, i, drndepth, drntop, drnbot)
Define drain depth and the top and bottom elevations used to scale the drain conductance.
Definition: gwf-drn.f90:502
subroutine log_drn_options(this, found)
@ brief Log DRN specific package options
Definition: gwf-drn.f90:246
subroutine drn_store_user_cond(this)
Store user-specified drain conductance.
Definition: gwf-drn.f90:613
subroutine drn_fc(this, rhs, ia, idxglo, matrix_sln)
Copy rhs and hcof into solution rhs and amat.
Definition: gwf-drn.f90:378
subroutine drn_df_obs(this)
Store observation type supported by DRN package.
Definition: gwf-drn.f90:595
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
character(len=lenmempath) function create_mem_path(component, subcomponent, context)
returns the path to the memory object
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
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
real(dp) function squadraticsaturation(top, bot, x, eps)
@ brief sQuadraticSaturation
real(dp) function sqsaturationderivative(top, bot, x, c1, c2)
@ brief sQSaturationDerivative
real(dp) function sqsaturation(top, bot, x, c1, c2)
@ brief sQSaturation
integer(i4b), pointer, public kper
current stress period number
Definition: tdis.f90:23
@ brief BndType
This class is used to store a single deferred-length character string. It was designed to work in an ...
Definition: CharString.f90:23