MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
swf-flw.f90
Go to the documentation of this file.
1 !> @brief This module contains the FLW package methods
2 !!
3 !! This module can be used to represent inflow to streams. It is
4 !! designed similarly to the GWF WEL package.
5 !!
6 !<
8  ! -- modules
9  use kindmodule, only: dp, i4b
10  use constantsmodule, only: dzero, dem1, done, lenftype, dnodata, &
12  use simvariablesmodule, only: errmsg
15  use bndmodule, only: bndtype
16  use bndextmodule, only: bndexttype
19  use observemodule, only: observetype
25  !
26  implicit none
27  !
28  private
29  public :: flw_create
30  !
31  character(len=LENFTYPE) :: ftype = 'FLW' !< package ftype
32  character(len=16) :: text = ' FLW' !< package flow text string
33  !
34  type, extends(bndexttype) :: swfflwtype
35  real(dp), dimension(:), pointer, contiguous :: q => null() !< volumetric rate
36  contains
37  procedure :: allocate_scalars => flw_allocate_scalars
38  procedure :: allocate_arrays => flw_allocate_arrays
39  procedure :: source_options => flw_options
40  procedure :: log_flw_options
41  procedure :: bnd_rp => flw_rp
42  procedure :: bnd_cf => flw_cf
43  procedure :: bnd_fc => flw_fc
44  procedure :: bnd_da => flw_da
45  procedure :: define_listlabel
46  procedure :: bound_value => flw_bound_value
47  procedure :: q_mult
48  ! -- methods for observations
49  procedure, public :: bnd_obs_supported => flw_obs_supported
50  procedure, public :: bnd_df_obs => flw_df_obs
51  procedure, public :: bnd_bd_obs => flw_bd_obs
52  ! -- methods for time series
53  procedure, public :: bnd_rp_ts => flw_rp_ts
54  end type swfflwtype
55 
56 contains
57 
58  !> @ brief Create a new package object
59  !!
60  !! Create a new FLW Package object
61  !!
62  !<
63  subroutine flw_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, &
64  mempath)
65  ! -- dummy variables
66  class(bndtype), pointer :: packobj !< pointer to default package type
67  integer(I4B), intent(in) :: id !< package id
68  integer(I4B), intent(in) :: ibcnum !< boundary condition number
69  integer(I4B), intent(in) :: inunit !< unit number of FLW package input file
70  integer(I4B), intent(in) :: iout !< unit number of model listing file
71  character(len=*), intent(in) :: namemodel !< model name
72  character(len=*), intent(in) :: pakname !< package name
73  character(len=*), intent(in) :: mempath !< input mempath
74  ! -- local variables
75  type(swfflwtype), pointer :: flwobj
76  !
77  ! -- allocate the object and assign values to object variables
78  allocate (flwobj)
79  packobj => flwobj
80  !
81  ! -- create name and memory path
82  call packobj%set_names(ibcnum, namemodel, pakname, ftype, mempath)
83  packobj%text = text
84  !
85  ! -- allocate scalars
86  call flwobj%allocate_scalars()
87  !
88  ! -- initialize package
89  call packobj%pack_initialize()
90 
91  packobj%inunit = inunit
92  packobj%iout = iout
93  packobj%id = id
94  packobj%ibcnum = ibcnum
95  packobj%ncolbnd = 1
96  packobj%iscloc = 1
97  packobj%ictMemPath = ''
98  end subroutine flw_create
99 
100  !> @ brief Allocate scalars
101  !!
102  !! Allocate and initialize scalars for the FLW package. The base model
103  !! allocate scalars method is also called.
104  !!
105  !<
106  subroutine flw_allocate_scalars(this)
107  ! -- modules
109  ! -- dummy variables
110  class(swfflwtype) :: this !< SwfFlwType object
111  !
112  ! -- call base type allocate scalars
113  call this%BndExtType%allocate_scalars()
114  !
115  ! -- allocate the object and assign values to object variables
116  ! none for this package
117  !
118  ! -- Set values
119  ! none for this package
120  end subroutine flw_allocate_scalars
121 
122  !> @ brief Allocate arrays
123  !!
124  !! Allocate and initialize arrays for the SWF package
125  !!
126  !<
127  subroutine flw_allocate_arrays(this, nodelist, auxvar)
128  ! -- modules
130  ! -- dummy
131  class(swfflwtype) :: this
132  integer(I4B), dimension(:), pointer, contiguous, optional :: nodelist
133  real(DP), dimension(:, :), pointer, contiguous, optional :: auxvar
134  ! -- local
135  !
136  ! -- call BndExtType allocate scalars
137  call this%BndExtType%allocate_arrays(nodelist, auxvar)
138  !
139  ! -- set q array input context pointer
140  call mem_setptr(this%q, 'Q', this%input_mempath)
141  !
142  ! -- checkin q array input context pointer
143  call mem_checkin(this%q, 'Q', this%memoryPath, &
144  'Q', this%input_mempath)
145  end subroutine flw_allocate_arrays
146 
147  !> @ brief Deallocate package memory
148  !!
149  !! Deallocate SWF package scalars and arrays.
150  !!
151  !<
152  subroutine flw_da(this)
153  ! -- modules
155  ! -- dummy variables
156  class(swfflwtype) :: this !< SwfFlwType object
157  !
158  ! -- Deallocate parent package
159  call this%BndExtType%bnd_da()
160  !
161  ! -- scalars
162  call mem_deallocate(this%q, 'Q', this%memoryPath)
163  end subroutine flw_da
164 
165  !> @ brief Source additional options for package
166  !!
167  !! Source additional options for SWF package.
168  !!
169  !<
170  subroutine flw_options(this)
171  ! -- modules
172  use inputoutputmodule, only: urword
175  ! -- dummy variables
176  class(swfflwtype), intent(inout) :: this !< SwfFlwType object
177  ! -- local variables
178  type(swfflwparamfoundtype) :: found
179  ! -- formats
180  !
181  ! -- source base BndExtType options
182  call this%BndExtType%source_options()
183  !
184  ! -- source options from input context
185  ! none
186  !
187  ! -- log SWF specific options
188  call this%log_flw_options(found)
189  end subroutine flw_options
190 
191  !> @ brief Log SWF specific package options
192  !<
193  subroutine log_flw_options(this, found)
194  ! -- modules
196  ! -- dummy variables
197  class(swfflwtype), intent(inout) :: this !< BndExtType object
198  type(swfflwparamfoundtype), intent(in) :: found
199  ! -- local variables
200  ! -- format
201  !
202  ! -- log found options
203  write (this%iout, '(/1x,a)') 'PROCESSING '//trim(adjustl(this%text)) &
204  //' OPTIONS'
205  !
206  ! if (found%mover) then
207  ! write (this%iout, '(4x,A)') 'MOVER OPTION ENABLED'
208  ! end if
209  !
210  ! -- close logging block
211  write (this%iout, '(1x,a)') &
212  'END OF '//trim(adjustl(this%text))//' OPTIONS'
213  end subroutine log_flw_options
214 
215  !> @ brief SWF read and prepare
216  !!
217  !<
218  subroutine flw_rp(this)
219  use tdismodule, only: kper
220  ! -- dummy
221  class(swfflwtype), intent(inout) :: this
222  ! -- local
223  !
224  if (this%iper /= kper) return
225  !
226  ! -- Call the parent class read and prepare
227  call this%BndExtType%bnd_rp()
228  !
229  ! -- Write the list to iout if requested
230  if (this%iprpak /= 0) then
231  call this%write_list()
232  end if
233  end subroutine flw_rp
234 
235  !> @ brief Formulate the package hcof and rhs terms.
236  !!
237  !! Formulate the hcof and rhs terms for the FLW package that will be
238  !! added to the coefficient matrix and right-hand side vector.
239  !!
240  !<
241  subroutine flw_cf(this)
242  ! -- dummy variables
243  class(swfflwtype) :: this !< SwfFlwType object
244  ! -- local variables
245  integer(I4B) :: i, node
246  real(DP) :: q
247  !
248  ! -- Return if no inflows
249  if (this%nbound == 0) return
250  !
251  ! -- Calculate hcof and rhs for each flw entry
252  do i = 1, this%nbound
253  node = this%nodelist(i)
254  this%hcof(i) = dzero
255  if (this%ibound(node) <= 0) then
256  this%rhs(i) = dzero
257  cycle
258  end if
259  q = this%q_mult(i)
260  this%rhs(i) = -q
261  end do
262  end subroutine flw_cf
263 
264  !> @ brief Copy hcof and rhs terms into solution.
265  !!
266  !! Add the hcof and rhs terms for the FLW package to the
267  !! coefficient matrix and right-hand side vector.
268  !!
269  !<
270  subroutine flw_fc(this, rhs, ia, idxglo, matrix_sln)
271  ! -- dummy variables
272  class(swfflwtype) :: this !< SwfFlwType object
273  real(DP), dimension(:), intent(inout) :: rhs !< right-hand side vector for model
274  integer(I4B), dimension(:), intent(in) :: ia !< solution CRS row pointers
275  integer(I4B), dimension(:), intent(in) :: idxglo !< mapping vector for model (local) to solution (global)
276  class(matrixbasetype), pointer :: matrix_sln !< solution coefficient matrix
277  ! -- local variables
278  integer(I4B) :: i
279  integer(I4B) :: n
280  integer(I4B) :: ipos
281  !
282  ! -- pakmvrobj fc
283  if (this%imover == 1) then
284  call this%pakmvrobj%fc()
285  end if
286  !
287  ! -- Copy package rhs and hcof into solution rhs and amat
288  do i = 1, this%nbound
289  n = this%nodelist(i)
290  rhs(n) = rhs(n) + this%rhs(i)
291  ipos = ia(n)
292  call matrix_sln%add_value_pos(idxglo(ipos), this%hcof(i))
293  !
294  ! -- If mover is active and this flw item is discharging,
295  ! store available water (as positive value).
296  if (this%imover == 1 .and. this%rhs(i) > dzero) then
297  call this%pakmvrobj%accumulate_qformvr(i, this%rhs(i))
298  end if
299  end do
300  end subroutine flw_fc
301 
302  !> @ brief Define the list label for the package
303  !!
304  !! Method defined the list label for the FLW package. The list label is
305  !! the heading that is written to iout when PRINT_INPUT option is used.
306  !!
307  !<
308  subroutine define_listlabel(this)
309  ! -- dummy variables
310  class(swfflwtype), intent(inout) :: this !< SwfFlwType object
311  !
312  ! -- create the header list label
313  this%listlabel = trim(this%filtyp)//' NO.'
314  if (this%dis%ndim == 3) then
315  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'LAYER'
316  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'ROW'
317  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'COL'
318  elseif (this%dis%ndim == 2) then
319  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'LAYER'
320  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'CELL2D'
321  else
322  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'NODE'
323  end if
324  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'FLOW RATE'
325  if (this%inamedbound == 1) then
326  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'BOUNDARY NAME'
327  end if
328  end subroutine define_listlabel
329 
330  ! -- Procedures related to observations
331 
332  !> @brief Determine if observations are supported.
333  !!
334  !! Function to determine if observations are supported by the FLW package.
335  !! Observations are supported by the FLW package.
336  !!
337  !! @return flw_obs_supported boolean indicating if observations are supported
338  !!
339  !<
340  logical function flw_obs_supported(this)
341  ! -- dummy variables
342  class(swfflwtype) :: this !< SwfFlwType object
343  !
344  ! -- set boolean
345  flw_obs_supported = .true.
346  end function flw_obs_supported
347 
348  !> @brief Define the observation types available in the package
349  !!
350  !! Method to define the observation types available in the FLW package.
351  !!
352  !<
353  subroutine flw_df_obs(this)
354  ! -- dummy variables
355  class(swfflwtype) :: this !< SwfFlwType object
356  ! -- local variables
357  integer(I4B) :: indx
358  !
359  ! -- initialize observations
360  call this%obs%StoreObsType('flw', .true., indx)
361  this%obs%obsData(indx)%ProcessIdPtr => defaultobsidprocessor
362  !
363  ! -- Store obs type and assign procedure pointer
364  ! for to-mvr observation type.
365  call this%obs%StoreObsType('to-mvr', .true., indx)
366  this%obs%obsData(indx)%ProcessIdPtr => defaultobsidprocessor
367  end subroutine flw_df_obs
368 
369  !> @brief Save observations for the package
370  !!
371  !! Method to save simulated values for the FLW package.
372  !!
373  !<
374  subroutine flw_bd_obs(this)
375  ! -- dummy variables
376  class(swfflwtype) :: this !< SwfFlwType object
377  ! -- local variables
378  integer(I4B) :: i
379  integer(I4B) :: n
380  integer(I4B) :: jj
381  real(DP) :: v
382  type(observetype), pointer :: obsrv => null()
383  !
384  ! -- clear the observations
385  call this%obs%obs_bd_clear()
386  !
387  ! -- Save simulated values for all of package's observations.
388  do i = 1, this%obs%npakobs
389  obsrv => this%obs%pakobs(i)%obsrv
390  if (obsrv%BndFound) then
391  do n = 1, obsrv%indxbnds_count
392  v = dnodata
393  jj = obsrv%indxbnds(n)
394  select case (obsrv%ObsTypeId)
395  case ('TO-MVR')
396  if (this%imover == 1) then
397  v = this%pakmvrobj%get_qtomvr(jj)
398  if (v > dzero) then
399  v = -v
400  end if
401  end if
402  case ('FLW')
403  v = this%simvals(jj)
404  case default
405  errmsg = 'Unrecognized observation type: '//trim(obsrv%ObsTypeId)
406  call store_error(errmsg)
407  end select
408  call this%obs%SaveOneSimval(obsrv, v)
409  end do
410  else
411  call this%obs%SaveOneSimval(obsrv, dnodata)
412  end if
413  end do
414  end subroutine flw_bd_obs
415 
416  ! -- Procedure related to time series
417 
418  !> @brief Assign time series links for the package
419  !!
420  !! Assign the time series links for the FLW package. Only
421  !! the Q variable can be defined with time series.
422  !!
423  !<
424  subroutine flw_rp_ts(this)
425  ! -- dummy variables
426  class(swfflwtype), intent(inout) :: this !< SwfFlwType object
427  ! -- local variables
428  integer(I4B) :: i, nlinks
429  type(timeserieslinktype), pointer :: tslink => null()
430  !
431  ! -- set up the time series links
432  nlinks = this%TsManager%boundtslinks%Count()
433  do i = 1, nlinks
434  tslink => gettimeserieslinkfromlist(this%TsManager%boundtslinks, i)
435  if (associated(tslink)) then
436  if (tslink%JCol == 1) then
437  tslink%Text = 'Q'
438  end if
439  end if
440  end do
441  end subroutine flw_rp_ts
442 
443  function q_mult(this, row) result(q)
444  ! -- modules
445  use constantsmodule, only: dzero
446  ! -- dummy variables
447  class(swfflwtype), intent(inout) :: this !< BndExtType object
448  integer(I4B), intent(in) :: row
449  ! -- result
450  real(dp) :: q
451  !
452  if (this%iauxmultcol > 0) then
453  q = this%q(row) * this%auxvar(this%iauxmultcol, row)
454  else
455  q = this%q(row)
456  end if
457  end function q_mult
458 
459  !> @ brief Return a bound value
460  !!
461  !! Return a bound value associated with an ncolbnd index
462  !! and row.
463  !!
464  !<
465  function flw_bound_value(this, col, row) result(bndval)
466  ! -- modules
467  use constantsmodule, only: dzero
468  ! -- dummy variables
469  class(swfflwtype), intent(inout) :: this !< BndExtType object
470  integer(I4B), intent(in) :: col
471  integer(I4B), intent(in) :: row
472  ! -- result
473  real(dp) :: bndval
474  !
475  select case (col)
476  case (1)
477  bndval = this%q_mult(row)
478  case default
479  errmsg = 'Programming error. FLW bound value requested column '&
480  &'outside range of ncolbnd (1).'
481  call store_error(errmsg)
482  call store_error_filename(this%input_fname)
483  end select
484  end function flw_bound_value
485 
486 end module swfflwmodule
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
real(dp), parameter dnodata
real no data constant
Definition: Constants.f90:95
real(dp), parameter dem1
real constant 1e-1
Definition: Constants.f90:103
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
real(dp), parameter done
real constant 1
Definition: Constants.f90:76
integer(i4b) function, public getunit()
Get a free unit number.
subroutine, public openfile(iu, iout, fname, ftype, fmtarg_opt, accarg_opt, filstat_opt, mode_opt)
Open a file.
Definition: InputOutput.f90:30
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 types ObserveType and ObsDataType.
Definition: Observe.f90:15
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
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 sqsaturationderivative(top, bot, x, c1, c2)
@ brief sQSaturationDerivative
real(dp) function sqsaturation(top, bot, x, c1, c2)
@ brief sQSaturation
This module contains the FLW package methods.
Definition: swf-flw.f90:7
subroutine flw_df_obs(this)
Define the observation types available in the package.
Definition: swf-flw.f90:354
character(len=lenftype) ftype
package ftype
Definition: swf-flw.f90:31
subroutine flw_cf(this)
@ brief Formulate the package hcof and rhs terms.
Definition: swf-flw.f90:242
subroutine, public flw_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, mempath)
@ brief Create a new package object
Definition: swf-flw.f90:65
subroutine flw_da(this)
@ brief Deallocate package memory
Definition: swf-flw.f90:153
real(dp) function flw_bound_value(this, col, row)
@ brief Return a bound value
Definition: swf-flw.f90:466
logical function flw_obs_supported(this)
Determine if observations are supported.
Definition: swf-flw.f90:341
subroutine flw_allocate_scalars(this)
@ brief Allocate scalars
Definition: swf-flw.f90:107
character(len=16) text
package flow text string
Definition: swf-flw.f90:32
subroutine flw_rp(this)
@ brief SWF read and prepare
Definition: swf-flw.f90:219
subroutine flw_bd_obs(this)
Save observations for the package.
Definition: swf-flw.f90:375
subroutine define_listlabel(this)
@ brief Define the list label for the package
Definition: swf-flw.f90:309
subroutine log_flw_options(this, found)
@ brief Log SWF specific package options
Definition: swf-flw.f90:194
subroutine flw_options(this)
@ brief Source additional options for package
Definition: swf-flw.f90:171
real(dp) function q_mult(this, row)
Definition: swf-flw.f90:444
subroutine flw_allocate_arrays(this, nodelist, auxvar)
@ brief Allocate arrays
Definition: swf-flw.f90:128
subroutine flw_fc(this, rhs, ia, idxglo, matrix_sln)
@ brief Copy hcof and rhs terms into solution.
Definition: swf-flw.f90:271
subroutine flw_rp_ts(this)
Assign time series links for the package.
Definition: swf-flw.f90:425
integer(i4b), pointer, public kper
current stress period number
Definition: tdis.f90:23
type(timeserieslinktype) function, pointer, public gettimeserieslinkfromlist(list, indx)
Get time series link from a list.
@ brief BndType