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

Data Types

type  rchtype
 

Functions/Subroutines

subroutine, public rch_create (packobj, id, ibcnum, inunit, iout, namemodel, pakname, mempath)
 Create a New Recharge Package. More...
 
subroutine rch_allocate_scalars (this)
 Allocate scalar members. More...
 
subroutine rch_allocate_arrays (this, nodelist, auxvar)
 Allocate package arrays. More...
 
subroutine rch_source_options (this)
 Source options specific to RchType. More...
 
subroutine log_rch_options (this, found_fixed_cell, found_readasarrays)
 Log options specific to RchType. More...
 
subroutine rch_source_dimensions (this)
 Source the dimensions for this package. More...
 
subroutine rch_read_initial_attr (this)
 Part of allocate and read. More...
 
subroutine rch_rp (this)
 Read and Prepare. More...
 
subroutine set_nodesontop (this)
 Store nodelist in nodesontop. More...
 
subroutine rch_cf (this)
 Formulate the HCOF and RHS terms. More...
 
subroutine rch_fc (this, rhs, ia, idxglo, matrix_sln)
 Copy rhs and hcof into solution rhs and amat. More...
 
subroutine rch_da (this)
 Deallocate memory. More...
 
subroutine rch_define_listlabel (this)
 Define the list heading that is written to iout when PRINT_INPUT option is used. More...
 
subroutine default_nodelist (this)
 Assign default nodelist when READASARRAYS is specified. More...
 
logical function rch_obs_supported (this)
 Overrides BndTypebnd_obs_supported() More...
 
subroutine rch_df_obs (this)
 Implements bnd_df_obs. More...
 
real(dp) function rch_bound_value (this, col, row)
 Return requested boundary value. More...
 
subroutine nodelist_update (nodelist, nbound, maxbound, dis, input_mempath)
 Update the nodelist based on IRCH input. More...
 

Variables

character(len=lenftype) ftype = 'RCH'
 
character(len=lenpackagename) text = ' RCH'
 
character(len=lenpackagename) texta = ' RCHA'
 

Function/Subroutine Documentation

◆ default_nodelist()

