MODFLOW 6  version 6.7.0.dev3
USGS Modular Hydrologic Model
GwfConductanceUtils.f90
Go to the documentation of this file.
1 !> @brief This module contains stateless conductance functions
2 !!
3 !! This module contains the functions to calculate the horizontal
4 !! and vertical conductance between two cells that are used in the
5 !! the node property flow (NPF) package. It also contains functions
6 !! to calculate the wetted cell fraction. This module does not
7 !! depend on the NPF package.
8 !!
9 !<
11  use kindmodule, only: dp, i4b
12  use constantsmodule, only: dzero, dhalf, done, &
13  dlnlow, dlnhigh, &
15 
16  implicit none
17  private
18  public :: hcond
19  public :: vcond
20  public :: condmean
21  public :: thksatnm
22  public :: staggered_thkfrac
23  public :: ccond_hmean
24 
25  !> @brief enumerator that defines the conductance options
26  !<
27  ENUM, BIND(C)
28  ENUMERATOR :: ccond_hmean = 0 !< Harmonic mean
29  ENUMERATOR :: ccond_lmean = 1 !< Logarithmic mean
30  ENUMERATOR :: ccond_amtlmk = 2 !< Arithmetic-mean thickness and logarithmic-mean hydraulic conductivity
31  ENUMERATOR :: ccond_amthmk = 3 !< Arithmetic-mean thickness and harmonic-mean hydraulic conductivity
32  END ENUM
33 
34 contains
35 
36  !> @brief Horizontal conductance between two cells
37  !!
38  !! This function uses a weighted transmissivity in the harmonic mean
39  !! conductance calculations. This differs from the MODFLOW-NWT and
40  !! MODFLOW-USG conductance calculations for the Newton-Raphson formulation
41  !! which use a weighted hydraulic conductivity.
42  !<
43  function hcond(ibdn, ibdm, ictn, ictm, iupstream, ihc, icellavg, &
44  condsat, hn, hm, satn, satm, hkn, hkm, topn, topm, &
45  botn, botm, cln, clm, fawidth) &
46  result(condnm)
47  ! return variable
48  real(dp) :: condnm !< horizontal conductance between two cells
49  ! dummy
50  integer(I4B), intent(in) :: ibdn !< cell n active flag
51  integer(I4B), intent(in) :: ibdm !< cell m active flag
52  integer(I4B), intent(in) :: ictn !< cell n convertible cell flag
53  integer(I4B), intent(in) :: ictm !< cell m convertible cell flag
54  integer(I4B), intent(in) :: iupstream !< flag for upstream weighting
55  integer(I4B), intent(in) :: ihc !< connection type
56  integer(I4B), intent(in) :: icellavg !< cell averaging option
57  real(dp), intent(in) :: condsat !< saturated conductance
58  real(dp), intent(in) :: hn !< cell n head
59  real(dp), intent(in) :: hm !< cell m head
60  real(dp), intent(in) :: satn !< cell n wetted cell fraction
61  real(dp), intent(in) :: satm !< cell m wetted cell fraction
62  real(dp), intent(in) :: hkn !< horizontal hydraulic conductivity for cell n (in the direction of cell m)
63  real(dp), intent(in) :: hkm !< horizontal hydraulic conductivity for cell m (in the direction of cell n)
64  real(dp), intent(in) :: topn !< top of cell n
65  real(dp), intent(in) :: topm !< top of cell m
66  real(dp), intent(in) :: botn !< bottom of cell n
67  real(dp), intent(in) :: botm !< bottom of cell m
68  real(dp), intent(in) :: cln !< distance from the center of cell n to the shared face with cell m
69  real(dp), intent(in) :: clm !< distance from the center of cell m to the shared face with cell n
70  real(dp), intent(in) :: fawidth !< width of cell perpendicular to flow
71 
72  ! n or m is inactive
73  if (ibdn == 0 .or. ibdm == 0) then
74  condnm = dzero
75  ! both cells are non-convertible
76  elseif (ictn == 0 .and. ictm == 0) then
77  condnm = condsat
78  else if (iupstream == 1) then
79  condnm = convertible_upstream(hn, hm, satn, satm, condsat)
80  else
81  condnm = convertible_standard(ihc, icellavg, &
82  satn, satm, hkn, hkm, &
83  topn, topm, botn, botm, &
84  cln, clm, fawidth)
85  end if
86  end function hcond
87 
88  !> @brief Convertible cell(s) with upstream weighted horizontal conductance
89  !<
90  function convertible_upstream(hn, hm, satn, satm, condsat) &
91  result(condnm)
92  ! return variable
93  real(dp) :: condnm !< horizontal conductance between two cells
94  ! dummy
95  real(dp), intent(in) :: condsat !< saturated conductance
96  real(dp), intent(in) :: hn !< cell n head
97  real(dp), intent(in) :: hm !< cell m head
98  real(dp), intent(in) :: satn !< cell n wetted cell fraction
99  real(dp), intent(in) :: satm !< cell m wetted cell fraction
100  ! local
101  real(dp) :: sat_up
102 
103  if (hn > hm) then
104  sat_up = satn
105  else
106  sat_up = satm
107  end if
108  condnm = sat_up * condsat
109  end function convertible_upstream
110 
111  !> @brief Convertible cell(s) with standard weighted horizontal conductance
112  !<
113  function convertible_standard(ihc, icellavg, satn, satm, hkn, hkm, &
114  topn, topm, botn, botm, cln, clm, fawidth) &
115  result(condnm)
116  ! return variable
117  real(dp) :: condnm !< horizontal conductance between two cells
118  ! dummy
119  integer(I4B), intent(in) :: ihc !< connection type
120  integer(I4B), intent(in) :: icellavg !< cell averaging option
121  real(dp), intent(in) :: satn !< cell n wetted cell fraction
122  real(dp), intent(in) :: satm !< cell m wetted cell fraction
123  real(dp), intent(in) :: hkn !< horizontal hydraulic conductivity for cell n (in the direction of cell m)
124  real(dp), intent(in) :: hkm !< horizontal hydraulic conductivity for cell m (in the direction of cell n)
125  real(dp), intent(in) :: topn !< top of cell n
126  real(dp), intent(in) :: topm !< top of cell m
127  real(dp), intent(in) :: botn !< bottom of cell n
128  real(dp), intent(in) :: botm !< bottom of cell m
129  real(dp), intent(in) :: cln !< distance from the center of cell n to the shared face with cell m
130  real(dp), intent(in) :: clm !< distance from the center of cell m to the shared face with cell n
131  real(dp), intent(in) :: fawidth !< width of cell perpendicular to flow
132  ! local
133  real(dp) :: thksatn
134  real(dp) :: thksatm
135 
136  if (ihc == c3d_staggered) then
137  thksatn = staggered_thkfrac(topn, botn, satn, topm, botm)
138  thksatm = staggered_thkfrac(topm, botm, satm, topn, botn)
139  else
140  thksatn = satn * (topn - botn)
141  thksatm = satm * (topm - botm)
142  end if
143  condnm = condmean(hkn, hkm, thksatn, thksatm, cln, clm, &
144  fawidth, icellavg)
145  end function convertible_standard
146 
147  !> @brief Vertical conductance between two cells
148  !<
149  function vcond(ibdn, ibdm, ictn, ictm, inewton, ivarcv, idewatcv, &
150  condsat, hn, hm, vkn, vkm, satn, satm, topn, topm, botn, &
151  botm, flowarea) result(condnm)
152  ! return variable
153  real(dp) :: condnm
154  ! dummy
155  integer(I4B), intent(in) :: ibdn !< cell n active flag
156  integer(I4B), intent(in) :: ibdm !< cell m active flag
157  integer(I4B), intent(in) :: ictn !< cell n convertible cell flag
158  integer(I4B), intent(in) :: ictm !< cell m convertible cell flag
159  integer(I4B), intent(in) :: inewton !< flag for Newton-Raphson formulation
160  integer(I4B), intent(in) :: ivarcv !< variable vertical conductance flag
161  integer(I4B), intent(in) :: idewatcv !< dewatered vertical conductance flag
162  real(dp), intent(in) :: condsat !< saturated conductance
163  real(dp), intent(in) :: hn !< cell n head
164  real(dp), intent(in) :: hm !< cell m head
165  real(dp), intent(in) :: vkn !< vertical hydraulic conductivity for cell n (in the direction of cell m)
166  real(dp), intent(in) :: vkm !< vertical hydraulic conductivity for cell m (in the direction of cell n)
167  real(dp), intent(in) :: satn !< cell n wetted cell fraction
168  real(dp), intent(in) :: satm !< cell m wetted cell fraction
169  real(dp), intent(in) :: topn !< top of cell n
170  real(dp), intent(in) :: topm !< top of cell m
171  real(dp), intent(in) :: botn !< bottom of cell n
172  real(dp), intent(in) :: botm !< bottom of cell m
173  real(dp), intent(in) :: flowarea !< flow area between cell n and m
174  ! local
175  real(dp) :: satntmp
176  real(dp) :: satmtmp
177  real(dp) :: bovk1
178  real(dp) :: bovk2
179  real(dp) :: denom
180  !
181  ! Either n or m is inactive
182  if (ibdn == 0 .or. ibdm == 0) then
183  condnm = dzero
184  !
185  ! constantcv
186  elseif (ivarcv == 0) then
187  condnm = condsat
188  !
189  ! both cells are non-convertible
190  elseif (ictn == 0 .and. ictm == 0) then
191  condnm = condsat
192  !
193  ! both cells are fully saturated
194  elseif (hn >= topn .and. hm >= topm) then
195  condnm = condsat
196  !
197  ! At least one cell is partially saturated, so recalculate vertical
198  ! conductance for this connection
199  ! todo: upstream weighting?
200  else
201  !
202  ! Default is for CV correction (dewatered option); use underlying
203  ! saturation of 1.
204  satntmp = satn
205  satmtmp = satm
206  if (idewatcv == 0) then
207  if (botn > botm) then
208  satmtmp = done
209  else
210  satntmp = done
211  end if
212  else
213  if (botn > botm) then
214  if (satmtmp < done) then
215  satmtmp = dzero
216  end if
217  else
218  if (satntmp < done) then
219  satntmp = dzero
220  end if
221  end if
222  end if
223  bovk1 = satntmp * (topn - botn) * dhalf / vkn
224  bovk2 = satmtmp * (topm - botm) * dhalf / vkm
225  denom = (bovk1 + bovk2)
226  if (denom /= dzero) then
227  condnm = flowarea / denom
228  else
229  condnm = dzero
230  end if
231  end if
232  end function vcond
233 
234  !> @brief Calculate the conductance between two cells
235  !<
236  function condmean(k1, k2, thick1, thick2, cl1, cl2, width, iavgmeth)
237  ! return variable
238  real(dp) :: condmean !< mean conductance between two cells
239  ! dummy
240  real(dp), intent(in) :: k1 !< hydraulic conductivity for cell n (in the direction of cell m)
241  real(dp), intent(in) :: k2 !< hydraulic conductivity for cell m (in the direction of celln)
242  real(dp), intent(in) :: thick1 !< saturated thickness for cell 1
243  real(dp), intent(in) :: thick2 !< saturated thickness for cell 2
244  real(dp), intent(in) :: cl1 !< distance from the center of cell n to the shared face with cell m
245  real(dp), intent(in) :: cl2 !< distance from the center of cell m to the shared face with cell n
246  real(dp), intent(in) :: width !< width of cell perpendicular to flow
247  integer(I4B), intent(in) :: iavgmeth !< averaging method
248  ! local
249  real(dp) :: t1
250  real(dp) :: t2
251  real(dp) :: tmean
252  real(dp) :: kmean
253  real(dp) :: denom
254  !
255  ! Initialize
256  t1 = k1 * thick1
257  t2 = k2 * thick2
258 
259  ! Averaging method
260  select case (iavgmeth)
261 
262  case (ccond_hmean)
263  if (t1 * t2 > dzero) then
264  condmean = width * t1 * t2 / (t1 * cl2 + t2 * cl1)
265  else
266  condmean = dzero
267  end if
268 
269  case (ccond_lmean)
270  if (t1 * t2 > dzero) then
271  tmean = logmean(t1, t2)
272  else
273  tmean = dzero
274  end if
275  condmean = tmean * width / (cl1 + cl2)
276 
277  case (ccond_amtlmk)
278  if (k1 * k2 > dzero) then
279  kmean = logmean(k1, k2)
280  else
281  kmean = dzero
282  end if
283  condmean = kmean * dhalf * (thick1 + thick2) * width / (cl1 + cl2)
284 
285  case (ccond_amthmk)
286  denom = (k1 * cl2 + k2 * cl1)
287  if (denom > dzero) then
288  kmean = k1 * k2 / denom
289  else
290  kmean = dzero
291  end if
292  condmean = kmean * dhalf * (thick1 + thick2) * width
293  end select
294  end function condmean
295 
296  !> @brief Calculate the the logarithmic mean of two double precision numbers
297  !!
298  !! Use an approximation if the ratio is near 1
299  !<
300  function logmean(d1, d2)
301  ! return variable
302  real(dp) :: logmean !< logarithmic mean for two number
303  ! dummy
304  real(dp), intent(in) :: d1 !< first number
305  real(dp), intent(in) :: d2 !< second number
306  ! local
307  real(dp) :: drat
308 
309  drat = d2 / d1
310  if (drat <= dlnlow .or. drat >= dlnhigh) then
311  logmean = (d2 - d1) / log(drat)
312  else
313  logmean = dhalf * (d1 + d2)
314  end if
315  end function logmean
316 
317  !> @brief Calculate wetted cell thickness at interface between two cells
318  !<
319  function thksatnm(ibdn, ibdm, ictn, ictm, iupstream, ihc, &
320  hn, hm, satn, satm, topn, topm, botn, botm) result(res)
321  ! return variable
322  real(dp) :: res !< wetted cell thickness for connection nm
323  ! dummy
324  integer(I4B), intent(in) :: ibdn !< cell n active flag
325  integer(I4B), intent(in) :: ibdm !< cell m active flag
326  integer(I4B), intent(in) :: ictn !< cell n convertible cell flag
327  integer(I4B), intent(in) :: ictm !< cell m convertible cell flag
328  integer(I4B), intent(in) :: iupstream !< flag for upstream weighting
329  integer(I4B), intent(in) :: ihc !< connection type
330  real(dp), intent(in) :: hn !< cell n head
331  real(dp), intent(in) :: hm !< cell m head
332  real(dp), intent(in) :: satn !< cell n wetted cell fraction
333  real(dp), intent(in) :: satm !< cell m wetted cell fraction
334  real(dp), intent(in) :: topn !< top of cell n
335  real(dp), intent(in) :: topm !< top of cell m
336  real(dp), intent(in) :: botn !< bottom of cell n
337  real(dp), intent(in) :: botm !< bottom of cell m
338  ! local
339  real(dp) :: thksatn
340  real(dp) :: thksatm
341  real(dp) :: sill_top
342  real(dp) :: sill_bot
343  !
344  ! n or m is inactive
345  if (ibdn == 0 .or. ibdm == 0) then
346  res = dzero
347  !
348  ! both cells are non-convertible
349  elseif (ictn == 0 .and. ictm == 0) then
350  if (ihc == c3d_staggered) then
351  sill_top = min(topn, topm)
352  sill_bot = max(botn, botm)
353 
354  thksatn = max(sill_top - sill_bot, dzero)
355  thksatm = thksatn
356  else
357  thksatn = topn - botn
358  thksatm = topm - botm
359  end if
360  res = dhalf * (thksatn + thksatm)
361  !
362  ! At least one of the cells is convertible
363  elseif (iupstream == 1) then
364  if (hn > hm) then
365  res = satn * (topn - botn)
366  else
367  res = satm * (topm - botm)
368  end if
369  !
370  ! At least one of the cells is convertible and not upstream weighted
371  else
372  if (ihc == c3d_staggered) then
373  thksatn = staggered_thkfrac(topn, botn, satn, topm, botm)
374  thksatm = staggered_thkfrac(topm, botm, satm, topn, botn)
375  else
376  thksatn = satn * (topn - botn)
377  thksatm = satm * (topm - botm)
378  end if
379  res = dhalf * (thksatn + thksatm)
380  end if
381  end function thksatnm
382 
383  !> @brief Calculate the thickness fraction for staggered grids
384  !<
385  function staggered_thkfrac(top, bot, sat, topc, botc) result(res)
386  ! return variable
387  real(dp) :: res !< staggered thickness fraction for cell
388  ! dummy
389  real(dp) :: top !< top of cell
390  real(dp) :: bot !< bottom of cell
391  real(dp) :: sat !< cell saturation
392  real(dp) :: topc !< top of connected cell
393  real(dp) :: botc !< bottom of connected cells
394  ! local
395  real(dp) :: sill_top
396  real(dp) :: sill_bot
397  real(dp) :: tp
398 
399  sill_top = min(top, topc)
400  sill_bot = max(bot, botc)
401  tp = bot + sat * (top - bot)
402  res = max(min(tp, sill_top) - sill_bot, dzero)
403  end function staggered_thkfrac
404 
405 end module gwfconductanceutilsmodule
This module contains simulation constants.
Definition: Constants.f90:9
@ c3d_staggered
horizontal connection for a vertically staggered grid
Definition: Constants.f90:224
real(dp), parameter dlnlow
real constant low ratio used to calculate log mean of K
Definition: Constants.f90:125
real(dp), parameter dhalf
real constant 1/2
Definition: Constants.f90:68
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
real(dp), parameter dlnhigh
real constant high ratio used to calculate log mean of K
Definition: Constants.f90:126
real(dp), parameter done
real constant 1
Definition: Constants.f90:76
This module contains stateless conductance functions.
real(dp) function, public thksatnm(ibdn, ibdm, ictn, ictm, iupstream, ihc, hn, hm, satn, satm, topn, topm, botn, botm)
Calculate wetted cell thickness at interface between two cells.
real(dp) function convertible_upstream(hn, hm, satn, satm, condsat)
Convertible cell(s) with upstream weighted horizontal conductance.
real(dp) function logmean(d1, d2)
Calculate the the logarithmic mean of two double precision numbers.
@ ccond_amthmk
Arithmetic-mean thickness and harmonic-mean hydraulic conductivity.
@ ccond_amtlmk
Arithmetic-mean thickness and logarithmic-mean hydraulic conductivity.
real(dp) function convertible_standard(ihc, icellavg, satn, satm, hkn, hkm, topn, topm, botn, botm, cln, clm, fawidth)
Convertible cell(s) with standard weighted horizontal conductance.
real(dp) function, public condmean(k1, k2, thick1, thick2, cl1, cl2, width, iavgmeth)
Calculate the conductance between two cells.
real(dp) function, public hcond(ibdn, ibdm, ictn, ictm, iupstream, ihc, icellavg, condsat, hn, hm, satn, satm, hkn, hkm, topn, topm, botn, botm, cln, clm, fawidth)
Horizontal conductance between two cells.
real(dp) function, public staggered_thkfrac(top, bot, sat, topc, botc)
Calculate the thickness fraction for staggered grids.
@, public ccond_hmean
Harmonic mean.
real(dp) function, public vcond(ibdn, ibdm, ictn, ictm, inewton, ivarcv, idewatcv, condsat, hn, hm, vkn, vkm, satn, satm, topn, topm, botn, botm, flowarea)
Vertical conductance between two cells.
This module defines variable data types.
Definition: kind.f90:8