MODFLOW 6  version 6.7.0.dev3
USGS Modular Hydrologic Model
gwe-esl.f90
Go to the documentation of this file.
2  !
3  use kindmodule, only: dp, i4b
5  use simvariablesmodule, only: warnmsg
6  use simmodule, only: store_warning
7  use bndextmodule, only: bndexttype
11  !
12  implicit none
13  !
14  private
15  public :: esl_create
16  !
17  character(len=LENFTYPE) :: ftype = 'ESL'
18  character(len=16) :: text = ' ESL'
19  !
20  type, extends(bndexttype) :: gweesltype
21 
22  type(gweinputdatatype), pointer :: gwecommon => null() !< pointer to shared gwe data used by multiple packages but set in mst
23  real(dp), dimension(:), pointer, contiguous :: senerrate => null() !< energy source loading rate
24 
25  contains
26 
27  procedure :: allocate_scalars => esl_allocate_scalars
28  procedure :: allocate_arrays => esl_allocate_arrays
29  procedure :: bnd_cf => esl_cf
30  procedure :: bnd_ck => esl_ck
31  procedure :: bnd_fc => esl_fc
32  procedure :: bnd_da => esl_da
33  procedure :: define_listlabel
34  procedure :: bound_value => esl_bound_value
35  procedure :: ener_mult
36  ! -- methods for observations
37  procedure, public :: bnd_obs_supported => esl_obs_supported
38  procedure, public :: bnd_df_obs => esl_df_obs
39 
40  end type gweesltype
41 
42 contains
43 
44  !> @brief Create an energy source loading package
45  !!
46  !! This subroutine points bndobj to the newly created package
47  !<
48  subroutine esl_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, &
49  gwecommon, input_mempath)
50  ! -- modules
51  use bndmodule, only: bndtype
52  ! -- dummy
53  class(bndtype), pointer :: packobj
54  integer(I4B), intent(in) :: id
55  integer(I4B), intent(in) :: ibcnum
56  integer(I4B), intent(in) :: inunit
57  integer(I4B), intent(in) :: iout
58  character(len=*), intent(in) :: namemodel
59  character(len=*), intent(in) :: pakname
60  type(gweinputdatatype), intent(in), target :: gwecommon !< shared data container for use by multiple GWE packages
61  character(len=*), intent(in) :: input_mempath
62  ! -- local
63  type(gweesltype), pointer :: eslobj
64  !
65  ! -- Allocate the object and assign values to object variables
66  allocate (eslobj)
67  packobj => eslobj
68  !
69  ! -- Create name and memory path
70  call packobj%set_names(ibcnum, namemodel, pakname, ftype, input_mempath)
71  packobj%text = text
72  !
73  ! -- Allocate scalars
74  call eslobj%allocate_scalars()
75  !
76  ! -- Initialize package
77  call packobj%pack_initialize()
78  !
79  packobj%inunit = inunit
80  packobj%iout = iout
81  packobj%id = id
82  packobj%ibcnum = ibcnum
83  packobj%ncolbnd = 1
84  packobj%iscloc = 1
85  !
86  ! -- Store pointer to shared data module for accessing cpw, rhow
87  ! for the budget calculations, and for accessing the latent heat of
88  ! vaporization for evaporative cooling.
89  eslobj%gwecommon => gwecommon
90  end subroutine esl_create
91 
92  !> @brief Deallocate memory
93  !<
94  subroutine esl_da(this)
95  ! -- modules
97  ! -- dummy
98  class(gweesltype) :: this
99  !
100  ! -- Deallocate parent package
101  call this%BndExtType%bnd_da()
102  end subroutine esl_da
103 
104  !> @brief Allocate scalars
105  !!
106  !! Allocate scalars specific to this energy source loading package
107  !<
108  subroutine esl_allocate_scalars(this)
109  ! -- modules
111  ! -- dummy
112  class(gweesltype) :: this
113  !
114  ! -- base class allocate scalars
115  call this%BndExtType%allocate_scalars()
116  !
117  ! -- allocate the object and assign values to object variables
118  !
119  ! -- Set values
120  end subroutine esl_allocate_scalars
121 
122  !> @brief Allocate arrays
123  !<
124  subroutine esl_allocate_arrays(this, nodelist, auxvar)
126  ! -- dummy
127  class(gweesltype) :: this
128  ! -- local
129  integer(I4B), dimension(:), pointer, contiguous, optional :: nodelist !< package nodelist
130  real(DP), dimension(:, :), pointer, contiguous, optional :: auxvar !< package aux variable array
131 
132  ! -- base class allocate arrays
133  call this%BndExtType%allocate_arrays(nodelist, auxvar)
134 
135  ! -- set input context pointers
136  call mem_setptr(this%senerrate, 'SENERRATE', this%input_mempath)
137  !
138  ! -- checkin input context pointers
139  call mem_checkin(this%senerrate, 'SENERRATE', this%memoryPath, &
140  'SENERRATE', this%input_mempath)
141  end subroutine esl_allocate_arrays
142 
143  !> @brief Check energy source loading boundary condition data
144  !<
145  subroutine esl_ck(this)
146  ! -- dummy
147  class(gweesltype), intent(inout) :: this
148  ! -- local
149  integer(I4B) :: i
150  integer(I4B) :: node
151  ! -- formats
152  character(len=*), parameter :: fmtenermulterr = &
153  "('ESL BOUNDARY (',i0,') ESL MULTIPLIER (',g10.3,') IS &
154  &LESS THAN ZERO THEREBY REVERSING THE ORIGINAL SIGN ON THE &
155  &AMOUNT OF ENERGY ENTERING OR EXITING THE MODEL.')"
156  !
157  ! -- check stress period data
158  do i = 1, this%nbound
159  node = this%nodelist(i)
160  !
161  ! -- accumulate warnings
162  if (this%iauxmultcol > 0) then
163  if (this%auxvar(this%iauxmultcol, i) < dzero) then
164  write (warnmsg, fmt=fmtenermulterr) &
165  i, this%auxvar(this%iauxmultcol, i)
166  call store_warning(warnmsg)
167  write (this%iout, '(/1x,a)') 'WARNING: '//trim(warnmsg)
168  end if
169  end if
170  end do
171  end subroutine esl_ck
172 
173  !> @brief Formulate the HCOF and RHS terms
174  !!
175  !! This subroutine:
176  !! - calculates hcof and rhs terms
177  !! - skip if no sources
178  !<
179  subroutine esl_cf(this)
180  ! -- dummy
181  class(gweesltype) :: this
182  ! -- local
183  integer(I4B) :: i, node
184  real(DP) :: q
185  !
186  ! -- Return if no sources
187  if (this%nbound == 0) return
188  !
189  ! -- Calculate hcof and rhs for each source entry
190  do i = 1, this%nbound
191  node = this%nodelist(i)
192  this%hcof(i) = dzero
193  if (this%ibound(node) <= 0) then
194  this%rhs(i) = dzero
195  cycle
196  end if
197  !
198  ! -- set energy loading rate accounting for multiplier
199  q = this%ener_mult(i)
200  !
201  this%rhs(i) = -q
202  end do
203  end subroutine esl_cf
204 
205  !> @brief Add matrix terms related to specified energy source loading
206  !!
207  !! Copy rhs and hcof into solution rhs and amat
208  !<
209  subroutine esl_fc(this, rhs, ia, idxglo, matrix_sln)
210  ! -- dummy
211  class(gweesltype) :: this
212  real(DP), dimension(:), intent(inout) :: rhs
213  integer(I4B), dimension(:), intent(in) :: ia
214  integer(I4B), dimension(:), intent(in) :: idxglo
215  class(matrixbasetype), pointer :: matrix_sln
216  ! -- local
217  integer(I4B) :: i, n, ipos
218  !
219  ! -- pakmvrobj fc
220  if (this%imover == 1) then
221  call this%pakmvrobj%fc()
222  end if
223  !
224  ! -- Copy package rhs and hcof into solution rhs and amat
225  do i = 1, this%nbound
226  n = this%nodelist(i)
227  rhs(n) = rhs(n) + this%rhs(i)
228  ipos = ia(n)
229  call matrix_sln%add_value_pos(idxglo(ipos), this%hcof(i))
230  !
231  ! -- If mover is active and mass is being withdrawn,
232  ! store available mass (as positive value).
233  if (this%imover == 1 .and. this%rhs(i) > dzero) then
234  call this%pakmvrobj%accumulate_qformvr(i, this%rhs(i))
235  end if
236  end do
237  end subroutine esl_fc
238 
239  !> @brief Define list labels
240  !!
241  !! Define the list heading that is written to iout when
242  !! PRINT_INPUT option is used.
243  !<
244  subroutine define_listlabel(this)
245  ! -- dummy
246  class(gweesltype), intent(inout) :: this
247  !
248  ! -- Create the header list label
249  this%listlabel = trim(this%filtyp)//' NO.'
250  if (this%dis%ndim == 3) then
251  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'LAYER'
252  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'ROW'
253  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'COL'
254  elseif (this%dis%ndim == 2) then
255  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'LAYER'
256  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'CELL2D'
257  else
258  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'NODE'
259  end if
260  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'STRESS RATE'
261  if (this%inamedbound == 1) then
262  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'BOUNDARY NAME'
263  end if
264  end subroutine define_listlabel
265 
266  ! -- Procedures related to observations
267 
268  !> @brief Support function for specified energy source loading observations
269  !!
270  !! This function:
271  !! - returns true because ESL package supports observations.
272  !! - overrides BndType%bnd_obs_supported()
273  !<
274  logical function esl_obs_supported(this)
275  implicit none
276  ! -- dummy
277  class(gweesltype) :: this
278  !
279  esl_obs_supported = .true.
280  end function esl_obs_supported
281 
282  !> @brief Define observations
283  !!
284  !! This subroutine:
285  !! - stores observation types supported by ESL package.
286  !! - overrides BndType%bnd_df_obs
287  !<
288  subroutine esl_df_obs(this)
289  implicit none
290  ! -- dummy
291  class(gweesltype) :: this
292  ! -- local
293  integer(I4B) :: indx
294  !
295  call this%obs%StoreObsType('esl', .true., indx)
296  this%obs%obsData(indx)%ProcessIdPtr => defaultobsidprocessor
297  !
298  ! -- Store obs type and assign procedure pointer
299  ! for to-mvr observation type.
300  call this%obs%StoreObsType('to-mvr', .true., indx)
301  this%obs%obsData(indx)%ProcessIdPtr => defaultobsidprocessor
302  end subroutine esl_df_obs
303 
304  !> @ brief Return a bound value
305  !!
306  !! Return a bound value associated with an ncolbnd index
307  !! and row.
308  !<
309  function esl_bound_value(this, col, row) result(bndval)
310  ! -- modules
311  use constantsmodule, only: dzero
312  ! -- dummy variables
313  class(gweesltype), intent(inout) :: this
314  integer(I4B), intent(in) :: col
315  integer(I4B), intent(in) :: row
316  ! -- result
317  real(dp) :: bndval
318  !
319  select case (col)
320  case (1)
321  bndval = this%senerrate(row)
322  case default
323  end select
324  end function esl_bound_value
325 
326  !> @brief Return a value that applies a multiplier
327  !!
328  !! Apply multiplier to specified energy load depending on user-selected
329  !! option
330  !<
331  function ener_mult(this, row) result(ener)
332  ! -- modules
333  use constantsmodule, only: dzero
334  ! -- dummy variables
335  class(gweesltype), intent(inout) :: this !< BndExtType object
336  integer(I4B), intent(in) :: row
337  ! -- result
338  real(dp) :: ener
339  !
340  if (this%iauxmultcol > 0) then
341  ener = this%senerrate(row) * this%auxvar(this%iauxmultcol, row)
342  else
343  ener = this%senerrate(row)
344  end if
345  end function ener_mult
346 
347 end module gweeslmodule
This module contains the extended boundary package.
This module contains the base boundary package.
This module contains simulation constants.
Definition: Constants.f90:9
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
real(dp) function ener_mult(this, row)
Return a value that applies a multiplier.
Definition: gwe-esl.f90:332
subroutine, public esl_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, gwecommon, input_mempath)
Create an energy source loading package.
Definition: gwe-esl.f90:50
real(dp) function esl_bound_value(this, col, row)
@ brief Return a bound value
Definition: gwe-esl.f90:310
subroutine esl_da(this)
Deallocate memory.
Definition: gwe-esl.f90:95
subroutine esl_ck(this)
Check energy source loading boundary condition data.
Definition: gwe-esl.f90:146
subroutine esl_allocate_arrays(this, nodelist, auxvar)
Allocate arrays.
Definition: gwe-esl.f90:125
subroutine esl_cf(this)
Formulate the HCOF and RHS terms.
Definition: gwe-esl.f90:180
character(len=lenftype) ftype
Definition: gwe-esl.f90:17
subroutine define_listlabel(this)
Define list labels.
Definition: gwe-esl.f90:245
subroutine esl_df_obs(this)
Define observations.
Definition: gwe-esl.f90:289
subroutine esl_fc(this, rhs, ia, idxglo, matrix_sln)
Add matrix terms related to specified energy source loading.
Definition: gwe-esl.f90:210
logical function esl_obs_supported(this)
Support function for specified energy source loading observations.
Definition: gwe-esl.f90:275
character(len=16) text
Definition: gwe-esl.f90:18
subroutine esl_allocate_scalars(this)
Allocate scalars.
Definition: gwe-esl.f90:109
This module defines variable data types.
Definition: kind.f90:8
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_warning(msg, substring)
Store warning message.
Definition: Sim.f90:236
This module contains simulation variables.
Definition: SimVariables.f90:9
character(len=maxcharlen) warnmsg
warning message string
@ brief BndType
Data for sharing among multiple packages. Originally read in from.