subroutine rchmodule::default_nodelist ( class(rchtype this)
private

Equivalent to reading IRCH as CONSTANT 1

Definition at line 434 of file gwf-rch.f90.

435  ! -- dummy
436  class(RchType) :: this
437  ! -- local
438  integer(I4B) :: il, ir, ic, ncol, nrow, nlay, nodeu, noder, ipos
439  !
440  ! -- set variables
441  if (this%dis%ndim == 3) then
442  nlay = this%dis%mshape(1)
443  nrow = this%dis%mshape(2)
444  ncol = this%dis%mshape(3)
445  elseif (this%dis%ndim == 2) then
446  nlay = this%dis%mshape(1)
447  nrow = 1
448  ncol = this%dis%mshape(2)
449  end if
450  !
451  ! -- Populate nodelist
452  ipos = 1
453  il = 1
454  do ir = 1, nrow
455  do ic = 1, ncol
456  nodeu = get_node(il, ir, ic, nlay, nrow, ncol)
457  noder = this%dis%get_nodenumber(nodeu, 0)
458  this%nodelist(ipos) = noder
459  ipos = ipos + 1
460  end do
461  end do
462  !
463  ! -- Assign nbound
464  this%nbound = ipos - 1
465  !
466  ! -- if fixed_cell option not set, then need to store nodelist
467  ! in the nodesontop array
468  if (.not. this%fixed_cell) call this%set_nodesontop()
Here is the call graph for this function:

◆ log_rch_options()

subroutine rchmodule::log_rch_options ( class(rchtype), intent(inout)  this,
logical(lgp), intent(in)  found_fixed_cell,
logical(lgp), intent(in)  found_readasarrays 
)

Definition at line 173 of file gwf-rch.f90.

174  implicit none
175  ! -- dummy
176  class(RchType), intent(inout) :: this
177  logical(LGP), intent(in) :: found_fixed_cell
178  logical(LGP), intent(in) :: found_readasarrays
179  ! -- formats
180  character(len=*), parameter :: fmtfixedcell = &
181  &"(4x, 'RECHARGE WILL BE APPLIED TO SPECIFIED CELL.')"
182  character(len=*), parameter :: fmtreadasarrays = &
183  &"(4x, 'RECHARGE INPUT WILL BE READ AS ARRAY(S).')"
184  !
185  ! -- log found options
186  write (this%iout, '(/1x,a)') 'PROCESSING '//trim(adjustl(this%text)) &
187  //' OPTIONS'
188  !
189  if (found_fixed_cell) then
190  write (this%iout, fmtfixedcell)
191  end if
192  !
193  if (found_readasarrays) then
194  write (this%iout, fmtreadasarrays)
195  end if
196  !
197  ! -- close logging block
198  write (this%iout, '(1x,a)') &
199  'END OF '//trim(adjustl(this%text))//' OPTIONS'

◆ nodelist_update()

subroutine rchmodule::nodelist_update ( integer(i4b), dimension(:), intent(inout), pointer, contiguous  nodelist,
integer(i4b), intent(inout)  nbound,
integer(i4b), intent(in)  maxbound,
class(disbasetype), intent(in), pointer  dis,
character(len=*), intent(in)  input_mempath 
)

This is a module scoped routine to check for IRCH input. If array input was provided, INIRCH and IRCH will be allocated in the input context. If the read state variable INIRCH is set to 1 during this period update, IRCH input was read and is used here to update the nodelist.

Definition at line 538 of file gwf-rch.f90.

540  ! -- modules
542  use basedismodule, only: disbasetype
543  ! -- dummy
544  integer(I4B), dimension(:), contiguous, &
545  pointer, intent(inout) :: nodelist
546  class(DisBaseType), pointer, intent(in) :: dis
547  character(len=*), intent(in) :: input_mempath
548  integer(I4B), intent(inout) :: nbound
549  integer(I4B), intent(in) :: maxbound
550  character(len=24) :: aname = ' LAYER OR NODE INDEX'
551  ! -- local
552  integer(I4B), dimension(:), contiguous, &
553  pointer :: irch => null()
554  integer(I4B), pointer :: inirch => null()
555  !
556  ! -- set pointer to input context INIRCH
557  call mem_setptr(inirch, 'INIRCH', input_mempath)
558  !
559  ! -- check INIRCH read state
560  if (inirch == 1) then
561  ! -- irch was read this period
562  !
563  ! -- set pointer to input context IRCH
564  call mem_setptr(irch, 'IRCH', input_mempath)
565  !
566  ! -- update nodelist
567  call dis%nlarray_to_nodelist(irch, nodelist, &
568  maxbound, nbound, aname)
569  end if
Here is the caller graph for this function:

◆ rch_allocate_arrays()

subroutine rchmodule::rch_allocate_arrays ( class(rchtype this,
integer(i4b), dimension(:), optional, pointer, contiguous  nodelist,
real(dp), dimension(:, :), optional, pointer, contiguous  auxvar 
)
private

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

117  ! -- modules
119  ! -- dummy
120  class(RchType) :: this
121  integer(I4B), dimension(:), pointer, contiguous, optional :: nodelist
122  real(DP), dimension(:, :), pointer, contiguous, optional :: auxvar
123  !
124  ! -- allocate base arrays
125  call this%BndExtType%allocate_arrays(nodelist, auxvar)
126  !
127  ! -- set recharge input context pointer
128  call mem_setptr(this%recharge, 'RECHARGE', this%input_mempath)
129  !
130  ! -- checkin recharge input context pointer
131  call mem_checkin(this%recharge, 'RECHARGE', this%memoryPath, &
132  'RECHARGE', this%input_mempath)

◆ rch_allocate_scalars()

subroutine rchmodule::rch_allocate_scalars ( class(rchtype), intent(inout)  this)
private

Definition at line 98 of file gwf-rch.f90.

99  ! -- dummy
100  class(RchType), intent(inout) :: this
101  !
102  ! -- allocate base scalars
103  call this%BndExtType%allocate_scalars()
104  !
105  ! -- allocate internal members
106  allocate (this%fixed_cell)
107  allocate (this%read_as_arrays)
108  !
109  ! -- Set values
110  this%fixed_cell = .false.
111  this%read_as_arrays = .false.

◆ rch_bound_value()

real(dp) function rchmodule::rch_bound_value ( class(rchtype), intent(inout)  this,
integer(i4b), intent(in)  col,
integer(i4b), intent(in)  row 
)
private
Parameters
[in,out]thisBndExtType object

Definition at line 503 of file gwf-rch.f90.

504  ! -- modules
505  use constantsmodule, only: dzero
506  ! -- dummy
507  class(RchType), intent(inout) :: this !< BndExtType object
508  integer(I4B), intent(in) :: col
509  integer(I4B), intent(in) :: row
510  ! -- result
511  real(DP) :: bndval
512  !
513  select case (col)
514  case (1)
515  if (this%iauxmultcol > 0) then
516  bndval = this%recharge(row) * this%auxvar(this%iauxmultcol, row)
517  else
518  bndval = this%recharge(row)
519  end if
520  case default
521  errmsg = 'Programming error. RCH bound value requested column '&
522  &'outside range of ncolbnd (1).'
523  call store_error(errmsg)
524  call store_error_filename(this%input_fname)
525  end select
This module contains simulation constants.
Definition: Constants.f90:9
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
Here is the call graph for this function:

◆ rch_cf()

subroutine rchmodule::rch_cf ( class(rchtype this)
private

Skip if no recharge. Otherwise, calculate hcof and rhs

Definition at line 303 of file gwf-rch.f90.

304  ! -- dummy
305  class(rchtype) :: this
306  ! -- local
307  integer(I4B) :: i, node
308  !
309  ! -- Return if no recharge
310  if (this%nbound == 0) return
311  !
312  ! -- Calculate hcof and rhs for each recharge entry
313  do i = 1, this%nbound
314  !
315  ! -- Find the node number
316  if (this%fixed_cell) then
317  node = this%nodelist(i)
318  else
319  node = this%nodesontop(i)
320  end if
321  !
322  ! -- cycle if nonexistent bound
323  if (node <= 0) then
324  this%hcof(i) = dzero
325  this%rhs(i) = dzero
326  cycle
327  end if
328  !
329  ! -- reset nodelist to highest active
330  if (.not. this%fixed_cell) then
331  if (this%ibound(node) == 0) &
332  call this%dis%highest_active(node, this%ibound)
333  this%nodelist(i) = node
334  end if
335  !
336  ! -- Set rhs and hcof
337  this%hcof(i) = dzero
338  if (this%iauxmultcol > 0) then
339  this%rhs(i) = -this%recharge(i) * this%dis%get_area(node) * &
340  this%auxvar(this%iauxmultcol, i)
341  else
342  this%rhs(i) = -this%recharge(i) * this%dis%get_area(node)
343  end if
344  if (this%ibound(node) <= 0) then
345  this%rhs(i) = dzero
346  cycle
347  end if
348  if (this%ibound(node) == iwetlake) then
349  this%rhs(i) = dzero
350  cycle
351  end if
352  end do

◆ rch_create()

subroutine, public rchmodule::rch_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 
)

Create new RCH package and point packobj to the new package

Definition at line 61 of file gwf-rch.f90.

63  ! -- dummy
64  class(BndType), pointer :: packobj
65  integer(I4B), intent(in) :: id
66  integer(I4B), intent(in) :: ibcnum
67  integer(I4B), intent(in) :: inunit
68  integer(I4B), intent(in) :: iout
69  character(len=*), intent(in) :: namemodel
70  character(len=*), intent(in) :: pakname
71  character(len=*), intent(in) :: mempath
72  ! -- local
73  type(rchtype), pointer :: rchobj
74  !
75  ! -- allocate recharge object and scalar variables
76  allocate (rchobj)
77  packobj => rchobj
78  !
79  ! -- create name and memory path
80  call packobj%set_names(ibcnum, namemodel, pakname, ftype, mempath)
81  packobj%text = text
82  !
83  ! -- allocate scalars
84  call rchobj%rch_allocate_scalars()
85  !
86  ! -- initialize package
87  call packobj%pack_initialize()
88  !
89  packobj%inunit = inunit
90  packobj%iout = iout
91  packobj%id = id
92  packobj%ibcnum = ibcnum
93  packobj%ictMemPath = create_mem_path(namemodel, 'NPF')
Here is the call graph for this function:
Here is the caller graph for this function:

◆ rch_da()

subroutine rchmodule::rch_da ( class(rchtype this)
private

Definition at line 385 of file gwf-rch.f90.

386  ! -- modules
388  ! -- dummy
389  class(RchType) :: this
390  !
391  ! -- Deallocate parent package
392  call this%BndExtType%bnd_da()
393  !
394  ! -- scalars
395  deallocate (this%fixed_cell)
396  deallocate (this%read_as_arrays)
397  !
398  ! -- arrays
399  if (associated(this%nodesontop)) deallocate (this%nodesontop)
400  call mem_deallocate(this%recharge, 'RECHARGE', this%memoryPath)

◆ rch_define_listlabel()

subroutine rchmodule::rch_define_listlabel ( class(rchtype), intent(inout)  this)

Definition at line 406 of file gwf-rch.f90.

407  ! -- dummy
408  class(RchType), intent(inout) :: this
409  !
410  ! -- create the header list label
411  this%listlabel = trim(this%filtyp)//' NO.'
412  if (this%dis%ndim == 3) then
413  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'LAYER'
414  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'ROW'
415  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'COL'
416  elseif (this%dis%ndim == 2) then
417  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'LAYER'
418  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'CELL2D'
419  else
420  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'NODE'
421  end if
422  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'RECHARGE'
423 ! if(this%multindex > 0) &
424 ! write(this%listlabel, '(a, a16)') trim(this%listlabel), 'MULTIPLIER'
425  if (this%inamedbound == 1) then
426  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'BOUNDARY NAME'
427  end if

◆ rch_df_obs()

subroutine rchmodule::rch_df_obs ( class(rchtype this)
private

Store observation type supported by RCH package. Overrides BndTypebnd_df_obs

Definition at line 490 of file gwf-rch.f90.

491  implicit none
492  ! -- dummy
493  class(RchType) :: this
494  ! -- local
495  integer(I4B) :: indx
496  !
497  call this%obs%StoreObsType('rch', .true., indx)
498  this%obs%obsData(indx)%ProcessIdPtr => defaultobsidprocessor
Here is the call graph for this function:

◆ rch_fc()

subroutine rchmodule::rch_fc ( class(rchtype 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 357 of file gwf-rch.f90.

358  ! -- dummy
359  class(RchType) :: this
360  real(DP), dimension(:), intent(inout) :: rhs
361  integer(I4B), dimension(:), intent(in) :: ia
362  integer(I4B), dimension(:), intent(in) :: idxglo
363  class(MatrixBaseType), pointer :: matrix_sln
364  ! -- local
365  integer(I4B) :: i, n, ipos
366  !
367  ! -- Copy package rhs and hcof into solution rhs and amat
368  do i = 1, this%nbound
369  n = this%nodelist(i)
370  if (n <= 0) cycle
371  ! -- reset hcof and rhs for excluded cells
372  if (this%ibound(n) == iwetlake) then
373  this%hcof(i) = dzero
374  this%rhs(i) = dzero
375  cycle
376  end if
377  rhs(n) = rhs(n) + this%rhs(i)
378  ipos = ia(n)
379  call matrix_sln%add_value_pos(idxglo(ipos), this%hcof(i))
380  end do

◆ rch_obs_supported()

logical function rchmodule::rch_obs_supported ( class(rchtype this)
private

Definition at line 477 of file gwf-rch.f90.

478  implicit none
479  ! -- dummy
480  class(RchType) :: this
481  !
482  rch_obs_supported = .true.

◆ rch_read_initial_attr()

subroutine rchmodule::rch_read_initial_attr ( class(rchtype), intent(inout)  this)
private

Definition at line 236 of file gwf-rch.f90.

237  ! -- dummy
238  class(RchType), intent(inout) :: this
239  !
240  if (this%read_as_arrays) then
241  call this%default_nodelist()
242  end if

◆ rch_rp()

subroutine rchmodule::rch_rp ( class(rchtype), intent(inout)  this)
private

Read itmp and read new boundaries if itmp > 0

Definition at line 249 of file gwf-rch.f90.

250  ! -- modules
251  use tdismodule, only: kper
252  implicit none
253  ! -- dummy
254  class(RchType), intent(inout) :: this
255  !
256  if (this%iper /= kper) return
257  !
258  if (this%read_as_arrays) then
259  !
260  ! -- update nodelist based on IRCH input
261  call nodelist_update(this%nodelist, this%nbound, this%maxbound, &
262  this%dis, this%input_mempath)
263  !
264  else
265  !
266  call this%BndExtType%bnd_rp()
267  !
268  end if
269  !
270  ! -- copy nodelist to nodesontop if not fixed cell
271  if (.not. this%fixed_cell) call this%set_nodesontop()
272  !
273  ! -- Write the list to iout if requested
274  if (this%iprpak /= 0) then
275  call this%write_list()
276  end if
integer(i4b), pointer, public kper
current stress period number
Definition: tdis.f90:23
Here is the call graph for this function:

◆ rch_source_dimensions()

subroutine rchmodule::rch_source_dimensions ( class(rchtype), intent(inout)  this)
private

Dimensions block is not required if: (1) discretization is DIS or DISV, and (2) READASARRAYS option has been specified.

Definition at line 208 of file gwf-rch.f90.

209  ! -- dummy
210  class(RchType), intent(inout) :: this
211  !
212  if (this%read_as_arrays) then
213  this%maxbound = this%dis%get_ncpl()
214  !
215  ! -- verify dimensions were set
216  if (this%maxbound <= 0) then
217  write (errmsg, '(a)') &
218  'MAXBOUND must be an integer greater than zero.'
219  call store_error(errmsg)
220  call store_error_filename(this%input_fname)
221  end if
222  !
223  else
224  !
225  ! -- source maxbound
226  call this%BndExtType%source_dimensions()
227  end if
228  !
229  ! -- Call define_listlabel to construct the list label that is written
230  ! when PRINT_INPUT option is used.
231  call this%define_listlabel()
Here is the call graph for this function:

◆ rch_source_options()

subroutine rchmodule::rch_source_options ( class(rchtype), intent(inout)  this)

Definition at line 137 of file gwf-rch.f90.

138  ! -- modules
140  implicit none
141  ! -- dummy
142  class(RchType), intent(inout) :: this
143  ! -- local
144  logical(LGP) :: found_fixed_cell = .false.
145  logical(LGP) :: found_readasarrays = .false.
146  !
147  ! -- source common bound options
148  call this%BndExtType%source_options()
149  !
150  ! -- update defaults with idm sourced values
151  call mem_set_value(this%fixed_cell, 'FIXED_CELL', this%input_mempath, &
152  found_fixed_cell)
153  call mem_set_value(this%read_as_arrays, 'READASARRAYS', this%input_mempath, &
154  found_readasarrays)
155  !
156  if (found_readasarrays) then
157  if (this%dis%supports_layers()) then
158  this%text = texta
159  else
160  errmsg = 'READASARRAYS option is not compatible with selected'// &
161  ' discretization type.'
162  call store_error(errmsg)
163  call store_error_filename(this%input_fname)
164  end if
165  end if
166  !
167  ! -- log rch params
168  call this%log_rch_options(found_fixed_cell, found_readasarrays)
Here is the call graph for this function:

◆ set_nodesontop()

subroutine rchmodule::set_nodesontop ( class(rchtype), intent(inout)  this)

Definition at line 281 of file gwf-rch.f90.

282  implicit none
283  ! -- dummy
284  class(RchType), intent(inout) :: this
285  ! -- local
286  integer(I4B) :: n
287  !
288  ! -- allocate if necessary
289  if (.not. associated(this%nodesontop)) then
290  allocate (this%nodesontop(this%maxbound))
291  end if
292  !
293  ! -- copy nodelist into nodesontop
294  do n = 1, this%nbound
295  this%nodesontop(n) = this%nodelist(n)
296  end do

Variable Documentation

◆ ftype

character(len=lenftype) rchmodule::ftype = 'RCH'
private

Definition at line 23 of file gwf-rch.f90.

23  character(len=LENFTYPE) :: ftype = 'RCH'

◆ text

character(len=lenpackagename) rchmodule::text = ' RCH'
private

Definition at line 24 of file gwf-rch.f90.

24  character(len=LENPACKAGENAME) :: text = ' RCH'

◆ texta

character(len=lenpackagename) rchmodule::texta = ' RCHA'
private

Definition at line 25 of file gwf-rch.f90.

25  character(len=LENPACKAGENAME) :: texta = ' RCHA'