MODFLOW 6  version 6.7.0.dev2
USGS Modular Hydrologic Model
tsp-adv.f90
Go to the documentation of this file.
2 
3  use kindmodule, only: dp, i4b
6  use basedismodule, only: disbasetype
7  use tspfmimodule, only: tspfmitype
10  ! -- Gradient schemes
11  use igradient, only: igradienttype
13  ! -- Interpolation schemes
21 
22  implicit none
23  private
24  public :: tspadvtype
25  public :: adv_cr
26 
27  type, extends(numericalpackagetype) :: tspadvtype
28  integer(I4B), pointer :: iadvwt => null() !< advection scheme. See ADV_SCHEME_* constants
29  real(dp), pointer :: ats_percel => null() !< user-specified fractional number of cells advection can move a particle during one time step
30  integer(I4B), dimension(:), pointer, contiguous :: ibound => null() !< pointer to model ibound
31  type(tspfmitype), pointer :: fmi => null() !< pointer to fmi object
32  real(dp), pointer :: eqnsclfac => null() !< governing equation scale factor; =1. for solute; =rhow*cpw for energy
33 
34  class(interpolationschemeinterface), allocatable :: face_interpolation !< interpolation scheme for face values
35  class(igradienttype), allocatable :: gradient !< cell centered gradient
36  contains
37 
38  procedure :: adv_df
39  procedure :: adv_ar
40  procedure :: adv_dt
41  procedure :: adv_fc
42  procedure :: adv_cq
43  procedure :: adv_da
44 
45  procedure :: allocate_scalars
46  procedure, private :: source_options
47 
48  end type tspadvtype
49 
50 contains
51 
52  !> @ brief Create a new ADV object
53  !!
54  !! Create a new ADV package
55  !<
56  subroutine adv_cr(advobj, name_model, input_mempath, inunit, iout, fmi, &
57  eqnsclfac)
58  ! -- dummy
59  type(tspadvtype), pointer :: advobj
60  character(len=*), intent(in) :: name_model
61  character(len=*), intent(in) :: input_mempath
62  integer(I4B), intent(in) :: inunit
63  integer(I4B), intent(in) :: iout
64  type(tspfmitype), intent(in), target :: fmi
65  real(dp), intent(in), pointer :: eqnsclfac !< governing equation scale factor
66  !
67  ! -- Create the object
68  allocate (advobj)
69  !
70  ! -- create name and memory path
71  call advobj%set_names(1, name_model, 'ADV', 'ADV', input_mempath)
72  !
73  ! -- Allocate scalars
74  call advobj%allocate_scalars()
75  !
76  ! -- Set variables
77  advobj%inunit = inunit
78  advobj%iout = iout
79  advobj%fmi => fmi
80  advobj%eqnsclfac => eqnsclfac
81  end subroutine adv_cr
82 
83  !> @brief Define ADV object
84  !!
85  !! Define the ADV package
86  !<
87  subroutine adv_df(this, adv_options)
88  ! -- dummy
89  class(tspadvtype) :: this
90  type(tspadvoptionstype), optional, intent(in) :: adv_options !< the optional options, for when not constructing from file
91  ! -- local
92  character(len=*), parameter :: fmtadv = &
93  "(1x,/1x,'ADV -- ADVECTION PACKAGE, VERSION 1, 8/25/2017', &
94  &' INPUT READ FROM MEMPATH: ', A, //)"
95  !
96  ! -- Read or set advection options
97  if (.not. present(adv_options)) then
98  !
99  ! --print a message identifying the advection package.
100  write (this%iout, fmtadv) this%input_mempath
101  !
102  ! --read options from file
103  call this%source_options()
104  else
105  !
106  ! --set options from input arg
107  this%iadvwt = adv_options%iAdvScheme
108  end if
109  end subroutine adv_df
110 
111  !> @brief Allocate and read method for package
112  !!
113  !! Method to allocate and read static data for the ADV package.
114  !<
115  subroutine adv_ar(this, dis, ibound)
116  ! -- modules
117  use simmodule, only: store_error
118  ! -- dummy
119  class(tspadvtype) :: this
120  class(disbasetype), pointer, intent(in) :: dis
121  integer(I4B), dimension(:), pointer, contiguous, intent(in) :: ibound
122  ! -- local
123  integer(I4B) :: iadvwt_value
124  !
125  ! -- adv pointers to arguments that were passed in
126  this%dis => dis
127  this%ibound => ibound
128  !
129  ! -- Create interpolation scheme
130  iadvwt_value = this%iadvwt ! Dereference iadvwt to work with case statement
131  select case (iadvwt_value)
132  case (adv_scheme_upstream)
133  this%face_interpolation = &
134  upstreamschemetype(this%dis, this%fmi)
135  case (adv_scheme_central)
136  this%face_interpolation = &
137  centraldifferenceschemetype(this%dis, this%fmi)
138  case (adv_scheme_tvd)
139  this%face_interpolation = &
140  tvdschemetype(this%dis, this%fmi, this%ibound)
141  case (adv_scheme_utvd)
142  this%gradient = leastsquaresgradienttype(this%dis)
143  this%face_interpolation = &
144  utvdschemetype(this%dis, this%fmi, this%gradient)
145  case default
146  call store_error("Unknown advection scheme", terminate=.true.)
147  end select
148  end subroutine adv_ar
149 
150  !> @brief Calculate maximum time step length
151  !!
152  !! Return the largest time step that meets stability constraints
153  !<
154  subroutine adv_dt(this, dtmax, msg, thetam)
155  ! dummy
156  class(tspadvtype) :: this !< this instance
157  real(DP), intent(out) :: dtmax !< maximum allowable dt subject to stability constraint
158  character(len=*), intent(inout) :: msg !< package/cell dt constraint message
159  real(DP), dimension(:), intent(in) :: thetam !< porosity
160  ! local
161  integer(I4B) :: n
162  integer(I4B) :: m
163  integer(I4B) :: ipos
164  integer(I4B) :: nrmax
165  character(len=LINELENGTH) :: cellstr
166  real(DP) :: dt
167  real(DP) :: flowmax
168  real(DP) :: flowsumpos
169  real(DP) :: flowsumneg
170  real(DP) :: flownm
171  real(DP) :: cell_volume
172  dtmax = dnodata
173  nrmax = 0
174  msg = ''
175 
176  ! If ats_percel not specified by user, then return without making
177  ! the courant time step calculation
178  if (this%ats_percel == dnodata) then
179  return
180  end if
181 
182  ! Calculate time step lengths based on stability constraint for each cell
183  ! and store the smallest one
184  do n = 1, this%dis%nodes
185  if (this%ibound(n) == 0) cycle
186  flowsumneg = dzero
187  flowsumpos = dzero
188  do ipos = this%dis%con%ia(n) + 1, this%dis%con%ia(n + 1) - 1
189  if (this%dis%con%mask(ipos) == 0) cycle
190  m = this%dis%con%ja(ipos)
191  if (this%ibound(m) == 0) cycle
192  flownm = this%fmi%gwfflowja(ipos)
193  if (flownm < dzero) then
194  flowsumneg = flowsumneg - flownm
195  else
196  flowsumpos = flowsumpos + flownm
197  end if
198  end do
199  flowmax = max(flowsumneg, flowsumpos)
200  if (flowmax < dprec) cycle
201  cell_volume = this%dis%get_cell_volume(n, this%dis%top(n))
202  dt = cell_volume * this%fmi%gwfsat(n) * thetam(n) / flowmax
203  dt = dt * this%ats_percel
204  if (dt < dtmax) then
205  dtmax = dt
206  nrmax = n
207  end if
208  end do
209  if (nrmax > 0) then
210  call this%dis%noder_to_string(nrmax, cellstr)
211  write (msg, *) adjustl(trim(this%memoryPath))//'-'//trim(cellstr)
212  end if
213  end subroutine adv_dt
214 
215  !> @brief Fill coefficient method for ADV package
216  !!
217  !! Method to calculate coefficients and fill amat and rhs.
218  !<
219  subroutine adv_fc(this, nodes, matrix_sln, idxglo, cnew, rhs)
220  ! -- modules
221  ! -- dummy
222  class(tspadvtype) :: this !< this instance
223  integer(I4B), intent(in) :: nodes !< number of nodes
224  class(matrixbasetype), pointer :: matrix_sln !< pointer to solution matrix
225  integer(I4B), intent(in), dimension(:) :: idxglo !< global indices for matrix
226  real(DP), intent(in), dimension(:) :: cnew !< new concentration/temperature values
227  real(DP), dimension(:), intent(inout) :: rhs !< right-hand side vector
228  ! -- local
229  integer(I4B) :: n, m, idiag, ipos
230  real(DP) :: qnm !< volumetric flow rate
231  type(coefficientstype) :: coefficients
232 
233  ! Calculate internal domain fluxes and add to matrix_sln and rhs.
234  do n = 1, nodes
235  if (this%ibound(n) == 0) cycle ! skip inactive nodes
236  idiag = this%dis%con%ia(n)
237  do ipos = this%dis%con%ia(n) + 1, this%dis%con%ia(n + 1) - 1
238  m = this%dis%con%ja(ipos)
239  if (this%ibound(m) == 0) cycle ! skip inactive nodes
240  if (this%dis%con%mask(ipos) == 0) cycle ! skip masked connections
241 
242  qnm = this%fmi%gwfflowja(ipos) * this%eqnsclfac
243  coefficients = this%face_interpolation%compute(n, m, ipos, cnew)
244 
245  call matrix_sln%add_value_pos(idxglo(idiag), qnm * coefficients%c_n)
246  call matrix_sln%add_value_pos(idxglo(ipos), qnm * coefficients%c_m)
247  rhs(n) = rhs(n) + qnm * coefficients%rhs
248  end do
249  end do
250  end subroutine adv_fc
251 
252  !> @brief Calculate advection contribution to flowja
253  !<
254  subroutine adv_cq(this, cnew, flowja)
255  ! -- modules
256  ! -- dummy
257  class(tspadvtype) :: this
258  real(DP), intent(in), dimension(:) :: cnew
259  real(DP), intent(inout), dimension(:) :: flowja
260  ! -- local
261  integer(I4B) :: nodes
262  integer(I4B) :: n, m, ipos
263  real(DP) :: qnm
264  type(coefficientstype) :: coefficients
265  !
266  ! -- Calculate advection and add to flowja. qnm is the volumetric flow
267  ! rate and has dimensions of L^/T.
268  nodes = this%dis%nodes
269 
270  do n = 1, nodes
271  if (this%ibound(n) == 0) cycle
272  do ipos = this%dis%con%ia(n) + 1, this%dis%con%ia(n + 1) - 1
273  m = this%dis%con%ja(ipos)
274  if (this%ibound(m) == 0) cycle
275  qnm = this%fmi%gwfflowja(ipos) * this%eqnsclfac
276 
277  coefficients = this%face_interpolation%compute(n, m, ipos, cnew)
278  flowja(ipos) = flowja(ipos) &
279  + qnm * coefficients%c_n * cnew(n) &
280  + qnm * coefficients%c_m * cnew(m) &
281  - qnm * coefficients%rhs
282  end do
283  end do
284 
285  end subroutine adv_cq
286 
287  !> @brief Deallocate memory
288  !<
289  subroutine adv_da(this)
290  ! -- modules
292  ! -- dummy
293  class(tspadvtype) :: this
294  !
295  ! -- Deallocate arrays if package was active
296  if (this%inunit > 0) then
297  end if
298  !
299  ! -- nullify pointers
300  this%ibound => null()
301  !
302  ! -- Scalars
303  call mem_deallocate(this%iadvwt)
304  call mem_deallocate(this%ats_percel)
305  !
306  ! -- deallocate parent
307  call this%NumericalPackageType%da()
308  end subroutine adv_da
309 
310  !> @brief Allocate scalars specific to the streamflow energy transport (SFE)
311  !! package.
312  !<
313  subroutine allocate_scalars(this)
314  ! -- modules
316  ! -- dummy
317  class(tspadvtype) :: this
318  ! -- local
319  !
320  ! -- allocate scalars in NumericalPackageType
321  call this%NumericalPackageType%allocate_scalars()
322  !
323  ! -- Allocate
324  call mem_allocate(this%iadvwt, 'IADVWT', this%memoryPath)
325  call mem_allocate(this%ats_percel, 'ATS_PERCEL', this%memoryPath)
326  !
327  ! -- Initialize
328  this%iadvwt = adv_scheme_upstream
329  this%ats_percel = dnodata
330  !
331  ! -- Advection creates an asymmetric coefficient matrix
332  this%iasym = 1
333  end subroutine allocate_scalars
334 
335  !> @brief Source input options
336  !<
337  subroutine source_options(this)
338  ! -- modules
339  use kindmodule, only: lgp
340  use constantsmodule, only: lenvarname
341  use simvariablesmodule, only: errmsg
344  ! -- dummy
345  class(tspadvtype) :: this
346  ! -- locals
347  character(len=LENVARNAME), dimension(4) :: scheme = &
348  &[character(len=LENVARNAME) :: 'UPSTREAM', 'CENTRAL', 'TVD', 'UTVD']
349  logical(lgp) :: found_scheme, found_atspercel
350  ! -- formats
351  character(len=*), parameter :: fmtiadvwt = &
352  &"(4x,'ADVECTION WEIGHTING SCHEME HAS BEEN SET TO: ', a)"
353 
354  ! update defaults with input sourced values
355  call mem_set_value(this%iadvwt, 'SCHEME', this%input_mempath, &
356  scheme, found_scheme)
357  call mem_set_value(this%ats_percel, 'ATS_PERCEL', this%input_mempath, &
358  found_atspercel)
359 
360  if (found_scheme) then
361  ! should currently be set to index of scheme names
362  if (this%iadvwt == 0) then
363  write (errmsg, '(a, a)') &
364  'Unknown scheme, must be "UPSTREAM", "CENTRAL", "TVD" or "UTVD"'
365  call store_error(errmsg)
366  call store_error_filename(this%input_fname)
367  else
368  ! scheme parameters are 0 based
369  this%iadvwt = this%iadvwt - 1
370  end if
371  end if
372  if (found_atspercel) then
373  if (this%ats_percel == dzero) this%ats_percel = dnodata
374  end if
375 
376  ! log options
377  write (this%iout, '(1x,a)') 'PROCESSING ADVECTION OPTIONS'
378  if (found_scheme) then
379  write (this%iout, fmtiadvwt) trim(scheme(this%iadvwt + 1))
380  end if
381  if (found_atspercel) then
382  write (this%iout, '(4x,a,1pg15.6)') &
383  'User-specified fractional cell distance for adaptive time &
384  &steps: ', this%ats_percel
385  end if
386  write (this%iout, '(1x,a)') 'END OF ADVECTION OPTIONS'
387  end subroutine source_options
388 
389 end module tspadvmodule
integer(i4b), parameter adv_scheme_tvd
integer(i4b), parameter adv_scheme_upstream
integer(i4b), parameter adv_scheme_utvd
integer(i4b), parameter adv_scheme_central
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
real(dp), parameter dnodata
real no data constant
Definition: Constants.f90:95
integer(i4b), parameter lenvarname
maximum length of a variable name
Definition: Constants.f90:17
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
real(dp), parameter dprec
real constant machine precision
Definition: Constants.f90:120
real(dp), parameter done
real constant 1
Definition: Constants.f90:76
This module defines variable data types.
Definition: kind.f90:8
This module contains the base numerical package type.
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
subroutine, public store_error_filename(filename, terminate)
Store the erroring file name.
Definition: Sim.f90:203
This module contains simulation variables.
Definition: SimVariables.f90:9
character(len=maxcharlen) errmsg
error message string
subroutine, public adv_cr(advobj, name_model, input_mempath, inunit, iout, fmi, eqnsclfac)
@ brief Create a new ADV object
Definition: tsp-adv.f90:58
subroutine source_options(this)
Source input options.
Definition: tsp-adv.f90:338
subroutine adv_df(this, adv_options)
Define ADV object.
Definition: tsp-adv.f90:88
subroutine adv_fc(this, nodes, matrix_sln, idxglo, cnew, rhs)
Fill coefficient method for ADV package.
Definition: tsp-adv.f90:220
subroutine adv_cq(this, cnew, flowja)
Calculate advection contribution to flowja.
Definition: tsp-adv.f90:255
subroutine adv_da(this)
Deallocate memory.
Definition: tsp-adv.f90:290
subroutine adv_ar(this, dis, ibound)
Allocate and read method for package.
Definition: tsp-adv.f90:116
subroutine adv_dt(this, dtmax, msg, thetam)
Calculate maximum time step length.
Definition: tsp-adv.f90:155
subroutine allocate_scalars(this)
Allocate scalars specific to the streamflow energy transport (SFE) package.
Definition: tsp-adv.f90:314
Abstract interface for cell-based gradient computation.
Definition: IGradient.f90:15
Weighted least-squares gradient method for structured and unstructured grids.
Total Variation Diminishing (TVD) interpolation scheme.
Definition: UTVDScheme.f90:35