MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
gwf-rch.f90
Go to the documentation of this file.
1 module rchmodule
2  !
3  use kindmodule, only: dp, i4b, lgp
7  use bndmodule, only: bndtype
8  use bndextmodule, only: bndexttype
10  use simvariablesmodule, only: errmsg
16  use geomutilmodule, only: get_node
17  !
18  implicit none
19  !
20  private
21  public :: rch_create
22  !
23  character(len=LENFTYPE) :: ftype = 'RCH'
24  character(len=LENPACKAGENAME) :: text = ' RCH'
25  character(len=LENPACKAGENAME) :: texta = ' RCHA'
26  !
27  type, extends(bndexttype) :: rchtype
28  real(dp), dimension(:), pointer, contiguous :: recharge => null() !< boundary recharge array
29  integer(I4B), dimension(:), pointer, contiguous :: nodesontop => null() ! User provided cell numbers; nodelist is cells where recharge is applied)
30  logical, pointer, private :: fixed_cell
31  logical, pointer, private :: read_as_arrays
32 
33  contains
34 
35  procedure :: rch_allocate_scalars
36  procedure :: allocate_arrays => rch_allocate_arrays
37  procedure :: source_options => rch_source_options
38  procedure :: source_dimensions => rch_source_dimensions
39  procedure :: log_rch_options
40  procedure :: read_initial_attr => rch_read_initial_attr
41  procedure :: bnd_rp => rch_rp
42  procedure :: bnd_cf => rch_cf
43  procedure :: bnd_fc => rch_fc
44  procedure :: bnd_da => rch_da
45  procedure :: set_nodesontop
46  procedure :: define_listlabel => rch_define_listlabel
47  procedure :: bound_value => rch_bound_value
48  procedure, private :: default_nodelist
49  ! -- for observations
50  procedure, public :: bnd_obs_supported => rch_obs_supported
51  procedure, public :: bnd_df_obs => rch_df_obs
52 
53  end type rchtype
54 
55 contains
56 
57  !> @brief Create a New Recharge Package
58  !!
59  !! Create new RCH package and point packobj to the new package
60  !<
61  subroutine rch_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, &
62  mempath)
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')
94  end subroutine rch_create
95 
96  !> @brief Allocate scalar members
97  !<
98  subroutine rch_allocate_scalars(this)
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.
112  end subroutine rch_allocate_scalars
113 
114  !> @brief Allocate package arrays
115  !<
116  subroutine rch_allocate_arrays(this, nodelist, auxvar)
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)
133  end subroutine rch_allocate_arrays
134 
135  !> @brief Source options specific to RchType
136  !<
137  subroutine rch_source_options(this)
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)
169  end subroutine rch_source_options
170 
171  !> @brief Log options specific to RchType
172  !<
173  subroutine log_rch_options(this, found_fixed_cell, found_readasarrays)
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'
200  end subroutine log_rch_options
201 
202  !> @brief Source the dimensions for this package
203  !!
204  !! Dimensions block is not required if:
205  !! (1) discretization is DIS or DISV, and
206  !! (2) READASARRAYS option has been specified.
207  !<
208  subroutine rch_source_dimensions(this)
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()
232  end subroutine rch_source_dimensions
233 
234  !> @brief Part of allocate and read
235  !<
236  subroutine rch_read_initial_attr(this)
237  ! -- dummy
238  class(rchtype), intent(inout) :: this
239  !
240  if (this%read_as_arrays) then
241  call this%default_nodelist()
242  end if
243  end subroutine rch_read_initial_attr
244 
245  !> @brief Read and Prepare
246  !!
247  !! Read itmp and read new boundaries if itmp > 0
248  !<
249  subroutine rch_rp(this)
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
277  end subroutine rch_rp
278 
279  !> @brief Store nodelist in nodesontop
280  !<
281  subroutine set_nodesontop(this)
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
297  end subroutine set_nodesontop
298 
299  !> @brief Formulate the HCOF and RHS terms
300  !!
301  !! Skip if no recharge. Otherwise, calculate hcof and rhs
302  !<
303  subroutine rch_cf(this)
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
353  end subroutine rch_cf
354 
355  !> @brief Copy rhs and hcof into solution rhs and amat
356  !<
357  subroutine rch_fc(this, rhs, ia, idxglo, matrix_sln)
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
381  end subroutine rch_fc
382 
383  !> @brief Deallocate memory
384  !<
385  subroutine rch_da(this)
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)
401  end subroutine rch_da
402 
403  !> @brief Define the list heading that is written to iout when PRINT_INPUT
404  !! option is used.
405  !<
406  subroutine rch_define_listlabel(this)
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
428  end subroutine rch_define_listlabel
429 
430  !> @brief Assign default nodelist when READASARRAYS is specified.
431  !!
432  !! Equivalent to reading IRCH as CONSTANT 1
433  !<
434  subroutine default_nodelist(this)
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()
469  end subroutine default_nodelist
470 
471  ! -- Procedures related to observations
472 
473  !> @brief
474  !!
475  !! Overrides BndType%bnd_obs_supported()
476  !<
477  logical function rch_obs_supported(this)
478  implicit none
479  ! -- dummy
480  class(rchtype) :: this
481  !
482  rch_obs_supported = .true.
483  end function rch_obs_supported
484 
485  !> @brief Implements bnd_df_obs
486  !!
487  !! Store observation type supported by RCH package. Overrides
488  !! BndType%bnd_df_obs
489  !<
490  subroutine rch_df_obs(this)
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
499  end subroutine rch_df_obs
500 
501  !> @brief Return requested boundary value
502  !<
503  function rch_bound_value(this, col, row) result(bndval)
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
526  end function rch_bound_value
527 
528  !> @brief Update the nodelist based on IRCH input
529  !!
530  !! This is a module scoped routine to check for IRCH
531  !! input. If array input was provided, INIRCH and IRCH
532  !! will be allocated in the input context. If the read
533  !! state variable INIRCH is set to 1 during this period
534  !! update, IRCH input was read and is used here to update
535  !! the nodelist.
536  !!
537  !<
538  subroutine nodelist_update(nodelist, nbound, maxbound, &
539  dis, input_mempath)
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
570  end subroutine nodelist_update
571 
572 end module rchmodule
573 
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
integer(i4b), parameter lenpackagename
maximum length of the package name
Definition: Constants.f90:23
integer(i4b), parameter iwetlake
integer constant for a dry lake
Definition: Constants.f90:52
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 maxcharlen
maximum length of char string
Definition: Constants.f90:47
integer(i4b) function, public get_node(ilay, irow, icol, nlay, nrow, ncol)
Get node number, given layer, row, and column indices for a structured grid. If any argument is inval...
Definition: GeomUtil.f90:83
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
subroutine rch_allocate_arrays(this, nodelist, auxvar)
Allocate package arrays.
Definition: gwf-rch.f90:117
logical function rch_obs_supported(this)
Overrides BndTypebnd_obs_supported()
Definition: gwf-rch.f90:478
subroutine nodelist_update(nodelist, nbound, maxbound, dis, input_mempath)
Update the nodelist based on IRCH input.
Definition: gwf-rch.f90:540
subroutine rch_df_obs(this)
Implements bnd_df_obs.
Definition: gwf-rch.f90:491
subroutine default_nodelist(this)
Assign default nodelist when READASARRAYS is specified.
Definition: gwf-rch.f90:435
subroutine, public rch_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, mempath)
Create a New Recharge Package.
Definition: gwf-rch.f90:63
subroutine rch_fc(this, rhs, ia, idxglo, matrix_sln)
Copy rhs and hcof into solution rhs and amat.
Definition: gwf-rch.f90:358
real(dp) function rch_bound_value(this, col, row)
Return requested boundary value.
Definition: gwf-rch.f90:504
subroutine log_rch_options(this, found_fixed_cell, found_readasarrays)
Log options specific to RchType.
Definition: gwf-rch.f90:174
subroutine rch_allocate_scalars(this)
Allocate scalar members.
Definition: gwf-rch.f90:99
character(len=lenpackagename) texta
Definition: gwf-rch.f90:25
subroutine rch_read_initial_attr(this)
Part of allocate and read.
Definition: gwf-rch.f90:237
subroutine rch_rp(this)
Read and Prepare.
Definition: gwf-rch.f90:250
subroutine rch_define_listlabel(this)
Define the list heading that is written to iout when PRINT_INPUT option is used.
Definition: gwf-rch.f90:407
subroutine rch_cf(this)
Formulate the HCOF and RHS terms.
Definition: gwf-rch.f90:304
subroutine rch_source_options(this)
Source options specific to RchType.
Definition: gwf-rch.f90:138
subroutine rch_da(this)
Deallocate memory.
Definition: gwf-rch.f90:386
character(len=lenpackagename) text
Definition: gwf-rch.f90:24
subroutine set_nodesontop(this)
Store nodelist in nodesontop.
Definition: gwf-rch.f90:282
character(len=lenftype) ftype
Definition: gwf-rch.f90:23
subroutine rch_source_dimensions(this)
Source the dimensions for this package.
Definition: gwf-rch.f90:209
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
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