MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
drnmodule Module Reference

Data Types

type  drntype
 

Functions/Subroutines

subroutine, public drn_create (packobj, id, ibcnum, inunit, iout, namemodel, pakname, mempath)
 Create a New Drn Package and point packobj to the new package. More...
 
subroutine drn_da (this)
 Deallocate memory. More...
 
subroutine drn_allocate_scalars (this)
 Allocate package scalar members. More...
 
subroutine drn_allocate_arrays (this, nodelist, auxvar)
 Allocate package arrays. More...
 
subroutine drn_rp (this)
 Read and prepare. More...
 
subroutine drn_options (this)
 Source options specific to DrnType. More...
 
subroutine log_drn_options (this, found)
 @ brief Log DRN specific package options More...
 
subroutine drn_ck (this)
 Check drain boundary condition data. More...
 
subroutine drn_cf (this)
 Formulate the HCOF and RHS terms. More...
 
subroutine drn_fc (this, rhs, ia, idxglo, matrix_sln)
 Copy rhs and hcof into solution rhs and amat. More...
 
subroutine drn_fn (this, rhs, ia, idxglo, matrix_sln)
 Fill newton terms. More...
 
subroutine define_listlabel (this)
 Define the list heading that is written to iout when PRINT_INPUT option is used. More...
 
subroutine get_drain_elevations (this, i, drndepth, drntop, drnbot)
 Define drain depth and the top and bottom elevations used to scale the drain conductance. More...
 
subroutine get_drain_factor (this, i, factor, opt_drnbot)
 Get the drain conductance scale factor. More...
 
logical function drn_obs_supported (this)
 Return true because DRN package supports observations. More...
 
subroutine drn_df_obs (this)
 Store observation type supported by DRN package. More...
 
subroutine drn_store_user_cond (this)
 Store user-specified drain conductance. More...
 
real(dp) function cond_mult (this, row)
 Apply multiplier to conductance value depending on user-selected option. More...
 
real(dp) function drn_bound_value (this, col, row)
 Return requested boundary value. More...
 

Variables

character(len=lenftype) ftype = 'DRN'
 
character(len=lenpackagename) text = ' DRN'
 

Function/Subroutine Documentation

◆ cond_mult()

real(dp) function drnmodule::cond_mult ( class(drntype), intent(inout)  this,
integer(i4b), intent(in)  row 
)
private
Parameters
[in,out]thisBndExtType object

Definition at line 626 of file gwf-drn.f90.

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
This module contains simulation constants.
Definition: Constants.f90:9
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65

◆ define_listlabel()

subroutine drnmodule::define_listlabel ( class(drntype), intent(inout)  this)
private

Definition at line 475 of file gwf-drn.f90.

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

◆ drn_allocate_arrays()

subroutine drnmodule::drn_allocate_arrays ( class(drntype this,
integer(i4b), dimension(:), optional, pointer, contiguous  nodelist,
real(dp), dimension(:, :), optional, pointer, contiguous  auxvar 
)

Definition at line 140 of file gwf-drn.f90.

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)

◆ drn_allocate_scalars()

