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

Functions/Subroutines

logical(lgp) function, public isadaptiveperiod (kper)
 @ brief Determine if period is adaptive More...
 
subroutine, public ats_cr (inunit, nper_tdis)
 @ brief Create ATS object More...
 
subroutine ats_allocate_scalars ()
 @ brief Allocate scalars More...
 
subroutine ats_allocate_arrays ()
 @ brief Allocate arrays More...
 
subroutine, public ats_da ()
 @ brief Deallocate variables More...
 
subroutine ats_read_options ()
 @ brief Read options More...
 
subroutine ats_read_dimensions ()
 @ brief Read dimensions More...
 
subroutine ats_read_timing ()
 @ brief Read timing More...
 
subroutine ats_process_input ()
 @ brief Process input More...
 
subroutine ats_input_table ()
 @ brief Write input table More...
 
subroutine ats_check_timing ()
 @ brief Check timing More...
 
subroutine, public ats_period_message (kper)
 @ brief Write period message More...
 
subroutine, public ats_submit_delt (kstp, kper, dt, sloc, idir)
 @ brief Allow and external caller to submit preferred time step More...
 
subroutine, public ats_set_delt (kstp, kper, pertim, perlencurrent, delt)
 @ brief Set time step More...
 
subroutine, public ats_reset_delt (kstp, kper, lastStepFailed, delt, finishedTrying)
 @ brief Reset time step because failure has occurred More...
 
subroutine, public ats_set_endofperiod (kper, pertim, perlencurrent, endofperiod)
 @ brief Set end of period indicator More...
 

Variables

integer(i4b), pointer nper => null()
 set equal to nper More...
 
integer(i4b), pointer maxats => null()
 number of ats entries More...
 
real(dp), pointer, public dtstable => null()
 delt value required for stability More...
 
integer(i4b), dimension(:), pointer, contiguous kperats => null()
 array of stress period numbers to apply ats (size NPER) More...
 
integer(i4b), dimension(:), pointer, contiguous iperats => null()
 array of stress period numbers to apply ats (size MAXATS) More...
 
real(dp), dimension(:), pointer, contiguous dt0 => null()
 input array of initial time step sizes More...
 
real(dp), dimension(:), pointer, contiguous dtmin => null()
 input array of minimum time step sizes More...
 
real(dp), dimension(:), pointer, contiguous dtmax => null()
 input array of maximum time step sizes More...
 
real(dp), dimension(:), pointer, contiguous dtadj => null()
 input array of time step factors for shortening or increasing More...
 
real(dp), dimension(:), pointer, contiguous dtfailadj => null()
 input array of time step factors for shortening due to nonconvergence More...
 
