MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
GwfStorageUtils.f90
Go to the documentation of this file.
1 !> @brief This module contains stateless storage subroutines and functions
2 !!
3 !! This module contains the functions to calculate the specific
4 !! storage (SC1) and specific yield (SC2) capacities that are used in
5 !! the storage (STO) package. It also contains subroutines to calculate
6 !! the amat and rhs terms for specific storage and specific yield.
7 !! This module does not depend on the STO package.
8 !!
9 !<
11 
12  use kindmodule, only: dp, i4b
13  use constantsmodule, only: dzero, dhalf, done
14 
15  implicit none
16  private
17  public :: ssterms
18  public :: syterms
19  public :: sscapacity
20  public :: sycapacity
21 
22 contains
23 
24  !> @brief Calculate the specific storage terms
25  !!
26  !! Subroutine to calculate the specific storage terms for a cell using
27  !! the cell geometry, current and previous specific storage capacity,
28  !! current and previous cell saturation, and the current and previous head.
29  !! Subroutine can optionally return the flow rate from specific storage.
30  !!
31  !<
32  pure subroutine ssterms(iconvert, iorig_ss, iconf_ss, top, bot, &
33  rho1, rho1old, snnew, snold, hnew, hold, &
34  aterm, rhsterm, rate)
35  ! -- dummy variables
36  integer(I4B), intent(in) :: iconvert !< flag indicating if cell is convertible
37  integer(I4B), intent(in) :: iorig_ss !< flag indicating if the original MODFLOW 6 specific storage formulation is being used
38  integer(I4B), intent(in) :: iconf_ss !< flag indicating if specific storage only applies under confined conditions
39  real(dp), intent(in) :: top !< top of cell
40  real(dp), intent(in) :: bot !< bottom of cell
41  real(dp), intent(in) :: rho1 !< current specific storage capacity
42  real(dp), intent(in) :: rho1old !< previous specific storage capacity
43  real(dp), intent(in) :: snnew !< current cell saturation
44  real(dp), intent(in) :: snold !< previous cell saturation
45  real(dp), intent(in) :: hnew !< current head
46  real(dp), intent(in) :: hold !< previous head
47  real(dp), intent(inout) :: aterm !< coefficient matrix term
48  real(dp), intent(inout) :: rhsterm !< right-hand side term
49  real(dp), intent(inout), optional :: rate !< calculated specific storage rate
50  ! -- local variables
51  real(dp) :: tthk
52  real(dp) :: zold
53  real(dp) :: znew
54  !
55  ! -- initialize terms
56  aterm = -rho1 * snnew
57  rhsterm = dzero
58  !
59  ! -- calculate specific storage terms
60  if (iconvert /= 0) then
61  if (iorig_ss == 0) then
62  if (iconf_ss == 0) then
63  tthk = top - bot
64  zold = bot + dhalf * tthk * snold
65  znew = bot + dhalf * tthk * snnew
66  rhsterm = -rho1old * snold * (hold - zold) - rho1 * snnew * znew
67  else
68  if (snold == done) then
69  rhsterm = rhsterm - rho1old * (hold - top)
70  end if
71  if (snnew == done) then
72  rhsterm = rhsterm - rho1 * top
73  else
74  aterm = dzero
75  end if
76  end if
77  else
78  rhsterm = -rho1old * snold * hold
79  end if
80  else
81  rhsterm = -rho1old * snold * hold
82  end if
83  !
84  ! -- calculate rate
85  if (present(rate)) then
86  rate = aterm * hnew - rhsterm
87  end if
88  !
89  ! -- return
90  return
91  end subroutine ssterms
92 
93  !> @brief Calculate the specific yield storage terms
94  !!
95  !! Subroutine to calculate the specific yield storage terms for a cell
96  !! using the cell geometry, current and previous specific yield storage
97  !! capacity, and the current and previous cell saturation. Subroutine
98  !! can optionally return the flow rate from specific yield.
99  !!
100  !<
101  pure subroutine syterms(top, bot, rho2, rho2old, snnew, snold, &
102  aterm, rhsterm, rate)
103  ! -- dummy variables
104  real(dp), intent(in) :: top !< top of cell
105  real(dp), intent(in) :: bot !< bottom of cell
106  real(dp), intent(in) :: rho2 !< current specific yield storage capacity
107  real(dp), intent(in) :: rho2old !< previous specific yield storage capacity
108  real(dp), intent(in) :: snnew !< current cell saturation
109  real(dp), intent(in) :: snold !< previous cell saturation
110  real(dp), intent(inout) :: aterm !< coefficient matrix term
111  real(dp), intent(inout) :: rhsterm !< right-hand side term
112  real(dp), intent(inout), optional :: rate !< calculated specific yield rate
113  ! -- local variables
114  real(dp) :: tthk
115  !
116  ! -- initialize terms
117  aterm = dzero
118  tthk = top - bot
119  !
120  ! -- calculate specific yield storage terms
121  if (snnew < done) then
122  if (snnew > dzero) then
123  aterm = -rho2
124  rhsterm = -rho2old * tthk * snold - rho2 * bot
125  else
126  rhsterm = tthk * (dzero - rho2old * snold)
127  end if
128  ! -- known flow from specific yield
129  else
130  rhsterm = tthk * (rho2 * snnew - rho2old * snold)
131  end if
132  !
133  ! -- calculate rate
134  if (present(rate)) then
135  rate = rho2old * tthk * snold - rho2 * tthk * snnew
136  end if
137  !
138  ! -- return
139  return
140  end subroutine syterms
141 
142  !> @brief Calculate the specific storage capacity
143  !!
144  !! Function to calculate the specific storage capacity using
145  !! the cell geometry and the specific storage or storage coefficient.
146  !!
147  !! @return sc1 specific storage capacity
148  !<
149  pure function sscapacity(istor_coef, top, bot, area, ss) result(sc1)
150  ! -- dummy variables
151  integer(I4B), intent(in) :: istor_coef !< flag indicating if ss is the storage coefficient
152  real(dp), intent(in) :: top !< top of cell
153  real(dp), intent(in) :: bot !< bottom of cell
154  real(dp), intent(in) :: area !< horizontal cell area
155  real(dp), intent(in) :: ss !< specific storage or storage coefficient
156  ! -- local variables
157  real(dp) :: sc1
158  real(dp) :: thick
159  ! -- calculate specific storage capacity
160  if (istor_coef == 0) then
161  thick = top - bot
162  else
163  thick = done
164  end if
165  sc1 = ss * thick * area
166  !
167  ! -- return
168  return
169  end function sscapacity
170 
171  !> @brief Calculate the specific yield capacity
172  !!
173  !! Function to calculate the specific yield capacity using
174  !! the cell area and the specific yield.
175  !!
176  !! @return sc2 specific yield capacity
177  !<
178  pure function sycapacity(area, sy) result(sc2)
179  ! -- dummy variables
180  real(dp), intent(in) :: area !< horizontal cell area
181  real(dp), intent(in) :: sy !< specific yield
182  ! -- local variables
183  real(dp) :: sc2
184  ! -- calculate specific yield capacity
185  sc2 = sy * area
186  !
187  ! -- return
188  return
189  end function sycapacity
190 
191 end module gwfstorageutilsmodule
This module contains simulation constants.
Definition: Constants.f90:9
real(dp), parameter dhalf
real constant 1/2
Definition: Constants.f90:67
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:64
real(dp), parameter done
real constant 1
Definition: Constants.f90:75
This module contains stateless storage subroutines and functions.
pure real(dp) function, public sycapacity(area, sy)
Calculate the specific yield capacity.
pure subroutine, public syterms(top, bot, rho2, rho2old, snnew, snold, aterm, rhsterm, rate)
Calculate the specific yield storage terms.
pure subroutine, public ssterms(iconvert, iorig_ss, iconf_ss, top, bot, rho1, rho1old, snnew, snold, hnew, hold, aterm, rhsterm, rate)
Calculate the specific storage terms.
pure real(dp) function, public sscapacity(istor_coef, top, bot, area, ss)
Calculate the specific storage capacity.
This module defines variable data types.
Definition: kind.f90:8