MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
TimeStepSelect.f90
Go to the documentation of this file.
1 !> @brief Time step selection module.
3 
4  use kindmodule, only: dp, i4b, lgp
6  use simvariablesmodule, only: errmsg
7  use simmodule, only: store_error
8  use inputoutputmodule, only: urword
9 
10  implicit none
11  private
12  public :: timestepselecttype
13 
14  !> @brief Time step selection type.
15  !!
16  !! Represents a selection of time steps as configured in an input file's
17  !! period block settings. The object should be initiated with the init()
18  !! procedure. The read() procedure accepts a character string of form:
19  !!
20  !! ALL
21  !! STEPS 1 4 5 6
22  !! FIRST
23  !! LAST
24  !! FREQUENCY 4
25  !!
26  !! The read() procedure may be invoked multiple times to select multiple
27  !! time steps. Note that a character string re-using a keyword which has
28  !! been used for a previous read() invocation will override the previous
29  !! setting using that keyword. To combine multiple settings, be sure the
30  !! keywords are different on each invocation, e.g.:
31  !!
32  !! FIRST
33  !! LAST
34  !! STEPS 2
35  !!
36  !! The is_selected() function indicates whether the given time step is
37  !! active. This function accepts an optional argument, indicating that
38  !! the time step is the last in the stress period.
39  !<
41  logical(LGP) :: all
42  logical(LGP) :: first
43  logical(LGP) :: last
44  integer(I4B) :: freq
45  integer(I4B), allocatable :: steps(:)
46  contains
47  procedure :: deallocate
48  procedure :: init
49  procedure :: log
50  procedure :: read
51  procedure :: is_selected
52  procedure :: any
53  end type timestepselecttype
54 
55 contains
56 
57  !> @brief Deallocate the time step selection object.
58  subroutine deallocate (this)
59  class(timestepselecttype) :: this
60  deallocate (this%steps)
61  end subroutine deallocate
62 
63  !> @brief Initialize the time step selection object.
64  subroutine init(this)
65  class(timestepselecttype) :: this !< this instance
66 
67  if (allocated(this%steps)) deallocate (this%steps)
68  allocate (this%steps(0))
69  this%freq = 0
70  this%first = .false.
71  this%last = .false.
72  this%all = .false.
73  end subroutine init
74 
75  subroutine log(this, iout, verb)
76  ! dummy
77  class(timestepselecttype) :: this !< this instance
78  integer(I4B), intent(in) :: iout !< output unit
79  character(len=*), intent(in) :: verb !< selection name
80  ! formats
81  character(len=*), parameter :: fmt_steps = &
82  &"(6x,'THE FOLLOWING STEPS WILL BE ',A,': ',50(I0,' '))"
83  character(len=*), parameter :: fmt_freq = &
84  &"(6x,'THE FOLLOWING FREQUENCY WILL BE ',A,': ',I0)"
85 
86  if (this%all) then
87  write (iout, "(6x,a,a)") 'ALL TIME STEPS WILL BE ', verb
88  end if
89  if (size(this%steps) > 0) then
90  write (iout, fmt_steps) verb, this%steps
91  end if
92  if (this%freq > 0) then
93  write (iout, fmt_freq) verb, this%freq
94  end if
95  if (this%first) then
96  write (iout, "(6x,a,a)") 'THE FIRST TIME STEP WILL BE ', verb
97  end if
98  if (this%last) then
99  write (iout, "(6x,a,a)") 'THE LAST TIME STEP WILL BE ', verb
100  end if
101  end subroutine log
102 
103  !> @brief Read a line of input and prepare the selection object.
104  subroutine read (this, line)
105  class(timestepselecttype) :: this !< this instance
106  character(len=*), intent(in) :: line !< input line
107 
108  character(len=len(line)) :: l
109  integer(I4B) :: n, lloc, istart, istop, ival
110  real(DP) :: rval
111 
112  l(:) = line(:)
113  lloc = 1
114 
115  call urword(l, lloc, istart, istop, 1, ival, rval, 0, 0)
116  select case (l(istart:istop))
117  case ('ALL')
118  this%all = .true.
119  case ('STEPS')
120  listsearch: do
121  call urword(l, lloc, istart, istop, 2, ival, rval, -1, 0)
122  if (ival > 0) then
123  n = size(this%steps)
124  call expandarray(this%steps)
125  this%steps(n + 1) = ival
126  cycle listsearch
127  end if
128  exit listsearch
129  end do listsearch
130  case ('FREQUENCY')
131  call urword(l, lloc, istart, istop, 2, ival, rval, -1, 0)
132  this%freq = ival
133  case ('FIRST')
134  this%first = .true.
135  case ('LAST')
136  this%last = .true.
137  case default
138  write (errmsg, '(2a)') &
139  'Looking for ALL, STEPS, FIRST, LAST, OR FREQUENCY. Found: ', &
140  trim(adjustl(line))
141  call store_error(errmsg, terminate=.true.)
142  end select
143  end subroutine read
144 
145  !> @brief Indicates whether the given time step is selected.
146  logical function is_selected(this, kstp, endofperiod)
147  ! dummy
148  class(timestepselecttype) :: this !< this instance
149  integer(I4B), intent(in) :: kstp !< current time step
150  logical(LGP), intent(in), optional :: endofperiod !< whether last step of stress period
151  ! local
152  integer(I4B) :: i, n
153  logical(LGP) :: lend
154 
155  if (present(endofperiod)) then
156  lend = endofperiod
157  else
158  lend = .false.
159  end if
160 
161  is_selected = .false.
162  if (this%all) is_selected = .true.
163  if (kstp == 1 .and. this%first) is_selected = .true.
164  if (lend .and. this%last) is_selected = .true.
165  if (this%freq > 0) then
166  if (mod(kstp, this%freq) == 0) is_selected = .true.
167  end if
168  n = size(this%steps)
169  if (n > 0) then
170  do i = 1, n
171  if (kstp == this%steps(i)) then
172  is_selected = .true.
173  exit
174  end if
175  end do
176  end if
177  end function is_selected
178 
179  !> @brief Indicates whether any time steps are selected.
180  logical function any(this) result(a)
181  class(timestepselecttype) :: this !< this instance
182  a = (this%all .or. &
183  this%first .or. &
184  this%last .or. &
185  this%freq > 0 .or. &
186  size(this%steps) > 0)
187  end function any
188 
189 end module timestepselectmodule
subroutine init()
Definition: GridSorting.f90:24
subroutine, public urword(line, icol, istart, istop, ncode, n, r, iout, in)
Extract a word from a string.
This module defines variable data types.
Definition: kind.f90:8
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
This module contains simulation variables.
Definition: SimVariables.f90:9
character(len=maxcharlen) errmsg
error message string
Time step selection module.
subroutine deallocate(this)
Deallocate the time step selection object.
subroutine read(this, line)
Read a line of input and prepare the selection object.
logical function is_selected(this, kstp, endofperiod)
Indicates whether the given time step is selected.
logical function any(this)
Indicates whether any time steps are selected.
subroutine log(this, iout, verb)