type(blockparsertypeparser
 block parser for reading input file More...
 

Function/Subroutine Documentation

◆ ats_allocate_arrays()

subroutine adaptivetimestepmodule::ats_allocate_arrays

Allocate and initialize arrays for the ATS package.

Definition at line 131 of file ats.f90.

132  ! -- modules
134  ! -- local
135  integer(I4B) :: n
136  !
137  call mem_allocate(kperats, nper, 'KPERATS', 'ATS')
138  call mem_allocate(iperats, maxats, 'IPERATS', 'ATS')
139  call mem_allocate(dt0, maxats, 'DT0', 'ATS')
140  call mem_allocate(dtmin, maxats, 'DTMIN', 'ATS')
141  call mem_allocate(dtmax, maxats, 'DTMAX', 'ATS')
142  call mem_allocate(dtadj, maxats, 'DTADJ', 'ATS')
143  call mem_allocate(dtfailadj, maxats, 'DTFAILADJ', 'ATS')
144  !
145  ! -- initialize kperats
146  do n = 1, nper
147  kperats(n) = 0
148  end do
149  !
150  ! -- initialize
151  do n = 1, maxats
152  iperats(n) = 0
153  dt0(n) = dzero
154  dtmin(n) = dzero
155  dtmax(n) = dzero
156  dtadj(n) = dzero
157  dtfailadj(n) = dzero
158  end do
Here is the caller graph for this function:

◆ ats_allocate_scalars()

subroutine adaptivetimestepmodule::ats_allocate_scalars
private

Allocate and initialize scalars for the ATS package.

Definition at line 111 of file ats.f90.

112  ! -- modules
114  !
115  ! -- memory manager variables
116  call mem_allocate(nper, 'NPER', 'ATS')
117  call mem_allocate(maxats, 'MAXATS', 'ATS')
118  call mem_allocate(dtstable, 'DTSTABLE', 'ATS')
119  !
120  ! -- Initialize variables
121  nper = 0
122  maxats = 0
123  dtstable = dnodata
Here is the caller graph for this function:

◆ ats_check_timing()

subroutine adaptivetimestepmodule::ats_check_timing

Perform a check on the input data to make sure values are within required ranges.

Definition at line 386 of file ats.f90.

387  integer(I4B) :: n
388  write (iout, '(1x,a)') 'PROCESSING ATS INPUT'
389  do n = 1, maxats
390  !
391  ! -- check iperats
392  if (iperats(n) < 1) then
393  write (errmsg, '(a, i0, a, i0)') &
394  'IPERATS must be greater than zero. Found ', iperats(n), &
395  ' for ATS PERIODDATA record ', n
396  call store_error(errmsg)
397  end if
398  if (iperats(n) > nper) then
399  write (warnmsg, '(a, i0, a, i0)') &
400  'IPERATS greater than NPER. Found ', iperats(n), &
401  ' for ATS PERIODDATA record ', n
402  call store_warning(warnmsg)
403  end if
404  !
405  ! -- check dt0
406  if (dt0(n) < dzero) then
407  write (errmsg, '(a, g15.7, a, i0)') &
408  'DT0 must be >= zero. Found ', dt0(n), &
409  ' for ATS PERIODDATA record ', n
410  call store_error(errmsg)
411  end if
412  !
413  ! -- check dtmin
414  if (dtmin(n) <= dzero) then
415  write (errmsg, '(a, g15.7, a, i0)') &
416  'DTMIN must be > zero. Found ', dtmin(n), &
417  ' for ATS PERIODDATA record ', n
418  call store_error(errmsg)
419  end if
420  !
421  ! -- check dtmax
422  if (dtmax(n) <= dzero) then
423  write (errmsg, '(a, g15.7, a, i0)') &
424  'DTMAX must be > zero. Found ', dtmax(n), &
425  ' for ATS PERIODDATA record ', n
426  call store_error(errmsg)
427  end if
428  !
429  ! -- check dtmin <= dtmax
430  if (dtmin(n) > dtmax(n)) then
431  write (errmsg, '(a, 2g15.7, a, i0)') &
432  'DTMIN must be < dtmax. Found ', dtmin(n), dtmax(n), &
433  ' for ATS PERIODDATA record ', n
434  call store_error(errmsg)
435  end if
436  !
437  ! -- check dtadj
438  if (dtadj(n) .ne. dzero .and. dtadj(n) < done) then
439  write (errmsg, '(a, g15.7, a, i0)') &
440  'DTADJ must be 0 or >= 1.0. Found ', dtadj(n), &
441  ' for ATS PERIODDATA record ', n
442  call store_error(errmsg)
443  end if
444  !
445  ! -- check dtfailadj
446  if (dtfailadj(n) .ne. dzero .and. dtfailadj(n) < done) then
447  write (errmsg, '(a, g15.7, a, i0)') &
448  'DTFAILADJ must be 0 or >= 1.0. Found ', dtfailadj(n), &
449  ' for ATS PERIODDATA record ', n
450  call store_error(errmsg)
451  end if
452 
453  end do
454  !
455  ! -- Check for errors
456  if (count_errors() > 0) then
457  call parser%StoreErrorUnit()
458  end if
459  write (iout, '(1x,a)') 'DONE PROCESSING ATS INPUT'
Here is the call graph for this function:
Here is the caller graph for this function:

◆ ats_cr()

subroutine, public adaptivetimestepmodule::ats_cr ( integer(i4b), intent(in)  inunit,
integer(i4b), intent(in)  nper_tdis 
)

Create a new ATS object, and read and check input.

Definition at line 60 of file ats.f90.

61  ! -- modules
62  ! -- dummy
63  integer(I4B), intent(in) :: inunit
64  integer(I4B), intent(in) :: nper_tdis
65  ! -- local
66  ! -- formats
67  character(len=*), parameter :: fmtheader = &
68  "(1X,/1X,'ATS -- ADAPTIVE TIME STEP PACKAGE,', / &
69  &' VERSION 1 : 03/18/2021 - INPUT READ FROM UNIT ',I0)"
70  !
71  ! -- Allocate the scalar variables
72  call ats_allocate_scalars()
73  !
74  ! -- Identify package
75  write (iout, fmtheader) inunit
76  !
77  ! -- Initialize block parser
78  call parser%initialize(inunit, iout)
79  !
80  ! -- Read options
81  call ats_read_options()
82  !
83  ! -- store tdis nper in nper
84  nper = nper_tdis
85  !
86  ! -- Read dimensions and then allocate arrays
87  call ats_read_dimensions()
88  call ats_allocate_arrays()
89  !
90  ! -- Read timing
91  call ats_read_timing()
92  !
93  ! -- Echo input data to table
94  call ats_input_table()
95  !
96  ! -- Check timing
97  call ats_check_timing()
98  !
99  ! -- Process input
100  call ats_process_input()
101  !
102  ! -- Close the file
103  call parser%Clear()
Here is the call graph for this function:
Here is the caller graph for this function:

