24 integer(I4B),
pointer ::
nper => null()
25 integer(I4B),
pointer ::
maxats => null()
26 real(dp),
public,
pointer ::
dtstable => null()
27 integer(I4B),
dimension(:),
pointer,
contiguous ::
kperats => null()
28 integer(I4B),
dimension(:),
pointer,
contiguous ::
iperats => null()
29 real(dp),
dimension(:),
pointer,
contiguous ::
dt0 => null()
30 real(dp),
dimension(:),
pointer,
contiguous ::
dtmin => null()
31 real(dp),
dimension(:),
pointer,
contiguous ::
dtmax => null()
32 real(dp),
dimension(:),
pointer,
contiguous ::
dtadj => null()
33 real(dp),
dimension(:),
pointer,
contiguous ::
dtfailadj => null()
45 integer(I4B),
intent(in) :: kper
63 integer(I4B),
intent(in) :: inunit
64 integer(I4B),
intent(in) :: nper_tdis
67 character(len=*),
parameter :: fmtheader = &
68 "(1X,/1X,'ATS -- ADAPTIVE TIME STEP PACKAGE,', / &
69 &' VERSION 1 : 03/18/2021 - INPUT READ FROM UNIT ',I0)"
75 write (
iout, fmtheader) inunit
192 character(len=LINELENGTH) :: keyword
194 logical :: isfound, endOfBlock
198 call parser%GetBlock(
'OPTIONS', isfound, ierr, &
199 supportopenclose=.true., blockrequired=.false.)
203 write (
iout,
'(1x,a)')
'PROCESSING ATS OPTIONS'
205 call parser%GetNextLine(endofblock)
207 call parser%GetStringCaps(keyword)
208 select case (keyword)
210 write (
errmsg,
'(a,a)')
'Unknown ATS option: ', &
213 call parser%StoreErrorUnit()
216 write (
iout,
'(1x,a)')
'END OF ATS OPTIONS'
228 character(len=LINELENGTH) :: keyword
230 logical :: isfound, endOfBlock
232 character(len=*),
parameter :: fmtmaxats = &
233 &
"(1X,I0,' ADAPTIVE TIME STEP RECORDS(S) WILL FOLLOW IN PERIODDATA')"
236 call parser%GetBlock(
'DIMENSIONS', isfound, ierr, &
237 supportopenclose=.true.)
241 write (
iout,
'(1x,a)')
'PROCESSING ATS DIMENSIONS'
243 call parser%GetNextLine(endofblock)
245 call parser%GetStringCaps(keyword)
246 select case (keyword)
251 write (
errmsg,
'(a,a)')
'Unknown ATS dimension: ', &
254 call parser%StoreErrorUnit()
257 write (
iout,
'(1x,a)')
'END OF ATS DIMENSIONS'
259 write (
errmsg,
'(a)')
'Required DIMENSIONS block not found.'
261 call parser%StoreErrorUnit()
276 logical :: isfound, endOfBlock
280 call parser%GetBlock(
'PERIODDATA', isfound, ierr, &
281 supportopenclose=.true.)
285 write (
iout,
'(1x,a)')
'READING ATS PERIODDATA'
287 call parser%GetNextLine(endofblock)
300 call parser%terminateblock()
304 call parser%StoreErrorUnit()
306 write (
iout,
'(1x,a)')
'END READING ATS PERIODDATA'
308 write (
errmsg,
'(a)')
'Required PERIODDATA block not found.'
310 call parser%StoreErrorUnit()
320 integer(I4B) :: kkper
326 if (kkper > 0 .and. kkper <=
nper)
then
340 character(len=LINELENGTH) :: tag
341 type(
tabletype),
pointer :: inputtab => null()
344 call table_cr(inputtab,
'ATS',
'ATS PERIOD DATA')
349 call inputtab%initialize_column(tag, 10, alignment=
tableft)
351 call inputtab%initialize_column(tag, 10, alignment=
tableft)
353 call inputtab%initialize_column(tag, 10, alignment=
tabcenter)
355 call inputtab%initialize_column(tag, 10, alignment=
tabcenter)
357 call inputtab%initialize_column(tag, 10, alignment=
tabcenter)
359 call inputtab%initialize_column(tag, 10, alignment=
tabcenter)
361 call inputtab%initialize_column(tag, 10, alignment=
tabcenter)
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))
375 call inputtab%table_da()
376 deallocate (inputtab)
388 write (
iout,
'(1x,a)')
'PROCESSING ATS INPUT'
393 write (
errmsg,
'(a, i0, a, i0)') &
394 'IPERATS must be greater than zero. Found ',
iperats(n), &
395 ' for ATS PERIODDATA record ', n
399 write (
warnmsg,
'(a, i0, a, i0)') &
400 'IPERATS greater than NPER. Found ',
iperats(n), &
401 ' for ATS PERIODDATA record ', n
407 write (
errmsg,
'(a, g15.7, a, i0)') &
408 'DT0 must be >= zero. Found ',
dt0(n), &
409 ' for ATS PERIODDATA record ', n
415 write (
errmsg,
'(a, g15.7, a, i0)') &
416 'DTMIN must be > zero. Found ',
dtmin(n), &
417 ' for ATS PERIODDATA record ', n
423 write (
errmsg,
'(a, g15.7, a, i0)') &
424 'DTMAX must be > zero. Found ',
dtmax(n), &
425 ' for ATS PERIODDATA record ', n
431 write (
errmsg,
'(a, 2g15.7, a, i0)') &
432 'DTMIN must be < dtmax. Found ',
dtmin(n),
dtmax(n), &
433 ' for ATS PERIODDATA record ', n
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
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
457 call parser%StoreErrorUnit()
459 write (
iout,
'(1x,a)')
'DONE PROCESSING ATS INPUT'
470 integer(I4B),
intent(in) :: kper
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,/ &
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
502 character(len=*),
parameter :: fmtdtsubmit = &
503 &
"(1x, 'ATS: ', A,' submitted a preferred time step size of ', G15.7)"
508 if (tsfact >
done)
then
513 if (
present(idir))
then
516 dt_temp = dt / tsfact
517 else if (idir == 1)
then
518 dt_temp = dt * tsfact
523 if (kstp > 1 .and. dt_temp >
dzero)
then
524 write (
iout, fmtdtsubmit) trim(adjustl(sloc)), dt_temp
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
552 character(len=*),
parameter :: fmtdt = &
553 "(1x, 'ATS: time step set to ', G15.7, ' for step ', i0, &
554 &' and period ', i0)"
583 if (delt <
dtmin(n))
then
586 if (delt >
dtmax(n))
then
591 if (tstart + delt > perlencurrent -
dtmin(n))
then
592 delt = perlencurrent - tstart
596 write (
iout, fmtdt) delt, kstp, kper
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
615 real(dp) :: delt_temp
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)"
622 if (laststepfailed /= 0)
then
626 if (tsfact >
done)
then
627 delt_temp = delt / tsfact
628 if (delt_temp >=
dtmin(n))
then
629 finishedtrying = .false.
631 write (
iout, fmttsi) kstp, kper, delt
646 integer(I4B),
intent(in) :: kper
647 real(dp),
intent(inout) :: pertim
648 real(dp),
intent(in) :: perlencurrent
649 logical(LGP),
intent(inout) :: endofperiod
655 if (abs(pertim - perlencurrent) <
dtmin(n))
then
subroutine ats_read_timing()
@ brief Read timing
subroutine, public ats_set_delt(kstp, kper, pertim, perlencurrent, delt)
@ brief Set time step
subroutine ats_allocate_arrays()
@ brief Allocate arrays
subroutine, public ats_cr(inunit, nper_tdis)
@ brief Create ATS object
subroutine, public ats_set_endofperiod(kper, pertim, perlencurrent, endofperiod)
@ brief Set end of period indicator
real(dp), dimension(:), pointer, contiguous dtfailadj
input array of time step factors for shortening due to nonconvergence
real(dp), dimension(:), pointer, contiguous dtmin
input array of minimum time step sizes
subroutine ats_input_table()
@ brief Write input table
real(dp), dimension(:), pointer, contiguous dtmax
input array of maximum time step sizes
subroutine ats_check_timing()
@ brief Check timing
integer(i4b), pointer nper
set equal to nper
logical(lgp) function, public isadaptiveperiod(kper)
@ brief Determine if period is adaptive
real(dp), pointer, public dtstable
delt value required for stability
integer(i4b), dimension(:), pointer, contiguous kperats
array of stress period numbers to apply ats (size NPER)
integer(i4b), pointer maxats
number of ats entries
subroutine, public ats_da()
@ brief Deallocate variables
subroutine, public ats_reset_delt(kstp, kper, lastStepFailed, delt, finishedTrying)
@ brief Reset time step because failure has occurred
subroutine ats_read_dimensions()
@ brief Read dimensions
subroutine ats_process_input()
@ brief Process input
subroutine, public ats_submit_delt(kstp, kper, dt, sloc, idir)
@ brief Allow and external caller to submit preferred time step
real(dp), dimension(:), pointer, contiguous dt0
input array of initial time step sizes
subroutine ats_allocate_scalars()
@ brief Allocate scalars
subroutine, public ats_period_message(kper)
@ brief Write period message
real(dp), dimension(:), pointer, contiguous dtadj
input array of time step factors for shortening or increasing
subroutine ats_read_options()
@ brief Read options
integer(i4b), dimension(:), pointer, contiguous iperats
array of stress period numbers to apply ats (size MAXATS)
type(blockparsertype) parser
block parser for reading input file
This module contains block parser methods.
This module contains simulation constants.
integer(i4b), parameter linelength
maximum length of a standard line
@ tabcenter
centered table column
@ tableft
left justified table column
real(dp), parameter dnodata
real no data constant
real(dp), parameter dzero
real constant zero
real(dp), parameter done
real constant 1
This module defines variable data types.
This module contains simulation methods.
subroutine, public store_warning(msg, substring)
Store warning message.
subroutine, public store_error(msg, terminate)
Store an error message.
integer(i4b) function, public count_errors()
Return number of errors.
This module contains simulation variables.
character(len=maxcharlen) errmsg
error message string
character(len=maxcharlen) warnmsg
warning message string
integer(i4b) iout
file unit number for simulation output
subroutine, public table_cr(this, name, title)