MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
gwe-ctp.f90
Go to the documentation of this file.
2  !
3  use kindmodule, only: dp, i4b
6  use simvariablesmodule, only: errmsg
9  use bndmodule, only: bndtype
10  use bndextmodule, only: bndexttype
11  use observemodule, only: observetype
15  !
16  implicit none
17  !
18  private
19  public :: ctp_create
20  !
21  character(len=LENFTYPE) :: ftype = 'CTP'
22  character(len=LENPACKAGENAME) :: text = ' CTP'
23  !
24  type, extends(bndexttype) :: gwectptype
25 
26  real(dp), dimension(:), pointer, contiguous :: tspvar => null() !< constant temperature array
27  real(dp), dimension(:), pointer, contiguous :: ratectpin => null() !< simulated flows into constant temperature (excluding other CNTs)
28  real(dp), dimension(:), pointer, contiguous :: ratectpout => null() !< simulated flows out of constant temperature (excluding to other CNTs)
29  character(len=LENVARNAME) :: depvartype = '' !< stores string of dependent variable type, depending on model type
30  contains
31  procedure :: bnd_rp => ctp_rp
32  procedure :: bnd_ad => ctp_ad
33  procedure :: bnd_ck => ctp_ck
34  procedure :: bnd_fc => ctp_fc
35  procedure :: bnd_cq => ctp_cq
36  procedure :: bnd_bd => ctp_bd
37  procedure :: bnd_da => ctp_da
38  procedure :: allocate_arrays => ctp_allocate_arrays
39  procedure :: define_listlabel
40  procedure :: bound_value => ctp_bound_value
41  procedure :: temp_mult
42  ! -- methods for observations
43  procedure, public :: bnd_obs_supported => ctp_obs_supported
44  procedure, public :: bnd_df_obs => ctp_df_obs
45  ! -- method for time series
46  procedure, public :: bnd_rp_ts => ctp_rp_ts
47  end type gwectptype
48 
49 contains
50 
51  !> @brief Create a new constant temperature package
52  !!
53  !! Routine points packobj to the newly created package
54  !<
55  subroutine ctp_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, &
56  depvartype, mempath)
57  ! -- dummy
58  class(bndtype), pointer :: packobj
59  integer(I4B), intent(in) :: id
60  integer(I4B), intent(in) :: ibcnum
61  integer(I4B), intent(in) :: inunit
62  integer(I4B), intent(in) :: iout
63  character(len=*), intent(in) :: namemodel
64  character(len=*), intent(in) :: pakname
65  character(len=LENVARNAME), intent(in) :: depvartype
66  character(len=*), intent(in) :: mempath
67  ! -- local
68  type(gwectptype), pointer :: ctpobj
69  !
70  ! -- allocate the object and assign values to object variables
71  allocate (ctpobj)
72  packobj => ctpobj
73  !
74  ! -- create name and memory path
75  call packobj%set_names(ibcnum, namemodel, pakname, ftype, mempath)
76  packobj%text = text
77  !
78  ! -- allocate scalars
79  call ctpobj%allocate_scalars()
80  !
81  ! -- initialize package
82  call packobj%pack_initialize()
83  !
84  ! -- store values
85  packobj%inunit = inunit
86  packobj%iout = iout
87  packobj%id = id
88  packobj%ibcnum = ibcnum
89  packobj%ncolbnd = 1
90  packobj%iscloc = 1
91  !
92  ! -- Store the appropriate label based on the dependent variable
93  ctpobj%depvartype = depvartype
94  end subroutine ctp_create
95 
96  !> @brief Allocate arrays specific to the constant temperature package
97  !<
98  subroutine ctp_allocate_arrays(this, nodelist, auxvar)
99  ! -- modules
101  ! -- dummy
102  class(gwectptype) :: this
103  integer(I4B), dimension(:), pointer, contiguous, optional :: nodelist
104  real(DP), dimension(:, :), pointer, contiguous, optional :: auxvar
105  ! -- local
106  integer(I4B) :: i
107  !
108  ! -- call standard BndType allocate scalars
109  call this%BndExtType%allocate_arrays(nodelist, auxvar)
110  !
111  ! -- allocate ratectpex
112  call mem_allocate(this%ratectpin, this%maxbound, 'RATECTPIN', this%memoryPath)
113  call mem_allocate(this%ratectpout, this%maxbound, 'RATECTPOUT', &
114  this%memoryPath)
115  do i = 1, this%maxbound
116  this%ratectpin(i) = dzero
117  this%ratectpout(i) = dzero
118  end do
119  ! -- set constant head array input context pointer
120  call mem_setptr(this%tspvar, 'TSPVAR', this%input_mempath)
121  !
122  ! -- checkin constant head array input context pointer
123  call mem_checkin(this%tspvar, 'TSPVAR', this%memoryPath, &
124  'TSPVAR', this%input_mempath)
125  !
126  end subroutine ctp_allocate_arrays
127 
128  !> @brief Constant temperature read and prepare (rp) routine
129  !<
130  subroutine ctp_rp(this)
131  ! -- modules
132  use simmodule, only: store_error
133  use inputoutputmodule, only: lowcase
134  implicit none
135  ! -- dummy
136  class(gwectptype), intent(inout) :: this
137  ! -- local
138  integer(I4B) :: i, node, ibd, ierr
139  character(len=30) :: nodestr
140  character(len=LENVARNAME) :: dvtype
141  !
142  ! -- Reset previous CTPs to active cell
143  do i = 1, this%nbound
144  node = this%nodelist(i)
145  this%ibound(node) = this%ibcnum
146  end do
147  !
148  ! -- Call the parent class read and prepare
149  call this%BndExtType%bnd_rp()
150  !
151  ! -- Set ibound to -(ibcnum + 1) for constant temperature cells
152  ierr = 0
153  do i = 1, this%nbound
154  node = this%nodelist(i)
155  ibd = this%ibound(node)
156  if (ibd < 0) then
157  call this%dis%noder_to_string(node, nodestr)
158  dvtype = trim(this%depvartype)
159  call lowcase(dvtype)
160  call store_error('Cell is already a constant ' &
161  //dvtype//': '//trim(adjustl(nodestr)))
162  ierr = ierr + 1
163  else
164  this%ibound(node) = -this%ibcnum
165  end if
166  end do
167  !
168  ! -- Stop if errors detected
169  if (ierr > 0) then
170  call store_error_filename(this%input_fname)
171  end if
172  !
173  ! -- Write the list to iout if requested
174  if (this%iprpak /= 0) then
175  call this%write_list()
176  end if
177  end subroutine ctp_rp
178 
179  !> @brief Constant temperature package advance routine
180  !!
181  !! Add package connections to matrix
182  !<
183  subroutine ctp_ad(this)
184  ! -- dummy
185  class(gwectptype) :: this
186  ! -- local
187  integer(I4B) :: i, node
188  real(DP) :: cb
189  !
190  ! -- Advance the time series
191  call this%TsManager%ad()
192  !
193  ! -- Process each entry in the constant temperature cell list
194  do i = 1, this%nbound
195  node = this%nodelist(i)
196  cb = this%temp_mult(i)
197  !
198  this%xnew(node) = cb
199  this%xold(node) = this%xnew(node)
200  end do
201  !
202  ! -- For each observation, push simulated value and corresponding
203  ! simulation time from "current" to "preceding" and reset
204  ! "current" value.
205  call this%obs%obs_ad()
206  end subroutine ctp_ad
207 
208  !> @brief Check constant temperature boundary condition data
209  !<
210  subroutine ctp_ck(this)
211  ! -- dummy
212  class(gwectptype), intent(inout) :: this
213  ! -- local
214  character(len=30) :: nodestr
215  integer(I4B) :: i
216  integer(I4B) :: node
217  ! -- formats
218  character(len=*), parameter :: fmtctperr = &
219  &"('Specified dependent variable boundary ',i0, &
220  &' temperature (',g0,') is less than zero for cell', a)"
221  !
222  ! -- check stress period data
223  do i = 1, this%nbound
224  node = this%nodelist(i)
225  ! -- accumulate errors
226  if (this%temp_mult(i) < dzero) then
227  call this%dis%noder_to_string(node, nodestr)
228  write (errmsg, fmt=fmtctperr) i, this%tspvar(i), trim(nodestr)
229  call store_error(errmsg)
230  end if
231  end do
232  !
233  ! -- write summary of ctp package error messages
234  if (count_errors() > 0) then
235  call store_error_filename(this%input_fname)
236  end if
237  end subroutine ctp_ck
238 
239  !> @brief Override bnd_fc and do nothing
240  !!
241  !! For constant temperature boundary type, the call to bnd_fc needs to be
242  !! overwritten to prevent logic found in bnd from being executed
243  !<
244  subroutine ctp_fc(this, rhs, ia, idxglo, matrix_sln)
245  ! -- dummy
246  class(gwectptype) :: this
247  real(DP), dimension(:), intent(inout) :: rhs
248  integer(I4B), dimension(:), intent(in) :: ia
249  integer(I4B), dimension(:), intent(in) :: idxglo
250  class(matrixbasetype), pointer :: matrix_sln
251  end subroutine ctp_fc
252 
253  !> @brief Calculate flow associated with constant temperature boundary
254  !!
255  !! This method overrides bnd_cq()
256  !<
257  subroutine ctp_cq(this, x, flowja, iadv)
258  ! -- dummy
259  class(gwectptype), intent(inout) :: this
260  real(DP), dimension(:), intent(in) :: x
261  real(DP), dimension(:), contiguous, intent(inout) :: flowja
262  integer(I4B), optional, intent(in) :: iadv
263  ! -- local
264  integer(I4B) :: i
265  integer(I4B) :: ipos
266  integer(I4B) :: node
267  integer(I4B) :: n2
268  integer(I4B) :: idiag
269  real(DP) :: rate
270  real(DP) :: ratein, rateout
271  real(DP) :: q
272  !
273  ! -- If no boundaries, skip flow calculations.
274  if (this%nbound > 0) then
275  !
276  ! -- Loop through each boundary calculating flow.
277  do i = 1, this%nbound
278  node = this%nodelist(i)
279  idiag = this%dis%con%ia(node)
280  rate = dzero
281  ratein = dzero
282  rateout = dzero
283  !
284  ! -- Calculate the flow rate into the cell.
285  do ipos = this%dis%con%ia(node) + 1, &
286  this%dis%con%ia(node + 1) - 1
287  q = flowja(ipos)
288  rate = rate - q
289  ! -- Only accumulate chin and chout for active
290  ! connected cells
291  n2 = this%dis%con%ja(ipos)
292  if (this%ibound(n2) > 0) then
293  if (q < dzero) then
294  ratein = ratein - q
295  else
296  rateout = rateout + q
297  end if
298  end if
299  end do
300  !
301  ! -- For CTP, store total flow in rhs so it is available for other
302  ! calculations
303  this%rhs(i) = -rate
304  this%hcof(i) = dzero
305  !
306  ! -- Save simulated value to simvals array.
307  this%simvals(i) = rate
308  this%ratectpin(i) = ratein
309  this%ratectpout(i) = rateout
310  flowja(idiag) = flowja(idiag) + rate
311  !
312  end do
313  !
314  end if
315  end subroutine ctp_cq
316 
317  !> @brief Add package ratin/ratout to model budget
318  !<
319  subroutine ctp_bd(this, model_budget)
320  ! -- modules
321  use tdismodule, only: delt
323  ! -- dummy
324  class(gwectptype) :: this
325  ! -- local
326  type(budgettype), intent(inout) :: model_budget
327  real(DP) :: ratin
328  real(DP) :: ratout
329  real(DP) :: dum
330  integer(I4B) :: isuppress_output
331  !
332  isuppress_output = 0
333  call rate_accumulator(this%ratectpin(1:this%nbound), ratin, dum)
334  call rate_accumulator(this%ratectpout(1:this%nbound), ratout, dum)
335  call model_budget%addentry(ratin, ratout, delt, this%text, &
336  isuppress_output, this%packName)
337  end subroutine ctp_bd
338 
339  !> @brief Deallocate memory
340  !!
341  !! Method to deallocate memory for the package.
342  !<
343  subroutine ctp_da(this)
344  ! -- modules
346  ! -- dummy
347  class(gwectptype) :: this
348  !
349  ! -- Deallocate parent package
350  call this%BndExtType%bnd_da()
351  !
352  ! -- arrays
353  call mem_deallocate(this%ratectpin)
354  call mem_deallocate(this%ratectpout)
355  call mem_deallocate(this%tspvar, 'TSPVAR', this%memoryPath)
356  end subroutine ctp_da
357 
358  !> @brief Define labels used in list file
359  !!
360  !! Define the list heading that is written to iout when PRINT_INPUT option
361  !! is used.
362  !<
363  subroutine define_listlabel(this)
364  ! -- dummy
365  class(gwectptype), intent(inout) :: this
366  !
367  ! -- create the header list label
368  this%listlabel = trim(this%filtyp)//' NO.'
369  if (this%dis%ndim == 3) then
370  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'LAYER'
371  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'ROW'
372  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'COL'
373  elseif (this%dis%ndim == 2) then
374  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'LAYER'
375  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'CELL2D'
376  else
377  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'NODE'
378  end if
379  write (this%listlabel, '(a, a16)') trim(this%listlabel), &
380  trim(this%depvartype)
381  if (this%inamedbound == 1) then
382  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'BOUNDARY NAME'
383  end if
384  end subroutine define_listlabel
385 
386  !> @brief Procedure related to observation processing
387  !!
388  !! This routine:
389  !! - returns true because the SDV package supports observations,
390  !! - overrides packagetype%_obs_supported()
391  logical function ctp_obs_supported(this)
392  ! -- dummy
393  class(gwectptype) :: this
394  !
395  ctp_obs_supported = .true.
396  end function ctp_obs_supported
397 
398  !> @brief Procedure related to observation processing
399  !!
400  !! This routine:
401  !! - defines observations
402  !! - stores observation types supported by either of the SDV packages
403  !! (CTP or CTP),
404  !! - overrides BndExtType%bnd_df_obs
405  !<
406  subroutine ctp_df_obs(this)
407  ! -- dummy
408  class(gwectptype) :: this
409  ! -- local
410  integer(I4B) :: indx
411  !
412  call this%obs%StoreObsType(this%filtyp, .true., indx)
413  this%obs%obsData(indx)%ProcessIdPtr => defaultobsidprocessor
414  end subroutine ctp_df_obs
415 
416  ! -- Procedure related to time series
417 
418  !> @brief Procedure related to time series
419  !!
420  !! Assign tsLink%Text appropriately for all time series in use by package.
421  !! For the constant temperature packages, the dependent variable can also be
422  !! controlled by a time series.
423  !<
424  subroutine ctp_rp_ts(this)
425  ! -- dummy
426  class(gwectptype), intent(inout) :: this
427  ! -- local
428  integer(I4B) :: i, nlinks
429  type(timeserieslinktype), pointer :: tslink => null()
430  !
431  nlinks = this%TsManager%boundtslinks%Count()
432  do i = 1, nlinks
433  tslink => gettimeserieslinkfromlist(this%TsManager%boundtslinks, i)
434  if (associated(tslink)) then
435  select case (tslink%JCol)
436  case (1)
437  tslink%Text = trim(this%depvartype)
438  end select
439  end if
440  end do
441  end subroutine ctp_rp_ts
442 
443  !> @brief Apply auxiliary multiplier to specified temperature if
444  !< appropriate
445  function temp_mult(this, row) result(temp)
446  ! -- modules
447  use constantsmodule, only: dzero
448  ! -- dummy
449  class(gwectptype), intent(inout) :: this !< BndExtType object
450  integer(I4B), intent(in) :: row
451  ! -- result
452  real(dp) :: temp
453  !
454  if (this%iauxmultcol > 0) then
455  temp = this%tspvar(row) * this%auxvar(this%iauxmultcol, row)
456  else
457  temp = this%tspvar(row)
458  end if
459  end function temp_mult
460 
461  !> @ brief Return a bound value
462  !!
463  !! Return a bound value associated with an ncolbnd index and row.
464  !<
465  function ctp_bound_value(this, col, row) result(bndval)
466  ! -- modules
467  use constantsmodule, only: dzero
468  ! -- dummy variables
469  class(gwectptype), intent(inout) :: this !< BndExtType object
470  integer(I4B), intent(in) :: col
471  integer(I4B), intent(in) :: row
472  ! -- result
473  real(dp) :: bndval
474  !
475  select case (col)
476  case (1)
477  bndval = this%temp_mult(row)
478  case default
479  write (errmsg, '(3a)') 'Programming error. ', &
480  & adjustl(trim(this%filtyp)), ' bound value requested column '&
481  &'outside range of ncolbnd (1).'
482  call store_error(errmsg)
483  call store_error_filename(this%input_fname)
484  end select
485  end function ctp_bound_value
486 
487 end module gwectpmodule
This module contains the extended boundary package.
This module contains the base boundary package.
This module contains the BudgetModule.
Definition: Budget.f90:20
subroutine, public rate_accumulator(flow, rin, rout)
@ brief Rate accumulator subroutine
Definition: Budget.f90:632
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter lenpackagename
maximum length of the package name
Definition: Constants.f90:23
integer(i4b), parameter namedboundflag
named bound flag
Definition: Constants.f90:49
integer(i4b), parameter lenvarname
maximum length of a variable name
Definition: Constants.f90:17
integer(i4b), parameter lenftype
maximum length of a package type (DIS, WEL, OC, etc.)
Definition: Constants.f90:39
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
real(dp), parameter done
real constant 1
Definition: Constants.f90:76
subroutine ctp_bd(this, model_budget)
Add package ratin/ratout to model budget.
Definition: gwe-ctp.f90:320
character(len=lenpackagename) text
Definition: gwe-ctp.f90:22
subroutine ctp_cq(this, x, flowja, iadv)
Calculate flow associated with constant temperature boundary.
Definition: gwe-ctp.f90:258
real(dp) function temp_mult(this, row)
Apply auxiliary multiplier to specified temperature if.
Definition: gwe-ctp.f90:446
subroutine ctp_rp(this)
Constant temperature read and prepare (rp) routine.
Definition: gwe-ctp.f90:131
real(dp) function ctp_bound_value(this, col, row)
@ brief Return a bound value
Definition: gwe-ctp.f90:466
subroutine ctp_rp_ts(this)
Procedure related to time series.
Definition: gwe-ctp.f90:425
logical function ctp_obs_supported(this)
Procedure related to observation processing.
Definition: gwe-ctp.f90:392
subroutine ctp_df_obs(this)
Procedure related to observation processing.
Definition: gwe-ctp.f90:407
subroutine ctp_da(this)
Deallocate memory.
Definition: gwe-ctp.f90:344
subroutine define_listlabel(this)
Define labels used in list file.
Definition: gwe-ctp.f90:364
subroutine ctp_allocate_arrays(this, nodelist, auxvar)
Allocate arrays specific to the constant temperature package.
Definition: gwe-ctp.f90:99
character(len=lenftype) ftype
Definition: gwe-ctp.f90:21
subroutine ctp_fc(this, rhs, ia, idxglo, matrix_sln)
Override bnd_fc and do nothing.
Definition: gwe-ctp.f90:245
subroutine ctp_ad(this)
Constant temperature package advance routine.
Definition: gwe-ctp.f90:184
subroutine ctp_ck(this)
Check constant temperature boundary condition data.
Definition: gwe-ctp.f90:211
subroutine, public ctp_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, depvartype, mempath)
Create a new constant temperature package.
Definition: gwe-ctp.f90:57
subroutine, public lowcase(word)
Convert to lower case.
This module defines variable data types.
Definition: kind.f90:8
This module contains the derived types ObserveType and ObsDataType.
Definition: Observe.f90:15
This module contains the derived type ObsType.
Definition: Obs.f90:127
subroutine, public defaultobsidprocessor(obsrv, dis, inunitobs, iout)
@ brief Process IDstring provided for each observation
Definition: Obs.f90:246
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
integer(i4b) function, public count_errors()
Return number of errors.
Definition: Sim.f90:59
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
real(dp), pointer, public delt
length of the current time step
Definition: tdis.f90:29
type(timeserieslinktype) function, pointer, public gettimeserieslinkfromlist(list, indx)
Get time series link from a list.
@ brief BndType
Derived type for the Budget object.
Definition: Budget.f90:39