◆ ats_da()

subroutine, public adaptivetimestepmodule::ats_da

Deallocate all ATS variables.

Definition at line 166 of file ats.f90.

168  !
169  ! -- Scalars
170  call mem_deallocate(nper)
171  call mem_deallocate(maxats)
172  call mem_deallocate(dtstable)
173  !
174  ! -- Arrays
175  call mem_deallocate(kperats)
176  call mem_deallocate(iperats)
177  call mem_deallocate(dt0)
178  call mem_deallocate(dtmin)
179  call mem_deallocate(dtmax)
180  call mem_deallocate(dtadj)
181  call mem_deallocate(dtfailadj)
Here is the caller graph for this function:

◆ ats_input_table()

subroutine adaptivetimestepmodule::ats_input_table
private

Write a table showing the ATS input read from the perioddata block.

Definition at line 337 of file ats.f90.

338  use tablemodule, only: tabletype, table_cr
339  integer(I4B) :: n
340  character(len=LINELENGTH) :: tag
341  type(TableType), pointer :: inputtab => null()
342  !
343  ! -- setup table
344  call table_cr(inputtab, 'ATS', 'ATS PERIOD DATA')
345  call inputtab%table_df(maxats, 7, iout)
346  !
347  ! add columns
348  tag = 'RECORD'
349  call inputtab%initialize_column(tag, 10, alignment=tableft)
350  tag = 'IPERATS'
351  call inputtab%initialize_column(tag, 10, alignment=tableft)
352  tag = 'DT0'
353  call inputtab%initialize_column(tag, 10, alignment=tabcenter)
354  tag = 'DTMIN'
355  call inputtab%initialize_column(tag, 10, alignment=tabcenter)
356  tag = 'DTMAX'
357  call inputtab%initialize_column(tag, 10, alignment=tabcenter)
358  tag = 'DTADJ'
359  call inputtab%initialize_column(tag, 10, alignment=tabcenter)
360  tag = 'DTFAILADJ'
361  call inputtab%initialize_column(tag, 10, alignment=tabcenter)
362  !
363  ! -- write the data
364  do n = 1, maxats
365  call inputtab%add_term(n)
366  call inputtab%add_term(iperats(n))
367  call inputtab%add_term(dt0(n))
368  call inputtab%add_term(dtmin(n))
369  call inputtab%add_term(dtmax(n))
370  call inputtab%add_term(dtadj(n))
371  call inputtab%add_term(dtfailadj(n))
372  end do
373  !
374  ! -- deallocate the table
375  call inputtab%table_da()
376  deallocate (inputtab)
377  nullify (inputtab)
subroutine, public table_cr(this, name, title)
Definition: Table.f90:87
Here is the call graph for this function:
Here is the caller graph for this function:

◆ ats_period_message()

subroutine, public adaptivetimestepmodule::ats_period_message ( integer(i4b), intent(in)  kper)

Write message to mfsim.lst file with information on ATS settings for this period.

Definition at line 468 of file ats.f90.

469  ! -- dummy
470  integer(I4B), intent(in) :: kper
471  ! -- local
472  integer(I4B) :: n
473  character(len=*), parameter :: fmtspts = &
474  "(28X,'ATS IS OVERRIDING TIME STEPPING FOR THIS PERIOD',/ &
475  &28X,'INITIAL TIME STEP SIZE (DT0) = ',G15.7,/ &
476  &28X,'MINIMUM TIME STEP SIZE (DTMIN) = ',G15.7,/ &
477  &28X,'MAXIMUM TIME STEP SIZE (DTMAX) = ',G15.7,/ &
478  &28X,'MULTIPLIER/DIVIDER FOR TIME STEP (DTADJ) = ',G15.7,/ &
479  &28X,'DIVIDER FOR FAILED TIME STEP (DTFAILADJ) = ',G15.7,/ &
480  &)"
481  n = kperats(kper)
482  write (iout, fmtspts) dt0(n), dtmin(n), dtmax(n), dtadj(n), dtfailadj(n)
Here is the caller graph for this function:

◆ ats_process_input()

subroutine adaptivetimestepmodule::ats_process_input
private

Process ATS input by filling the kperats array.

Definition at line 319 of file ats.f90.

320  integer(I4B) :: kkper
321  integer(I4B) :: n
322  !
323  ! -- fill kperats for valid iperats values
324  do n = 1, maxats
325  kkper = iperats(n)
326  if (kkper > 0 .and. kkper <= nper) then
327  kperats(kkper) = n
328  end if
329  end do
Here is the caller graph for this function:

◆ ats_read_dimensions()

subroutine adaptivetimestepmodule::ats_read_dimensions
private

Read dimensions from ATS input file.

Definition at line 225 of file ats.f90.

226  ! -- dummy
227  ! -- local
228  character(len=LINELENGTH) :: keyword
229  integer(I4B) :: ierr
230  logical :: isfound, endOfBlock
231  ! -- formats
232  character(len=*), parameter :: fmtmaxats = &
233  &"(1X,I0,' ADAPTIVE TIME STEP RECORDS(S) WILL FOLLOW IN PERIODDATA')"
234  !
235  ! -- get DIMENSIONS block
236  call parser%GetBlock('DIMENSIONS', isfound, ierr, &
237  supportopenclose=.true.)
238  !
239  ! -- parse block if detected
240  if (isfound) then
241  write (iout, '(1x,a)') 'PROCESSING ATS DIMENSIONS'
242  do
243  call parser%GetNextLine(endofblock)
244  if (endofblock) exit
245  call parser%GetStringCaps(keyword)
246  select case (keyword)
247  case ('MAXATS')
248  maxats = parser%GetInteger()
249  write (iout, fmtmaxats) maxats
250  case default
251  write (errmsg, '(a,a)') 'Unknown ATS dimension: ', &
252  trim(keyword)
253  call store_error(errmsg)
254  call parser%StoreErrorUnit()
255  end select
256  end do
257  write (iout, '(1x,a)') 'END OF ATS DIMENSIONS'
258  else
259  write (errmsg, '(a)') 'Required DIMENSIONS block not found.'
260  call store_error(errmsg)
261  call parser%StoreErrorUnit()
262  end if
Here is the call graph for this function:
Here is the caller graph for this function:

◆ ats_read_options()

subroutine adaptivetimestepmodule::ats_read_options

Read options from ATS input file.

Definition at line 189 of file ats.f90.

190  ! -- dummy
191  ! -- local
192  character(len=LINELENGTH) :: keyword
193  integer(I4B) :: ierr
194  logical :: isfound, endOfBlock
195  ! -- formats
196  !
197  ! -- get options block
198  call parser%GetBlock('OPTIONS', isfound, ierr, &
199  supportopenclose=.true., blockrequired=.false.)
200  !
201  ! -- parse options block if detected
202  if (isfound) then
203  write (iout, '(1x,a)') 'PROCESSING ATS OPTIONS'
204  do
205  call parser%GetNextLine(endofblock)
206  if (endofblock) exit
207  call parser%GetStringCaps(keyword)
208  select case (keyword)
209  case default
210  write (errmsg, '(a,a)') 'Unknown ATS option: ', &
211  trim(keyword)
212  call store_error(errmsg)
213  call parser%StoreErrorUnit()
214  end select
215  end do
216  write (iout, '(1x,a)') 'END OF ATS OPTIONS'
217  end if
Here is the call graph for this function:
Here is the caller graph for this function:

◆ ats_read_timing()

subroutine adaptivetimestepmodule::ats_read_timing
private

Read timing information from ATS input file.

Definition at line 270 of file ats.f90.

271  ! -- modules
272  ! -- dummy
273  ! -- local
274  integer(I4B) :: ierr
275  integer(I4B) :: n
276  logical :: isfound, endOfBlock
277  ! -- formats
278  !
279  ! -- get PERIODDATA block
280  call parser%GetBlock('PERIODDATA', isfound, ierr, &
281  supportopenclose=.true.)
282  !
283  ! -- parse block if detected
284  if (isfound) then
285  write (iout, '(1x,a)') 'READING ATS PERIODDATA'
286  do n = 1, maxats
287  call parser%GetNextLine(endofblock)
288  if (endofblock) exit
289  !
290  ! -- fill the ats data arrays
291  iperats(n) = parser%GetInteger()
292  dt0(n) = parser%GetDouble()
293  dtmin(n) = parser%GetDouble()
294  dtmax(n) = parser%GetDouble()
295  dtadj(n) = parser%GetDouble()
296  dtfailadj(n) = parser%GetDouble()
297  end do
298  !
299  ! -- Close the block
300  call parser%terminateblock()
301  !
302  ! -- Check for errors
303  if (count_errors() > 0) then
304  call parser%StoreErrorUnit()
305  end if
306  write (iout, '(1x,a)') 'END READING ATS PERIODDATA'
307  else
308  write (errmsg, '(a)') 'Required PERIODDATA block not found.'
309  call store_error(errmsg)
310  call parser%StoreErrorUnit()
311  end if
Here is the call graph for this function:
Here is the caller graph for this function:

◆ ats_reset_delt()

subroutine, public adaptivetimestepmodule::ats_reset_delt ( integer(i4b), intent(in)  kstp,
integer(i4b), intent(in)  kper,
integer(i4b), intent(in)  lastStepFailed,
real(dp), intent(inout)  delt,
logical, intent(inout)  finishedTrying 
)

Reset the time step using dtfailadj because the time step did not converge.

Definition at line 605 of file ats.f90.

606  ! -- modules
607  ! -- dummy
608  integer(I4B), intent(in) :: kstp
609  integer(I4B), intent(in) :: kper
610  integer(I4B), intent(in) :: lastStepFailed
611  real(DP), intent(inout) :: delt
612  logical, intent(inout) :: finishedTrying
613  ! -- local
614  integer(I4B) :: n
615  real(DP) :: delt_temp
616  real(DP) :: tsfact
617  ! -- formats
618  character(len=*), parameter :: fmttsi = &
619  "(1X, 'Failed solution for step ', i0, ' and period ', i0, &
620  &' will be retried using time step of ', G15.7)"
621  if (isadaptiveperiod(kper)) then
622  if (laststepfailed /= 0) then
623  delt_temp = delt
624  n = kperats(kper)
625  tsfact = dtfailadj(n)
626  if (tsfact > done) then
627  delt_temp = delt / tsfact
628  if (delt_temp >= dtmin(n)) then
629  finishedtrying = .false.
630  delt = delt_temp
631  write (iout, fmttsi) kstp, kper, delt
632  end if
633  end if
634 
635  end if
636  end if
Here is the call graph for this function:
Here is the caller graph for this function:

◆ ats_set_delt()

subroutine, public adaptivetimestepmodule::ats_set_delt ( integer(i4b), intent(in)  kstp,
integer(i4b), intent(in)  kper,
real(dp), intent(inout)  pertim,
real(dp), intent(in)  perlencurrent,
real(dp), intent(inout)  delt 
)

Set the time step length (delt) for this time step using the ATS controls.

Definition at line 540 of file ats.f90.

541  ! -- modules
542  ! -- dummy
543  integer(I4B), intent(in) :: kstp
544  integer(I4B), intent(in) :: kper
545  real(DP), intent(inout) :: pertim
546  real(DP), intent(in) :: perlencurrent
547  real(DP), intent(inout) :: delt
548  ! -- local
549  integer(I4B) :: n
550  real(DP) :: tstart
551  ! -- formats
552  character(len=*), parameter :: fmtdt = &
553  "(1x, 'ATS: time step set to ', G15.7, ' for step ', i0, &
554  &' and period ', i0)"
555  !
556  ! -- initialize the record position (n) for this stress period
557  n = kperats(kper)
558  !
559  ! -- set tstart to the end of the last time step.
560  tstart = pertim
561  !
562  ! -- Calculate delt
563  !
564  ! -- Setup new stress period if kstp is 1
565  if (kstp == 1) then
566  !
567  ! -- Assign first value of delt for this stress period
568  if (dt0(n) /= dzero) then
569  delt = dt0(n)
570  else
571  ! leave delt the way it was
572  end if
573  else
574  !
575  ! -- Assign delt based on stability
576  if (dtstable /= dnodata) then
577  delt = dtstable
578  dtstable = dnodata
579  end if
580  end if
581  !
582  ! -- Ensure tsmin < delt < tsmax
583  if (delt < dtmin(n)) then
584  delt = dtmin(n)
585  end if
586  if (delt > dtmax(n)) then
587  delt = dtmax(n)
588  end if
589  !
590  ! -- Cut timestep down to meet end of period
591  if (tstart + delt > perlencurrent - dtmin(n)) then
592  delt = perlencurrent - tstart
593  end if
594  !
595  ! -- Write time step size information
596  write (iout, fmtdt) delt, kstp, kper
Here is the caller graph for this function:

◆ ats_set_endofperiod()

subroutine, public adaptivetimestepmodule::ats_set_endofperiod ( integer(i4b), intent(in)  kper,
real(dp), intent(inout)  pertim,
real(dp), intent(in)  perlencurrent,
logical(lgp), intent(inout)  endofperiod 
)

Determine if it is the end of the stress period and set the endofperiod logical variable if so.

Definition at line 645 of file ats.f90.

646  integer(I4B), intent(in) :: kper
647  real(DP), intent(inout) :: pertim
648  real(DP), intent(in) :: perlencurrent
649  logical(LGP), intent(inout) :: endofperiod
650  ! -- local
651  integer(I4B) :: n
652  !
653  ! -- End of stress period and/or simulation?
654  n = kperats(kper)
655  if (abs(pertim - perlencurrent) < dtmin(n)) then
656  endofperiod = .true.
657  end if
Here is the caller graph for this function:

◆ ats_submit_delt()

subroutine, public adaptivetimestepmodule::ats_submit_delt ( integer(i4b), intent(in)  kstp,
integer(i4b), intent(in)  kper,
real(dp), intent(in)  dt,
character(len=*), intent(in)  sloc,
integer(i4b), intent(in), optional  idir 
)

Submit a preferred time step length. Alternatively, if idir is is passed, then either increase or decrease the submitted time step by the dtadj input variable.

Definition at line 492 of file ats.f90.

493  integer(I4B), intent(in) :: kstp
494  integer(I4B), intent(in) :: kper
495  real(DP), intent(in) :: dt
496  character(len=*), intent(in) :: sloc
497  integer(I4B), intent(in), optional :: idir
498  ! -- local
499  integer(I4B) :: n
500  real(DP) :: tsfact
501  real(DP) :: dt_temp
502  character(len=*), parameter :: fmtdtsubmit = &
503  &"(1x, 'ATS: ', A,' submitted a preferred time step size of ', G15.7)"
504 
505  if (isadaptiveperiod(kper)) then
506  n = kperats(kper)
507  tsfact = dtadj(n)
508  if (tsfact > done) then
509  !
510  ! -- if idir is present, then dt is a length that should be adjusted
511  ! (divided by or multiplied by) by dtadj. If idir is not present
512  ! then dt is the submitted time step.
513  if (present(idir)) then
514  dt_temp = dzero
515  if (idir == -1) then
516  dt_temp = dt / tsfact
517  else if (idir == 1) then
518  dt_temp = dt * tsfact
519  end if
520  else
521  dt_temp = dt
522  end if
523  if (kstp > 1 .and. dt_temp > dzero) then
524  write (iout, fmtdtsubmit) trim(adjustl(sloc)), dt_temp
525  end if
526  if (dt_temp > dzero .and. dt_temp < dtstable) then
527  ! -- Reset dtstable to a smaller value
528  dtstable = dt_temp
529  end if
530  end if
531  end if
Here is the call graph for this function:
Here is the caller graph for this function:

