MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
timearrayseriesmanagermodule Module Reference

Data Types

type  timearrayseriesmanagertype
 

Functions/Subroutines

subroutine, public tasmanager_cr (this, dis, modelname, iout)
 Create the time-array series manager. More...
 
subroutine tasmanager_df (this)
 Define the time-array series manager. More...
 
subroutine tasmgr_ad (this)
 Time step (or subtime step) advance. More...
 
subroutine tasmgr_da (this)
 Deallocate. More...
 
subroutine add_tasfile (this, fname)
 Add a time-array series file. More...
 
subroutine reset (this, pkgName)
 Zero out arrays that are represented with time series. More...
 
subroutine maketaslink (this, pkgName, bndArray, iprpak, tasName, text, convertFlux, nodelist, inunit)
 Make link from time-array series to package array. More...
 
type(timearrayserieslinktype) function, pointer getlink (this, indx)
 Get link from the boundtaslinks list. More...
 
integer(i4b) function countlinks (this)
 Count number of links in the boundtaslinks list. More...
 
subroutine tasmgr_convert_flux (this, tasLink)
 Convert the array from a flux to a flow rate by multiplying by the cell area. More...
 
subroutine tasmgr_add_link (this, tasLink)
 Add a time arrays series link. More...
 

Function/Subroutine Documentation

◆ add_tasfile()

