MODFLOW 6  version 6.7.0.dev2
USGS Modular Hydrologic Model
gweeslmodule Module Reference

Data Types

type  gweesltype
 

Functions/Subroutines

subroutine, public esl_create (packobj, id, ibcnum, inunit, iout, namemodel, pakname, gwecommon, input_mempath)
 Create an energy source loading package. More...
 
subroutine esl_da (this)
 Deallocate memory. More...
 
subroutine esl_allocate_scalars (this)
 Allocate scalars. More...
 
subroutine esl_allocate_arrays (this, nodelist, auxvar)
 Allocate arrays. More...
 
subroutine esl_cf (this)
 Formulate the HCOF and RHS terms. More...
 
subroutine esl_fc (this, rhs, ia, idxglo, matrix_sln)
 Add matrix terms related to specified energy source loading. More...
 
subroutine define_listlabel (this)
 Define list labels. More...
 
logical function esl_obs_supported (this)
 Support function for specified energy source loading observations. More...
 
subroutine esl_df_obs (this)
 Define observations. More...
 
real(dp) function esl_bound_value (this, col, row)
 @ brief Return a bound value More...
 

Variables

character(len=lenftype) ftype = 'ESL'
 
character(len=16) text = ' ESL'
 

Function/Subroutine Documentation

◆ define_listlabel()

subroutine gweeslmodule::define_listlabel ( class(gweesltype), intent(inout)  this)
private

Define the list heading that is written to iout when PRINT_INPUT option is used.

Definition at line 207 of file gwe-esl.f90.

208  ! -- dummy
209  class(GweEslType), intent(inout) :: this
210  !
211  ! -- Create the header list label
212  this%listlabel = trim(this%filtyp)//' NO.'
213  if (this%dis%ndim == 3) then
214  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'LAYER'
215  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'ROW'
216  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'COL'
217  elseif (this%dis%ndim == 2) then
218  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'LAYER'
219  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'CELL2D'
220  else
221  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'NODE'
222  end if
223  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'STRESS RATE'
224  if (this%inamedbound == 1) then
225  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'BOUNDARY NAME'
226  end if

◆ esl_allocate_arrays()