subroutine drnmodule::drn_allocate_scalars ( class(drntype this)

Definition at line 116 of file gwf-drn.f90.

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

◆ drn_bound_value()

real(dp) function drnmodule::drn_bound_value ( class(drntype), intent(inout)  this,
integer(i4b), intent(in)  col,
integer(i4b), intent(in)  row 
)
Parameters
[in,out]thisBndExtType object

Definition at line 644 of file gwf-drn.f90.

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
Here is the call graph for this function:

◆ drn_cf()

subroutine drnmodule::drn_cf ( class(drntype this)
private

Skip if no drains

Definition at line 340 of file gwf-drn.f90.

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

◆ drn_ck()

subroutine drnmodule::drn_ck ( class(drntype), intent(inout)  this)

Definition at line 275 of file gwf-drn.f90.

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
Here is the call graph for this function:

◆ drn_create()

subroutine, public drnmodule::drn_create ( class(bndtype), pointer  packobj,
integer(i4b), intent(in)  id,
integer(i4b), intent(in)  ibcnum,
integer(i4b), intent(in)  inunit,
integer(i4b), intent(in)  iout,
character(len=*), intent(in)  namemodel,
character(len=*), intent(in)  pakname,
character(len=*), intent(in)  mempath 
)

Definition at line 58 of file gwf-drn.f90.

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')
Here is the call graph for this function:
Here is the caller graph for this function:

◆ drn_da()

subroutine drnmodule::drn_da ( class(drntype this)
private

Definition at line 96 of file gwf-drn.f90.

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)

◆ drn_df_obs()

subroutine drnmodule::drn_df_obs ( class(drntype this)
private

Overrides BndTypebnd_df_obs

Definition at line 594 of file gwf-drn.f90.

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
Here is the call graph for this function:

◆ drn_fc()

subroutine drnmodule::drn_fc ( class(drntype this,
real(dp), dimension(:), intent(inout)  rhs,
integer(i4b), dimension(:), intent(in)  ia,
integer(i4b), dimension(:), intent(in)  idxglo,
class(matrixbasetype), pointer  matrix_sln 
)
private

Definition at line 377 of file gwf-drn.f90.

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

◆ drn_fn()

subroutine drnmodule::drn_fn ( class(drntype this,
real(dp), dimension(:), intent(inout)  rhs,
integer(i4b), dimension(:), intent(in)  ia,
integer(i4b), dimension(:), intent(in)  idxglo,
class(matrixbasetype), pointer  matrix_sln 
)
private

Definition at line 420 of file gwf-drn.f90.

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
Here is the call graph for this function:

◆ drn_obs_supported()

logical function drnmodule::drn_obs_supported ( class(drntype this)
private

Overrides BndTypebnd_obs_supported()

Definition at line 582 of file gwf-drn.f90.

583  implicit none
584  ! -- dummy
585  class(DrnType) :: this
586  !
587  drn_obs_supported = .true.

◆ drn_options()

subroutine drnmodule::drn_options ( class(drntype), intent(inout)  this)

Definition at line 187 of file gwf-drn.f90.

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)
subroutine, public urword(line, icol, istart, istop, ncode, n, r, iout, in)
Extract a word from a string.
This class is used to store a single deferred-length character string. It was designed to work in an ...
Definition: CharString.f90:23
Here is the call graph for this function:

◆ drn_rp()

subroutine drnmodule::drn_rp ( class(drntype), intent(inout)  this)

Definition at line 164 of file gwf-drn.f90.

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
integer(i4b), pointer, public kper
current stress period number
Definition: tdis.f90:23

◆ drn_store_user_cond()

subroutine drnmodule::drn_store_user_cond ( class(drntype), intent(inout)  this)
private
Parameters
[in,out]thisBndExtType object

Definition at line 612 of file gwf-drn.f90.

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

◆ get_drain_elevations()

subroutine drnmodule::get_drain_elevations ( class(drntype), intent(inout)  this,
integer(i4b), intent(in)  i,
real(dp), intent(inout)  drndepth,
real(dp), intent(inout)  drntop,
real(dp), intent(inout)  drnbot 
)
private

Definition at line 501 of file gwf-drn.f90.

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

◆ get_drain_factor()

subroutine drnmodule::get_drain_factor ( class(drntype), intent(inout)  this,
integer(i4b), intent(in)  i,
real(dp), intent(inout)  factor,
real(dp), intent(inout), optional  opt_drnbot 
)
private

Definition at line 534 of file gwf-drn.f90.

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
Here is the call graph for this function:

◆ log_drn_options()

subroutine drnmodule::log_drn_options ( class(drntype), intent(inout)  this,
type(gwfdrnparamfoundtype), intent(in)  found 
)
Parameters
[in,out]thisBndExtType object

Definition at line 245 of file gwf-drn.f90.

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'

Variable Documentation

◆ ftype

character(len=lenftype) drnmodule::ftype = 'DRN'
private

Definition at line 21 of file gwf-drn.f90.

21  character(len=LENFTYPE) :: ftype = 'DRN'

◆ text

character(len=lenpackagename) drnmodule::text = ' DRN'
private

Definition at line 22 of file gwf-drn.f90.

22  character(len=LENPACKAGENAME) :: text = ' DRN'