MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
gwf-riv.f90
Go to the documentation of this file.
1 module rivmodule
2  use kindmodule, only: dp, i4b
4  use simvariablesmodule, only: errmsg
7  use bndmodule, only: bndtype
8  use bndextmodule, only: bndexttype
11  !
12  implicit none
13  !
14  private
15  public :: riv_create
16  public :: rivtype
17  !
18  character(len=LENFTYPE) :: ftype = 'RIV'
19  character(len=LENPACKAGENAME) :: text = ' RIV'
20  !
21  type, extends(bndexttype) :: rivtype
22  real(dp), dimension(:), pointer, contiguous :: stage => null() !< RIV head
23  real(dp), dimension(:), pointer, contiguous :: cond => null() !< RIV bed hydraulic conductance
24  real(dp), dimension(:), pointer, contiguous :: rbot => null() !< RIV bed bottom elevation
25 
26  contains
27 
28  procedure :: allocate_arrays => riv_allocate_arrays
29  procedure :: source_options => riv_options
30  procedure :: log_riv_options
31  procedure :: bnd_rp => riv_rp
32  procedure :: bnd_ck => riv_ck
33  procedure :: bnd_cf => riv_cf
34  procedure :: bnd_fc => riv_fc
35  procedure :: bnd_da => riv_da
36  procedure :: define_listlabel
37  procedure :: bound_value => riv_bound_value
38  procedure :: cond_mult
39  ! -- methods for observations
40  procedure, public :: bnd_obs_supported => riv_obs_supported
41  procedure, public :: bnd_df_obs => riv_df_obs
42  procedure, public :: riv_store_user_cond
43  end type rivtype
44 
45 contains
46 
47  !> @brief Create a New Riv Package and point packobj to the new package
48  !<
49  subroutine riv_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, &
50  mempath)
51  ! -- dummy
52  class(bndtype), pointer :: packobj
53  integer(I4B), intent(in) :: id
54  integer(I4B), intent(in) :: ibcnum
55  integer(I4B), intent(in) :: inunit
56  integer(I4B), intent(in) :: iout
57  character(len=*), intent(in) :: namemodel
58  character(len=*), intent(in) :: pakname
59  character(len=*), intent(in) :: mempath
60  ! -- local
61  type(rivtype), pointer :: rivobj
62  !
63  ! -- allocate the object and assign values to object variables
64  allocate (rivobj)
65  packobj => rivobj
66  !
67  ! -- create name and memory path
68  call packobj%set_names(ibcnum, namemodel, pakname, ftype, mempath)
69  packobj%text = text
70  !
71  ! -- allocate scalars
72  call rivobj%allocate_scalars()
73  !
74  ! -- initialize package
75  call packobj%pack_initialize()
76  !
77  packobj%inunit = inunit
78  packobj%iout = iout
79  packobj%id = id
80  packobj%ibcnum = ibcnum
81  packobj%ictMemPath = create_mem_path(namemodel, 'NPF')
82  end subroutine riv_create
83 
84  !> @brief Deallocate memory
85  !<
86  subroutine riv_da(this)
87  ! -- modules
89  ! -- dummy
90  class(rivtype) :: this
91  !
92  ! -- Deallocate parent package
93  call this%BndExtType%bnd_da()
94  !
95  ! -- arrays
96  call mem_deallocate(this%stage, 'STAGE', this%memoryPath)
97  call mem_deallocate(this%cond, 'COND', this%memoryPath)
98  call mem_deallocate(this%rbot, 'RBOT', this%memoryPath)
99  end subroutine riv_da
100 
101  !> @brief Set options specific to RivType
102  !<
103  subroutine riv_options(this)
104  ! -- modules
108  ! -- dummy
109  class(rivtype), intent(inout) :: this
110  ! -- local
111  type(gwfrivparamfoundtype) :: found
112  !
113  ! -- source base class options
114  call this%BndExtType%source_options()
115  !
116  ! -- source options from input context
117  call mem_set_value(this%imover, 'MOVER', this%input_mempath, found%mover)
118  !
119  ! -- log riv specific options
120  call this%log_riv_options(found)
121  end subroutine riv_options
122 
123  !> @brief Log options specific to RivType
124  !<
125  subroutine log_riv_options(this, found)
126  ! -- modules
128  ! -- dummy variables
129  class(rivtype), intent(inout) :: this !< BndExtType object
130  type(gwfrivparamfoundtype), intent(in) :: found
131  !
132  ! -- log found options
133  write (this%iout, '(/1x,a)') 'PROCESSING '//trim(adjustl(this%text)) &
134  //' OPTIONS'
135  !
136  if (found%mover) then
137  write (this%iout, '(4x,A)') 'MOVER OPTION ENABLED'
138  end if
139  !
140  ! -- close logging block
141  write (this%iout, '(1x,a)') &
142  'END OF '//trim(adjustl(this%text))//' OPTIONS'
143  end subroutine log_riv_options
144 
145  !> @brief Allocate package arrays
146  !<
147  subroutine riv_allocate_arrays(this, nodelist, auxvar)
148  ! -- modules
150  ! -- dummy
151  class(rivtype) :: this
152  integer(I4B), dimension(:), pointer, contiguous, optional :: nodelist
153  real(DP), dimension(:, :), pointer, contiguous, optional :: auxvar
154  !
155  ! -- call base type allocate arrays
156  call this%BndExtType%allocate_arrays(nodelist, auxvar)
157  !
158  ! -- set riv input context pointers
159  call mem_setptr(this%stage, 'STAGE', this%input_mempath)
160  call mem_setptr(this%cond, 'COND', this%input_mempath)
161  call mem_setptr(this%rbot, 'RBOT', this%input_mempath)
162  !
163  ! --checkin riv input context pointers
164  call mem_checkin(this%stage, 'STAGE', this%memoryPath, &
165  'STAGE', this%input_mempath)
166  call mem_checkin(this%cond, 'COND', this%memoryPath, &
167  'COND', this%input_mempath)
168  call mem_checkin(this%rbot, 'RBOT', this%memoryPath, &
169  'RBOT', this%input_mempath)
170  end subroutine riv_allocate_arrays
171 
172  !> @brief Read and prepare
173  !<
174  subroutine riv_rp(this)
175  ! -- modules
176  use tdismodule, only: kper
177  ! -- dummy
178  class(rivtype), intent(inout) :: this
179  !
180  if (this%iper /= kper) return
181  !
182  ! -- Call the parent class read and prepare
183  call this%BndExtType%bnd_rp()
184  !
185  ! -- store user cond
186  if (this%ivsc == 1) then
187  call this%riv_store_user_cond()
188  end if
189  !
190  ! -- Write the list to iout if requested
191  if (this%iprpak /= 0) then
192  call this%write_list()
193  end if
194  end subroutine riv_rp
195 
196  !> @brief Check river boundary condition data
197  !<
198  subroutine riv_ck(this)
199  ! -- modules
200  use constantsmodule, only: linelength
202  ! -- dummy
203  class(rivtype), intent(inout) :: this
204  ! -- local
205  character(len=LINELENGTH) :: errmsg
206  integer(I4B) :: i
207  integer(I4B) :: node
208  real(DP) :: bt
209  real(DP) :: stage
210  real(DP) :: rbot
211  ! -- formats
212  character(len=*), parameter :: fmtriverr = &
213  "('RIV BOUNDARY (',i0,') RIVER BOTTOM (',f10.4,') IS LESS &
214  &THAN CELL BOTTOM (',f10.4,')')"
215  character(len=*), parameter :: fmtriverr2 = &
216  "('RIV BOUNDARY (',i0,') RIVER STAGE (',f10.4,') IS LESS &
217  &THAN RIVER BOTTOM (',f10.4,')')"
218  character(len=*), parameter :: fmtriverr3 = &
219  "('RIV BOUNDARY (',i0,') RIVER STAGE (',f10.4,') IS LESS &
220  &THAN CELL BOTTOM (',f10.4,')')"
221  character(len=*), parameter :: fmtcondmulterr = &
222  "('RIV BOUNDARY (',i0,') CONDUCTANCE MULTIPLIER (',g10.3,') IS &
223  &LESS THAN ZERO')"
224  character(len=*), parameter :: fmtconderr = &
225  "('RIV BOUNDARY (',i0,') CONDUCTANCE (',g10.3,') IS LESS THAN &
226  &ZERO')"
227  !
228  ! -- check stress period data
229  do i = 1, this%nbound
230  node = this%nodelist(i)
231  bt = this%dis%bot(node)
232  stage = this%stage(i)
233  rbot = this%rbot(i)
234  ! -- accumulate errors
235  if (rbot < bt .and. this%icelltype(node) /= 0) then
236  write (errmsg, fmt=fmtriverr) i, rbot, bt
237  call store_error(errmsg)
238  end if
239  if (stage < rbot) then
240  write (errmsg, fmt=fmtriverr2) i, stage, rbot
241  call store_error(errmsg)
242  end if
243  if (stage < bt .and. this%icelltype(node) /= 0) then
244  write (errmsg, fmt=fmtriverr3) i, stage, bt
245  call store_error(errmsg)
246  end if
247  if (this%iauxmultcol > 0) then
248  if (this%auxvar(this%iauxmultcol, i) < dzero) then
249  write (errmsg, fmt=fmtcondmulterr) &
250  i, this%auxvar(this%iauxmultcol, i)
251  call store_error(errmsg)
252  end if
253  end if
254  if (this%cond(i) < dzero) then
255  write (errmsg, fmt=fmtconderr) i, this%cond(i)
256  call store_error(errmsg)
257  end if
258  end do
259  !
260  ! -- write summary of river package error messages
261  if (count_errors() > 0) then
262  call store_error_unit(this%inunit)
263  end if
264  end subroutine riv_ck
265 
266  !> @brief Formulate the HCOF and RHS terms
267  !!
268  !! Skip in no rivs, otherwise calculate hcof and rhs
269  !<
270  subroutine riv_cf(this)
271  ! -- dummy
272  class(rivtype) :: this
273  ! -- local
274  integer(I4B) :: i, node
275  real(DP) :: hriv, criv, rbot
276  !
277  ! -- Return if no rivs
278  if (this%nbound .eq. 0) return
279  !
280  ! -- Calculate hcof and rhs for each riv entry
281  do i = 1, this%nbound
282  node = this%nodelist(i)
283  if (this%ibound(node) <= 0) then
284  this%hcof(i) = dzero
285  this%rhs(i) = dzero
286  cycle
287  end if
288  hriv = this%stage(i)
289  criv = this%cond_mult(i)
290  rbot = this%rbot(i)
291  if (this%xnew(node) <= rbot) then
292  this%rhs(i) = -criv * (hriv - rbot)
293  this%hcof(i) = dzero
294  else
295  this%rhs(i) = -criv * hriv
296  this%hcof(i) = -criv
297  end if
298  end do
299  end subroutine riv_cf
300 
301  !> @brief Copy rhs and hcof into solution rhs and amat
302  !<
303  subroutine riv_fc(this, rhs, ia, idxglo, matrix_sln)
304  ! -- dummy
305  class(rivtype) :: this
306  real(DP), dimension(:), intent(inout) :: rhs
307  integer(I4B), dimension(:), intent(in) :: ia
308  integer(I4B), dimension(:), intent(in) :: idxglo
309  class(matrixbasetype), pointer :: matrix_sln
310  ! -- local
311  integer(I4B) :: i, n, ipos
312  real(DP) :: cond, stage, qriv !, rbot
313  !
314  ! -- pakmvrobj fc
315  if (this%imover == 1) then
316  call this%pakmvrobj%fc()
317  end if
318  !
319  ! -- Copy package rhs and hcof into solution rhs and amat
320  do i = 1, this%nbound
321  n = this%nodelist(i)
322  rhs(n) = rhs(n) + this%rhs(i)
323  ipos = ia(n)
324  call matrix_sln%add_value_pos(idxglo(ipos), this%hcof(i))
325  !
326  ! -- If mover is active and this river cell is discharging,
327  ! store available water (as positive value).
328  stage = this%stage(i)
329  if (this%imover == 1 .and. this%xnew(n) > stage) then
330  cond = this%cond_mult(i)
331  qriv = cond * (this%xnew(n) - stage)
332  call this%pakmvrobj%accumulate_qformvr(i, qriv)
333  end if
334  end do
335  end subroutine riv_fc
336 
337  !> @brief Define the list heading that is written to iout when PRINT_INPUT
338  !! option is used.
339  !<
340  subroutine define_listlabel(this)
341  ! -- modules
342  class(rivtype), intent(inout) :: this
343  !
344  ! -- create the header list label
345  this%listlabel = trim(this%filtyp)//' NO.'
346  if (this%dis%ndim == 3) then
347  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'LAYER'
348  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'ROW'
349  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'COL'
350  elseif (this%dis%ndim == 2) then
351  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'LAYER'
352  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'CELL2D'
353  else
354  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'NODE'
355  end if
356  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'STAGE'
357  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'CONDUCTANCE'
358  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'BOTTOM EL.'
359  if (this%inamedbound == 1) then
360  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'BOUNDARY NAME'
361  end if
362  end subroutine define_listlabel
363 
364  ! -- Procedures related to observations
365 
366  !> @brief Return true because RIV package supports observations
367  !!
368  !! Return true because RIV package supports observations.
369  !>
370  logical function riv_obs_supported(this)
371  implicit none
372  ! -- dummy
373  class(rivtype) :: this
374  !
375  riv_obs_supported = .true.
376  end function riv_obs_supported
377 
378  !> @brief Store observation type supported by RIV package
379  !!
380  !! Overrides BndType%bnd_df_obs
381  !<
382  subroutine riv_df_obs(this)
383  implicit none
384  ! -- dummy
385  class(rivtype) :: this
386  ! -- local
387  integer(I4B) :: indx
388  !
389  call this%obs%StoreObsType('riv', .true., indx)
390  this%obs%obsData(indx)%ProcessIdPtr => defaultobsidprocessor
391  !
392  ! -- Store obs type and assign procedure pointer
393  ! for to-mvr observation type.
394  call this%obs%StoreObsType('to-mvr', .true., indx)
395  this%obs%obsData(indx)%ProcessIdPtr => defaultobsidprocessor
396  end subroutine riv_df_obs
397 
398  !> @brief Store user-specified conductance value
399  !<
400  subroutine riv_store_user_cond(this)
401  ! -- dummy
402  class(rivtype), intent(inout) :: this !< BndExtType object
403  ! -- local
404  integer(I4B) :: n
405  !
406  ! -- store backup copy of conductance values
407  do n = 1, this%nbound
408  this%condinput(n) = this%cond_mult(n)
409  end do
410  end subroutine riv_store_user_cond
411 
412  !> @brief Apply multiplier to conductance if auxmultcol option is in use
413  !<
414  function cond_mult(this, row) result(cond)
415  ! -- modules
416  use constantsmodule, only: dzero
417  ! -- dummy
418  class(rivtype), intent(inout) :: this !< BndExtType object
419  integer(I4B), intent(in) :: row
420  ! -- result
421  real(dp) :: cond
422  !
423  if (this%iauxmultcol > 0) then
424  cond = this%cond(row) * this%auxvar(this%iauxmultcol, row)
425  else
426  cond = this%cond(row)
427  end if
428  end function cond_mult
429 
430  !> @brief Return requested boundary value
431  !<
432  function riv_bound_value(this, col, row) result(bndval)
433  ! -- modules
434  use constantsmodule, only: dzero
435  ! -- dummy
436  class(rivtype), intent(inout) :: this !< BndExtType object
437  integer(I4B), intent(in) :: col
438  integer(I4B), intent(in) :: row
439  ! -- result
440  real(dp) :: bndval
441  !
442  select case (col)
443  case (1)
444  bndval = this%stage(row)
445  case (2)
446  bndval = this%cond_mult(row)
447  case (3)
448  bndval = this%rbot(row)
449  case default
450  errmsg = 'Programming error. RIV bound value requested column '&
451  &'outside range of ncolbnd (3).'
452  call store_error(errmsg)
453  call store_error_filename(this%input_fname)
454  end select
455  end function riv_bound_value
456 
457 end module rivmodule
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
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
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 riv_store_user_cond(this)
Store user-specified conductance value.
Definition: gwf-riv.f90:401
logical function riv_obs_supported(this)
Return true because RIV package supports observations.
Definition: gwf-riv.f90:371
real(dp) function cond_mult(this, row)
Apply multiplier to conductance if auxmultcol option is in use.
Definition: gwf-riv.f90:415
subroutine riv_allocate_arrays(this, nodelist, auxvar)
Allocate package arrays.
Definition: gwf-riv.f90:148
subroutine log_riv_options(this, found)
Log options specific to RivType.
Definition: gwf-riv.f90:126
subroutine riv_df_obs(this)
Store observation type supported by RIV package.
Definition: gwf-riv.f90:383
character(len=lenftype) ftype
Definition: gwf-riv.f90:18
subroutine define_listlabel(this)
Define the list heading that is written to iout when PRINT_INPUT option is used.
Definition: gwf-riv.f90:341
subroutine riv_options(this)
Set options specific to RivType.
Definition: gwf-riv.f90:104
character(len=lenpackagename) text
Definition: gwf-riv.f90:19
subroutine, public riv_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, mempath)
Create a New Riv Package and point packobj to the new package.
Definition: gwf-riv.f90:51
subroutine riv_cf(this)
Formulate the HCOF and RHS terms.
Definition: gwf-riv.f90:271
real(dp) function riv_bound_value(this, col, row)
Return requested boundary value.
Definition: gwf-riv.f90:433
subroutine riv_ck(this)
Check river boundary condition data.
Definition: gwf-riv.f90:199
subroutine riv_da(this)
Deallocate memory.
Definition: gwf-riv.f90:87
subroutine riv_fc(this, rhs, ia, idxglo, matrix_sln)
Copy rhs and hcof into solution rhs and amat.
Definition: gwf-riv.f90:304
subroutine riv_rp(this)
Read and prepare.
Definition: gwf-riv.f90:175
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
subroutine, public store_error_unit(iunit, terminate)
Store the file unit number.
Definition: Sim.f90:168
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