subroutine gweeslmodule::esl_allocate_arrays ( class(gweesltype this,
integer(i4b), dimension(:), optional, pointer, contiguous  nodelist,
real(dp), dimension(:, :), optional, pointer, contiguous  auxvar 
)
Parameters
nodelistpackage nodelist
auxvarpackage aux variable array

Definition at line 120 of file gwe-esl.f90.

122  ! -- dummy
123  class(GweEslType) :: this
124  ! -- local
125  integer(I4B), dimension(:), pointer, contiguous, optional :: nodelist !< package nodelist
126  real(DP), dimension(:, :), pointer, contiguous, optional :: auxvar !< package aux variable array
127 
128  ! -- base class allocate arrays
129  call this%BndExtType%allocate_arrays(nodelist, auxvar)
130 
131  ! -- set input context pointers
132  call mem_setptr(this%senerrate, 'SENERRATE', this%input_mempath)
133  !
134  ! -- checkin input context pointers
135  call mem_checkin(this%senerrate, 'SENERRATE', this%memoryPath, &
136  'SENERRATE', this%input_mempath)

◆ esl_allocate_scalars()

subroutine gweeslmodule::esl_allocate_scalars ( class(gweesltype this)

Allocate scalars specific to this energy source loading package

Definition at line 104 of file gwe-esl.f90.

105  ! -- modules
107  ! -- dummy
108  class(GweEslType) :: this
109  !
110  ! -- base class allocate scalars
111  call this%BndExtType%allocate_scalars()
112  !
113  ! -- allocate the object and assign values to object variables
114  !
115  ! -- Set values

◆ esl_bound_value()

real(dp) function gweeslmodule::esl_bound_value ( class(gweesltype), intent(inout)  this,
integer(i4b), intent(in)  col,
integer(i4b), intent(in)  row 
)
private

Return a bound value associated with an ncolbnd index and row.

Definition at line 272 of file gwe-esl.f90.

273  ! -- modules
274  use constantsmodule, only: dzero
275  ! -- dummy variables
276  class(GweEslType), intent(inout) :: this
277  integer(I4B), intent(in) :: col
278  integer(I4B), intent(in) :: row
279  ! -- result
280  real(DP) :: bndval
281  !
282  select case (col)
283  case (1)
284  bndval = this%senerrate(row)
285  case default
286  end select
This module contains simulation constants.
Definition: Constants.f90:9
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65

◆ esl_cf()

subroutine gweeslmodule::esl_cf ( class(gweesltype this)

This subroutine:

  • calculates hcof and rhs terms
  • skip if no sources

Definition at line 145 of file gwe-esl.f90.

146  ! -- dummy
147  class(GweEslType) :: this
148  ! -- local
149  integer(I4B) :: i, node
150  real(DP) :: q
151  !
152  ! -- Return if no sources
153  if (this%nbound == 0) return
154  !
155  ! -- Calculate hcof and rhs for each source entry
156  do i = 1, this%nbound
157  node = this%nodelist(i)
158  this%hcof(i) = dzero
159  if (this%ibound(node) <= 0) then
160  this%rhs(i) = dzero
161  cycle
162  end if
163  q = this%bound_value(1, i)
164  this%rhs(i) = -q
165  end do

◆ esl_create()

subroutine, public gweeslmodule::esl_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,
type(gweinputdatatype), intent(in), target  gwecommon,
character(len=*), intent(in)  input_mempath 
)

This subroutine points bndobj to the newly created package

Parameters
[in]gwecommonshared data container for use by multiple GWE packages

Definition at line 44 of file gwe-esl.f90.

46  ! -- modules
47  use bndmodule, only: bndtype
48  ! -- dummy
49  class(BndType), pointer :: packobj
50  integer(I4B), intent(in) :: id
51  integer(I4B), intent(in) :: ibcnum
52  integer(I4B), intent(in) :: inunit
53  integer(I4B), intent(in) :: iout
54  character(len=*), intent(in) :: namemodel
55  character(len=*), intent(in) :: pakname
56  type(GweInputDataType), intent(in), target :: gwecommon !< shared data container for use by multiple GWE packages
57  character(len=*), intent(in) :: input_mempath
58  ! -- local
59  type(GweEslType), pointer :: eslobj
60  !
61  ! -- Allocate the object and assign values to object variables
62  allocate (eslobj)
63  packobj => eslobj
64  !
65  ! -- Create name and memory path
66  call packobj%set_names(ibcnum, namemodel, pakname, ftype, input_mempath)
67  packobj%text = text
68  !
69  ! -- Allocate scalars
70  call eslobj%allocate_scalars()
71  !
72  ! -- Initialize package
73  call packobj%pack_initialize()
74  !
75  packobj%inunit = inunit
76  packobj%iout = iout
77  packobj%id = id
78  packobj%ibcnum = ibcnum
79  packobj%ncolbnd = 1
80  packobj%iscloc = 1
81  !
82  ! -- Store pointer to shared data module for accessing cpw, rhow
83  ! for the budget calculations, and for accessing the latent heat of
84  ! vaporization for evaporative cooling.
85  eslobj%gwecommon => gwecommon
This module contains the base boundary package.
@ brief BndType
Here is the caller graph for this function:

◆ esl_da()

subroutine gweeslmodule::esl_da ( class(gweesltype this)

Definition at line 90 of file gwe-esl.f90.

91  ! -- modules
93  ! -- dummy
94  class(GweEslType) :: this
95  !
96  ! -- Deallocate parent package
97  call this%BndExtType%bnd_da()

◆ esl_df_obs()

subroutine gweeslmodule::esl_df_obs ( class(gweesltype this)
private

This subroutine:

  • stores observation types supported by ESL package.
  • overrides BndTypebnd_df_obs

Definition at line 251 of file gwe-esl.f90.

252  implicit none
253  ! -- dummy
254  class(GweEslType) :: this
255  ! -- local
256  integer(I4B) :: indx
257  !
258  call this%obs%StoreObsType('esl', .true., indx)
259  this%obs%obsData(indx)%ProcessIdPtr => defaultobsidprocessor
260  !
261  ! -- Store obs type and assign procedure pointer
262  ! for to-mvr observation type.
263  call this%obs%StoreObsType('to-mvr', .true., indx)
264  this%obs%obsData(indx)%ProcessIdPtr => defaultobsidprocessor
Here is the call graph for this function:

◆ esl_fc()

subroutine gweeslmodule::esl_fc ( class(gweesltype 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

Copy rhs and hcof into solution rhs and amat

Definition at line 172 of file gwe-esl.f90.

173  ! -- dummy
174  class(GweEslType) :: this
175  real(DP), dimension(:), intent(inout) :: rhs
176  integer(I4B), dimension(:), intent(in) :: ia
177  integer(I4B), dimension(:), intent(in) :: idxglo
178  class(MatrixBaseType), pointer :: matrix_sln
179  ! -- local
180  integer(I4B) :: i, n, ipos
181  !
182  ! -- pakmvrobj fc
183  if (this%imover == 1) then
184  call this%pakmvrobj%fc()
185  end if
186  !
187  ! -- Copy package rhs and hcof into solution rhs and amat
188  do i = 1, this%nbound
189  n = this%nodelist(i)
190  rhs(n) = rhs(n) + this%rhs(i)
191  ipos = ia(n)
192  call matrix_sln%add_value_pos(idxglo(ipos), this%hcof(i))
193  !
194  ! -- If mover is active and mass is being withdrawn,
195  ! store available mass (as positive value).
196  if (this%imover == 1 .and. this%rhs(i) > dzero) then
197  call this%pakmvrobj%accumulate_qformvr(i, this%rhs(i))
198  end if
199  end do

◆ esl_obs_supported()

logical function gweeslmodule::esl_obs_supported ( class(gweesltype this)
private

This function:

  • returns true because ESL package supports observations.
  • overrides BndTypebnd_obs_supported()

Definition at line 237 of file gwe-esl.f90.

238  implicit none
239  ! -- dummy
240  class(GweEslType) :: this
241  !
242  esl_obs_supported = .true.

Variable Documentation

◆ ftype

character(len=lenftype) gweeslmodule::ftype = 'ESL'
private

Definition at line 15 of file gwe-esl.f90.

15  character(len=LENFTYPE) :: ftype = 'ESL'

◆ text

character(len=16) gweeslmodule::text = ' ESL'
private

Definition at line 16 of file gwe-esl.f90.

16  character(len=16) :: text = ' ESL'