subroutine timearrayseriesmanagermodule::add_tasfile ( class(timearrayseriesmanagertype this,
character(len=*), intent(in)  fname 
)
private

Definition at line 221 of file TimeArraySeriesManager.f90.

222  ! -- modules
224  ! -- dummy
225  class(TimeArraySeriesManagerType) :: this
226  character(len=*), intent(in) :: fname
227  ! -- local
228  integer(I4B) :: indx
229  !
230  call expandarray(this%tasfiles, 1)
231  indx = size(this%tasfiles)
232  this%tasfiles(indx) = fname

◆ countlinks()

integer(i4b) function timearrayseriesmanagermodule::countlinks ( class(timearrayseriesmanagertype this)
private

Definition at line 339 of file TimeArraySeriesManager.f90.

340  ! -- return
341  integer(I4B) :: CountLinks
342  ! -- dummy
343  class(TimeArraySeriesManagerType) :: this
344  !
345  if (associated(this%boundtaslinks)) then
346  countlinks = this%boundTasLinks%Count()
347  else
348  countlinks = 0
349  end if

◆ getlink()

type(timearrayserieslinktype) function, pointer timearrayseriesmanagermodule::getlink ( class(timearrayseriesmanagertype this,
integer(i4b), intent(in)  indx 
)
private

Definition at line 323 of file TimeArraySeriesManager.f90.

324  ! -- dummy
325  class(TimeArraySeriesManagerType) :: this
326  integer(I4B), intent(in) :: indx
327  ! -- return
328  type(TimeArraySeriesLinkType), pointer :: tasLink
329  !
330  taslink => null()
331  !
332  if (associated(this%boundTasLinks)) then
333  taslink => gettimearrayserieslinkfromlist(this%boundTasLinks, indx)
334  end if
Here is the call graph for this function:

◆ maketaslink()

subroutine timearrayseriesmanagermodule::maketaslink ( class(timearrayseriesmanagertype this,
character(len=*), intent(in)  pkgName,
real(dp), dimension(:), pointer  bndArray,
integer(i4b), intent(in)  iprpak,
character(len=*), intent(in)  tasName,
character(len=*), intent(in)  text,
logical, intent(in)  convertFlux,
integer(i4b), dimension(:), intent(in), pointer, contiguous  nodelist,
integer(i4b), intent(in)  inunit 
)
private

Definition at line 275 of file TimeArraySeriesManager.f90.

277  ! -- dummy
278  class(TimeArraySeriesManagerType) :: this
279  character(len=*), intent(in) :: pkgName
280  real(DP), dimension(:), pointer :: bndArray
281  integer(I4B), intent(in) :: iprpak
282  character(len=*), intent(in) :: tasName
283  character(len=*), intent(in) :: text
284  logical, intent(in) :: convertFlux
285  integer(I4B), dimension(:), pointer, contiguous, intent(in) :: nodelist
286  integer(I4B), intent(in) :: inunit
287  ! -- local
288  integer(I4B) :: i, nfiles, iloc
289  character(LINELENGTH) :: ermsg
290  type(TimeArraySeriesLinkType), pointer :: newTasLink
291  type(TimeArraySeriesType), pointer :: tasptr => null()
292  !
293  ! -- Find the time array series
294  nfiles = size(this%tasnames)
295  iloc = 0
296  do i = 1, nfiles
297  if (this%tasnames(i) == tasname) then
298  iloc = i
299  exit
300  end if
301  end do
302  if (iloc == 0) then
303  ermsg = 'Error: Time-array series "'//trim(tasname)//'" not found.'
304  call store_error(ermsg)
305  call store_error_unit(inunit)
306  end if
307  tasptr => this%taslist(iloc)
308  !
309  ! -- Construct a time-array series link
310  newtaslink => null()
311  call constructtimearrayserieslink(newtaslink, tasptr, &
312  pkgname, bndarray, iprpak, &
313  text)
314  newtaslink%ConvertFlux = convertflux
315  newtaslink%nodelist => nodelist
316  !
317  ! -- Add link to list of links
318  call this%tasmgr_add_link(newtaslink)
Here is the call graph for this function:

◆ reset()

subroutine timearrayseriesmanagermodule::reset ( class(timearrayseriesmanagertype this,
character(len=*), intent(in)  pkgName 
)

Delete all existing links from time array series to package arrays as they will need to be created with a new BEGIN PERIOD block

Definition at line 240 of file TimeArraySeriesManager.f90.

241  ! -- dummy
242  class(TimeArraySeriesManagerType) :: this
243  character(len=*), intent(in) :: pkgName
244  ! -- local
245  integer(I4B) :: i, j, nlinks
246  type(TimeArraySeriesLinkType), pointer :: taslink
247  !
248  ! -- Reassign all linked elements to zero
249  nlinks = this%boundTasLinks%Count()
250  do i = 1, nlinks
251  taslink => gettimearrayserieslinkfromlist(this%boundTasLinks, i)
252  if (associated(taslink)) then
253  do j = 1, size(taslink%BndArray)
254  taslink%BndArray(j) = dzero
255  end do
256  end if
257  end do
258  !
259  ! -- Delete all existing time array links
260  if (associated(this%boundTasLinks)) then
261  ! Deallocate and remove all links belonging to package
262  nlinks = this%boundTasLinks%Count()
263  do i = nlinks, 1, -1
264  taslink => gettimearrayserieslinkfromlist(this%boundTasLinks, i)
265  if (associated(taslink)) then
266  call taslink%da()
267  call this%boundTasLinks%RemoveNode(i, .true.)
268  end if
269  end do
270  end if
Here is the call graph for this function:

◆ tasmanager_cr()

subroutine, public timearrayseriesmanagermodule::tasmanager_cr ( type(timearrayseriesmanagertype this,
class(disbasetype), optional, pointer  dis,
character(len=*), intent(in)  modelname,
integer(i4b), intent(in)  iout 
)

Definition at line 57 of file TimeArraySeriesManager.f90.

58  ! -- dummy
59  type(TimeArraySeriesManagerType) :: this
60  class(DisBaseType), pointer, optional :: dis
61  character(len=*), intent(in) :: modelname
62  integer(I4B), intent(in) :: iout
63  !
64  if (present(dis)) then
65  this%dis => dis
66  end if
67  !
68  this%modelname = modelname
69  this%iout = iout
70  allocate (this%boundTasLinks)
71  allocate (this%tasfiles(0))
Here is the caller graph for this function:

◆ tasmanager_df()

subroutine timearrayseriesmanagermodule::tasmanager_df ( class(timearrayseriesmanagertype this)
private

Definition at line 76 of file TimeArraySeriesManager.f90.

77  ! -- dummy
78  class(TimeArraySeriesManagerType) :: this
79  ! -- local
80  type(TimeArraySeriesType), pointer :: tasptr => null()
81  integer(I4B) :: nfiles
82  integer(I4B) :: i
83  !
84  ! -- determine how many tasfiles. This is the number of time array series
85  ! so allocate arrays to store them
86  nfiles = size(this%tasfiles)
87  allocate (this%taslist(nfiles))
88  allocate (this%tasnames(nfiles))
89  !
90  ! -- Setup a time array series for each file specified
91  do i = 1, nfiles
92  tasptr => this%taslist(i)
93  call tasptr%tas_init(this%tasfiles(i), this%modelname, &
94  this%iout, this%tasnames(i))
95  end do

◆ tasmgr_ad()

subroutine timearrayseriesmanagermodule::tasmgr_ad ( class(timearrayseriesmanagertype this)
private

Call this each time step or subtime step.

Definition at line 102 of file TimeArraySeriesManager.f90.

103  ! -- dummy
104  class(TimeArraySeriesManagerType) :: this
105  ! -- local
106  type(TimeArraySeriesLinkType), pointer :: tasLink => null()
107  type(TimeArraySeriesType), pointer :: timearrayseries => null()
108  integer(I4B) :: i, j, nlinks, nvals, isize1, isize2, inunit
109  real(DP) :: begintime, endtime
110  ! -- formats
111  character(len=*), parameter :: fmt5 = &
112  "(/,'Time-array-series controlled arrays in stress period ', &
113  &i0, ', time step ', i0, ':')"
114 10 format('"', a, '" package: ', a, ' array obtained from time-array series "', &
115  a, '"')
116  !
117  ! -- Initialize time variables
118  begintime = totimc
119  endtime = begintime + delt
120  !
121  ! -- Iterate through boundtaslinks and update specified
122  ! array with array of average values obtained from
123  ! appropriate time series.
124  if (associated(this%boundTasLinks)) then
125  nlinks = this%boundTasLinks%Count()
126  do i = 1, nlinks
127  taslink => gettimearrayserieslinkfromlist(this%boundTasLinks, i)
128  if (taslink%Iprpak == 1 .and. i == 1) then
129  write (this%iout, fmt5) kper, kstp
130  end if
131  if (taslink%UseDefaultProc) then
132  timearrayseries => taslink%timeArraySeries
133  nvals = size(taslink%BndArray)
134  !
135  ! -- Fill the package array with integrated values
136  call timearrayseries%GetAverageValues(nvals, taslink%BndArray, &
137  begintime, endtime)
138  !
139  ! -- If conversion from flux to flow is required, multiply by cell area
140  if (taslink%ConvertFlux) then
141  call this%tasmgr_convert_flux(taslink)
142  end if
143  !
144  ! -- If PRINT_INPUT is specified, write information
145  ! regarding source of time-array series data
146  if (taslink%Iprpak == 1) then
147  write (this%iout, 10) trim(taslink%PackageName), &
148  trim(taslink%Text), &
149  trim(taslink%timeArraySeries%Name)
150  end if
151  end if
152  if (i == nlinks) then
153  write (this%iout, '()')
154  end if
155  end do
156  !
157  ! -- Now that all array values have been substituted, can now multiply
158  ! an array by a multiplier array
159  do i = 1, nlinks
160  taslink => gettimearrayserieslinkfromlist(this%boundTasLinks, i)
161  if (taslink%UseDefaultProc) then
162  if (associated(taslink%RMultArray)) then
163  isize1 = size(taslink%BndArray)
164  isize2 = size(taslink%RMultArray)
165  if (isize1 == isize2 .and. isize1 == nvals) then
166  do j = 1, nvals
167  taslink%BndArray(j) = taslink%BndArray(j) * taslink%RMultArray(j)
168  end do
169  else
170  errmsg = 'Size mismatch between boundary and multiplier arrays'// &
171  ' using time-array series: '// &
172  trim(taslink%TimeArraySeries%Name)
173  call store_error(errmsg)
174  inunit = taslink%TimeArraySeries%GetInunit()
175  call store_error_unit(inunit)
176  end if
177  end if
178  end if
179  end do
180  end if
Here is the call graph for this function:

◆ tasmgr_add_link()

subroutine timearrayseriesmanagermodule::tasmgr_add_link ( class(timearrayseriesmanagertype this,
type(timearrayserieslinktype), pointer  tasLink 
)
private

Definition at line 385 of file TimeArraySeriesManager.f90.

386  ! -- dummy
387  class(TimeArraySeriesManagerType) :: this
388  type(TimeArraySeriesLinkType), pointer :: tasLink
389  ! -- local
390  !
391  call addtimearrayserieslinktolist(this%boundTasLinks, taslink)
Here is the call graph for this function:

◆ tasmgr_convert_flux()

subroutine timearrayseriesmanagermodule::tasmgr_convert_flux ( class(timearrayseriesmanagertype this,
type(timearrayserieslinktype), intent(inout), pointer  tasLink 
)
private

Definition at line 357 of file TimeArraySeriesManager.f90.

358  ! -- dummy
359  class(TimeArraySeriesManagerType) :: this
360  type(TimeArraySeriesLinkType), pointer, intent(inout) :: tasLink
361  ! -- local
362  integer(I4B) :: i, n, noder
363  real(DP) :: area
364  !
365  if (.not. (associated(this%dis) .and. &
366  associated(taslink%nodelist))) then
367  errmsg = 'Programming error. Cannot convert flux. Verify that '&
368  &'a valid DIS instance and nodelist were provided.'
369  call store_error(errmsg)
370  call store_error_unit(taslink%TimeArraySeries%GetInunit())
371  end if
372  !
373  n = size(taslink%BndArray)
374  do i = 1, n
375  noder = taslink%nodelist(i)
376  if (noder > 0) then
377  area = this%dis%get_area(noder)
378  taslink%BndArray(i) = taslink%BndArray(i) * area
379  end if
380  end do
Here is the call graph for this function:

◆ tasmgr_da()

subroutine timearrayseriesmanagermodule::tasmgr_da ( class(timearrayseriesmanagertype this)
private

Definition at line 185 of file TimeArraySeriesManager.f90.

186  ! -- dummy
187  class(TimeArraySeriesManagerType) :: this
188  ! -- local
189  integer :: i, n
190  type(TimeArraySeriesLinkType), pointer :: tasLink => null()
191  !
192  ! -- Deallocate contents of each TimeArraySeriesType object in list
193  ! of time-array series links.
194  n = this%boundTasLinks%Count()
195  do i = 1, n
196  taslink => gettimearrayserieslinkfromlist(this%boundTasLinks, i)
197  call taslink%da()
198  end do
199  !
200  ! -- Go through and deallocate individual time array series
201  do i = 1, size(this%taslist)
202  call this%taslist(i)%da()
203  end do
204  !
205  ! -- Deallocate the list of time-array series links.
206  call this%boundTasLinks%Clear(.true.)
207  deallocate (this%boundTasLinks)
208  deallocate (this%tasfiles)
209  !
210  ! -- Deallocate the time array series
211  deallocate (this%taslist)
212  deallocate (this%tasnames)
213  !
214  ! -- nullify pointers
215  this%dis => null()
216  this%boundTasLinks => null()
Here is the call graph for this function: