MODFLOW 6  version 6.7.0.dev3
USGS Modular Hydrologic Model
utvdschememodule Module Reference

Data Types

interface  utvdschemetype
 Total Variation Diminishing (TVD) interpolation scheme. More...
 

Functions/Subroutines

type(utvdschemetype) function constructor (dis, fmi, gradient)
 
subroutine destructor (this)
 
subroutine set_field (this, phi)
 Set the scalar field for which interpolation will be computed. More...
 
type(coefficientstype) function, target compute (this, n, m, iposnm)
 
real(dp) function limiter (this, r)
 
subroutine compute_node_distance (this)
 

Function/Subroutine Documentation

◆ compute()

type(coefficientstype) function, target utvdschememodule::compute ( class(utvdschemetype), target  this,
integer(i4b), intent(in)  n,
integer(i4b), intent(in)  m,
integer(i4b), intent(in)  iposnm 
)
private

Definition at line 106 of file UTVDScheme.f90.

107  !-- return
108  type(CoefficientsType), target :: phi_face ! Output: coefficients for the face between cells n and m
109  ! -- dummy
110  class(UTVDSchemeType), target :: this
111  integer(I4B), intent(in) :: n ! Index of the first cell
112  integer(I4B), intent(in) :: m ! Index of the second cell
113  integer(I4B), intent(in) :: iposnm ! Position in the connectivity array for the n-m connection
114  ! -- local
115  integer(I4B) :: iup, idn, isympos ! Indices for upwind, downwind, and symmetric position in connectivity
116  real(DP) :: qnm ! Flow rate across the face between n and m
117  real(DP), pointer :: coef_up, coef_dn ! Pointers to upwind and downwind coefficients in phi_face
118  real(DP), dimension(3) :: grad_c ! gradient at upwind cell
119  real(DP), dimension(3) :: dnm ! vector from upwind to downwind cell
120  real(DP) :: smooth ! Smoothness indicator for limiter i.e. ratio of gradients
121  real(DP) :: alimiter ! Value of the TVD limiter
122  real(DP) :: cl1, cl2 ! Connection lengths from upwind and downwind cells to the face
123  real(DP) :: relative_distance ! Relative distance factor for high-order term
124  real(DP) :: c_virtual ! Virtual node concentration (Darwish method)
125  real(DP), pointer :: min_phi, max_phi ! Local minimum and maximum among cell and neighbors
126 
127  isympos = this%dis%con%jas(iposnm)
128  qnm = this%fmi%gwfflowja(iposnm)
129  !
130  ! -- Find upstream node
131  if (qnm > dzero) then
132  ! -- positive flow into n means m is upstream
133  iup = m
134  idn = n
135 
136  cl1 = this%dis%con%cl2(isympos)
137  cl2 = this%dis%con%cl1(isympos)
138 
139  coef_up => phi_face%c_m
140  coef_dn => phi_face%c_n
141  else
142  iup = n
143  idn = m
144 
145  cl1 = this%dis%con%cl1(isympos)
146  cl2 = this%dis%con%cl2(isympos)
147 
148  coef_up => phi_face%c_n
149  coef_dn => phi_face%c_m
150  end if
151  !
152  ! Determine direction of distance vector from upwind to downwind cell
153  ! The cached_node_distance always stores vector from lower-numbered node to higher-numbered node.
154  ! Since we need dnm to point from upwind (iup) to downwind (idn), we must adjust the sign:
155  ! - If iup > idn: the cached vector points from idn to iup, so we negate it to get iup to idn
156  ! - If iup < idn: the cached vector already points from iup to idn, so use it as-is
157  if (iup > idn) then
158  dnm = -this%cached_node_distance(isympos, :)
159  else
160  dnm = this%cached_node_distance(isympos, :)
161  end if
162  !
163  ! -- Add low order terms
164  coef_up = done
165  !
166  ! -- Add high order terms
167  !
168  ! -- Return if straddled cells have same value
169  if (abs(this%phi(idn) - this%phi(iup)) < dsame) return
170  !
171  ! -- Compute cell concentration gradient
172  grad_c = this%gradient%get(iup)
173  !
174  ! Darwish's method to compute virtual node concentration
175  c_virtual = this%phi(idn) - 2.0_dp * (dot_product(grad_c, dnm))
176  !
177  ! Enforce local TVD condition.
178  ! This is done by limiting the virtual concentration to the range of
179  ! the max and min concentration of the neighbouring cells.
180  min_phi => this%min_max_phi%get_min(iup)
181  max_phi => this%min_max_phi%get_max(iup)
182 
183  if (c_virtual > max_phi) then
184  c_virtual = max_phi
185  end if
186 
187  if (c_virtual < max(min_phi, dzero)) then
188  c_virtual = max(min_phi, dzero)
189  end if
190  !
191  ! -- Compute smoothness factor
192  smooth = (this%phi(iup) - c_virtual) / (this%phi(idn) - this%phi(iup))
193  !
194  ! -- Compute limiter
195  alimiter = this%limiter(smooth)
196 
197  ! High order term is:
198  relative_distance = cl1 / (cl1 + cl2)
199  phi_face%rhs = -relative_distance * alimiter * (this%phi(idn) - this%phi(iup))
200 
201  ! Alternative way of writing the high order term by adding it to the
202  ! coefficients matrix. The equation to be added is:
203  ! high_order = cl1 / (cl1 + cl2) * alimiter * qnm * (phi(idn) - phi(iup))
204  ! This is split into two parts:
205  ! coef_up = coef_up - relative_distance * alimiter
206  ! coef_dn = coef_dn + relative_distance * alimiter
207 

◆ compute_node_distance()

subroutine utvdschememodule::compute_node_distance ( class(utvdschemetype), target  this)
private

Definition at line 235 of file UTVDScheme.f90.

236  ! -- dummy
237  class(UTVDSchemeType), target :: this
238  ! -- local
239  integer(I4B) :: n, m, ipos, isympos
240 
241  this%cached_node_distance = 0.0_dp
242  do n = 1, this%dis%nodes
243  do ipos = this%dis%con%ia(n) + 1, this%dis%con%ia(n + 1) - 1
244  m = this%dis%con%ja(ipos)
245  if (m <= n) cycle
246 
247  isympos = this%dis%con%jas(ipos)
248  this%cached_node_distance(isympos, :) = node_distance(this%dis, n, m)
249  end do
250  end do
251 
Here is the call graph for this function:
Here is the caller graph for this function:

◆ constructor()

type(utvdschemetype) function utvdschememodule::constructor ( class(disbasetype), intent(in), pointer  dis,
type(tspfmitype), intent(in), pointer  fmi,
class(igradienttype), intent(in), allocatable, target  gradient 
)
private

Definition at line 62 of file UTVDScheme.f90.

64  ! -- return
65  type(UTVDSchemeType) :: interpolation_scheme
66  ! -- dummy
67  class(DisBaseType), pointer, intent(in) :: dis
68  type(TspFmiType), pointer, intent(in) :: fmi
69  class(IGradientType), allocatable, intent(in), target :: gradient
70 
71  interpolation_scheme%dis => dis
72  interpolation_scheme%fmi => fmi
73 
74  interpolation_scheme%gradient => gradient
75  interpolation_scheme%min_max_phi = localcellextrematype(dis)
76 
77  allocate (interpolation_scheme%cached_node_distance(dis%njas, 3))
78  call compute_node_distance(interpolation_scheme)
79 
Here is the caller graph for this function:

◆ destructor()

subroutine utvdschememodule::destructor ( type(utvdschemetype), intent(inout)  this)
private

Definition at line 82 of file UTVDScheme.f90.

83  ! -- dummy
84  type(UTVDSchemeType), intent(inout) :: this
85 
86  deallocate (this%cached_node_distance)
Here is the caller graph for this function:

◆ limiter()

real(dp) function utvdschememodule::limiter ( class(utvdschemetype this,
real(dp)  r 
)
private

Definition at line 210 of file UTVDScheme.f90.

211  ! -- return
212  real(DP) :: theta ! limited slope
213  ! -- dummy
214  class(UTVDSchemeType) :: this
215  real(DP) :: r ! ratio of successive gradients
216 
217  select case (this%limiter_id)
218  case (2) ! van Leer
219  theta = max(0.0_dp, min((r + dabs(r)) / (1.0_dp + dabs(r)), 2.0_dp))
220  case (3) ! Koren
221  theta = max(0.0_dp, min(2.0_dp * r, &
222  1.0_dp / 3.0_dp + 2.0_dp / 3.0_dp * r, 2.0_dp))
223  case (4) ! Superbee
224  theta = max(0.0_dp, min(2.0_dp * r, 1.0_dp), min(r, 2.0_dp))
225  case (5) ! van Albada
226  theta = max(0.0_dp, (r * r + r) / (r * r + 1.0_dp))
227  case (6) ! Koren modified
228  theta = max(0.0_dp, min(4.0_dp * r * r + r, &
229  1.0_dp / 3.0_dp + 2.0_dp / 3.0_dp * r, 2.0_dp))
230  case default
231  theta = dzero
232  end select

◆ set_field()

subroutine utvdschememodule::set_field ( class(utvdschemetype), target  this,
real(dp), dimension(:), intent(in), pointer  phi 
)
private

This method establishes a pointer to the scalar field data and updates any dependent cached data (gradients and local extrema) to ensure subsequent interpolation computations use the current field values.

Definition at line 96 of file UTVDScheme.f90.

97  ! -- dummy
98  class(UTVDSchemeType), target :: this
99  real(DP), intent(in), dimension(:), pointer :: phi
100 
101  this%phi => phi
102  call this%gradient%set_field(phi)
103  call this%min_max_phi%set_field(phi)