◆ isadaptiveperiod()

logical(lgp) function, public adaptivetimestepmodule::isadaptiveperiod ( integer(i4b), intent(in)  kper)

Check settings and determine if kper is an adaptive stress period.

Definition at line 44 of file ats.f90.

45  integer(I4B), intent(in) :: kper
46  logical(LGP) :: lv
47  lv = .false.
48  if (associated(kperats)) then
49  if (kperats(kper) > 0) then
50  lv = .true.
51  end if
52  end if
Here is the caller graph for this function:

Variable Documentation

◆ dt0

real(dp), dimension(:), pointer, contiguous adaptivetimestepmodule::dt0 => null()
private

Definition at line 29 of file ats.f90.

29  real(DP), dimension(:), pointer, contiguous :: dt0 => null() !< input array of initial time step sizes

◆ dtadj

real(dp), dimension(:), pointer, contiguous adaptivetimestepmodule::dtadj => null()
private

Definition at line 32 of file ats.f90.

32  real(DP), dimension(:), pointer, contiguous :: dtadj => null() !< input array of time step factors for shortening or increasing

◆ dtfailadj

real(dp), dimension(:), pointer, contiguous adaptivetimestepmodule::dtfailadj => null()
private

Definition at line 33 of file ats.f90.

33  real(DP), dimension(:), pointer, contiguous :: dtfailadj => null() !< input array of time step factors for shortening due to nonconvergence

◆ dtmax

real(dp), dimension(:), pointer, contiguous adaptivetimestepmodule::dtmax => null()
private

Definition at line 31 of file ats.f90.

31  real(DP), dimension(:), pointer, contiguous :: dtmax => null() !< input array of maximum time step sizes

◆ dtmin

real(dp), dimension(:), pointer, contiguous adaptivetimestepmodule::dtmin => null()
private

Definition at line 30 of file ats.f90.

30  real(DP), dimension(:), pointer, contiguous :: dtmin => null() !< input array of minimum time step sizes

◆ dtstable

real(dp), pointer, public adaptivetimestepmodule::dtstable => null()

Definition at line 26 of file ats.f90.

26  real(DP), public, pointer :: dtstable => null() !< delt value required for stability

◆ iperats

integer(i4b), dimension(:), pointer, contiguous adaptivetimestepmodule::iperats => null()
private

Definition at line 28 of file ats.f90.

28  integer(I4B), dimension(:), pointer, contiguous :: iperats => null() !< array of stress period numbers to apply ats (size MAXATS)

◆ kperats

integer(i4b), dimension(:), pointer, contiguous adaptivetimestepmodule::kperats => null()
private

Definition at line 27 of file ats.f90.

27  integer(I4B), dimension(:), pointer, contiguous :: kperats => null() !< array of stress period numbers to apply ats (size NPER)

◆ maxats

integer(i4b), pointer adaptivetimestepmodule::maxats => null()
private

Definition at line 25 of file ats.f90.

25  integer(I4B), pointer :: maxats => null() !< number of ats entries

◆ nper

integer(i4b), pointer adaptivetimestepmodule::nper => null()
private

Definition at line 24 of file ats.f90.

24  integer(I4B), pointer :: nper => null() !< set equal to nper

◆ parser

type(blockparsertype) adaptivetimestepmodule::parser
private

Definition at line 34 of file ats.f90.

34  type(BlockParserType) :: parser !< block parser for reading input file