MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
ReleaseSchedule.f90
Go to the documentation of this file.
1 !> @brief Particle release scheduling.
3 
6  use kindmodule, only: i4b, lgp, dp
7  use mathutilmodule, only: is_close
10 
11  implicit none
12  private
13  public :: releasescheduletype
14  public :: create_release_schedule
15 
16  !> @brief Particle release scheduling utility.
17  !!
18  !! The release schedule composes a time selection object for any
19  !! explicitly specified release times, and a time step selection
20  !! object for release times specified in period/time step terms.
21  !!
22  !! Release time coincidence is computed within a given tolerance;
23  !! times closer than the tolerance are merged into a single time.
24  !!
25  !! The release schedule must be refreshed each time step. This is
26  !! achieved by calling `advance()`. After this, the `times` member
27  !! is a debounced/consolidated schedule for the current time step.
28  !<
30  real(dp), allocatable :: times(:) !< release times
31  real(dp) :: tolerance !< release time coincidence tolerance
32  type(timeselecttype), pointer :: time_select !< time selection
33  type(timestepselecttype), pointer :: step_select !< time step selection
34  contains
35  procedure :: advance
36  procedure :: any
37  procedure :: count
38  procedure :: deallocate
39  procedure :: log
40  procedure :: schedule
41  end type releasescheduletype
42 
43 contains
44 
45  !> @brief Create a new release schedule object.
46  function create_release_schedule(tol) result(sched)
47  real(dp), intent(in) :: tol !< coincident release time tolerance
48  type(releasescheduletype), pointer :: sched !< schedule pointer
49 
50  allocate (sched)
51  allocate (sched%times(0))
52  allocate (sched%time_select)
53  allocate (sched%step_select)
54  call sched%time_select%init()
55  call sched%step_select%init()
56  sched%tolerance = tol
57 
58  end function create_release_schedule
59 
60  !> @brief Deallocate the release schedule.
61  subroutine deallocate (this)
62  class(releasescheduletype), intent(inout) :: this !< this instance
63 
64  deallocate (this%times)
65  call this%time_select%deallocate()
66  call this%step_select%deallocate()
67  deallocate (this%time_select)
68  deallocate (this%step_select)
69 
70  end subroutine deallocate
71 
72  !> @brief Write the release schedule to the given output unit.
73  subroutine log(this, iout)
74  class(releasescheduletype), intent(inout) :: this !< this instance
75  integer(I4B), intent(in) :: iout !< output unit
76  character(len=*), parameter :: fmt = &
77  &"(6x,A,': ',50(G0,' '))"
78 
79  if (this%any()) then
80  write (iout, fmt) 'RELEASE SCHEDULE', this%times
81  else
82  write (iout, "(1x,a,1x,a)") 'NO RELEASES SCHEDULED'
83  end if
84  end subroutine log
85 
86  !> @brief Add a release time to the schedule.
87  !!
88  !! To schedule multiple release times at once, expand
89  !! and populate the time selection object by hand. DO
90  !! NOT attempt to manipulate the times array; this is
91  !! a read-only property which the schedule maintains.
92  !<
93  subroutine schedule(this, trelease)
94  class(releasescheduletype), intent(inout) :: this
95  real(DP), intent(in) :: trelease
96  call expandarray(this%times)
97  this%times(size(this%times)) = trelease
98  end subroutine schedule
99 
100  !> @brief Refresh the schedule for the current time step.
101  !!
102  !! This involves several tasks: first, advance the time
103  !! selection. Then, if period-block release setting lines
104  !! are provided, reinitialize the time step selection for
105  !! the given period. Finally, refresh the schedule array,
106  !! deduplicating any times closer than the set tolerance.
107  !!
108  !! This routine is idempotent.
109  !<
110  subroutine advance(this, lines)
111  use tdismodule, only: totimc, kstp, endofperiod
112  class(releasescheduletype), intent(inout) :: this
113  character(len=LINELENGTH), intent(in), optional :: lines(:)
114  integer(I4B) :: it, i
115  real(DP) :: tprevious
116  real(DP) :: trelease
117 
118  ! Advance the time selection.
119  call this%time_select%advance()
120 
121  ! Reinitialize the time step selection if new
122  ! period-block release settings are provided.
123  if (present(lines)) then
124  call this%step_select%init()
125  do i = 1, size(lines)
126  call this%step_select%read(lines(i))
127  end do
128  end if
129 
130  ! Reinitialize the release time schedule.
131  if (allocated(this%times)) deallocate (this%times)
132  allocate (this%times(0))
133 
134  tprevious = -done
135  trelease = -done
136 
137  ! Add a release time configured by period-block
138  ! settings, if one is scheduled this time step.
139  if (this%step_select%is_selected(kstp, endofperiod=endofperiod)) then
140  trelease = totimc
141  call this%schedule(trelease)
142  tprevious = trelease
143  end if
144 
145  ! Add explicitly configured release times, up
146  ! to the configured tolerance of coincidence.
147  if (this%time_select%any()) then
148  do it = this%time_select%selection(1), this%time_select%selection(2)
149  trelease = this%time_select%times(it)
150  ! Skip the release time if it's too close
151  ! to the previously scheduled release time.
152  if (tprevious >= dzero .and. is_close( &
153  tprevious, &
154  trelease, &
155  atol=this%tolerance)) cycle
156  call this%schedule(trelease)
157  tprevious = trelease
158  end do
159  end if
160  end subroutine advance
161 
162  !> @brief Check if any releases are scheduled.
163  !!
164  !! Note: be sure to call advance() before calling this function,
165  !! or the result may still be associated with a prior time step.
166  !<
167  logical function any(this) result(a)
168  class(releasescheduletype) :: this
169  a = this%count() > 0
170  end function any
171 
172  !> @brief Return the number of releases scheduled.
173  !!
174  !! Note: be sure to call advance() before calling this function,
175  !! or the result may still be associated with a prior time step.
176  !<
177  integer function count(this) result(n)
178  class(releasescheduletype) :: this
179  n = size(this%times)
180  end function count
181 
182 end module releaseschedulemodule
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
real(dp), parameter done
real constant 1
Definition: Constants.f90:76
This module defines variable data types.
Definition: kind.f90:8
pure logical function, public is_close(a, b, rtol, atol, symmetric)
Check if a real value is approximately equal to another.
Definition: MathUtil.f90:46
Particle release scheduling.
subroutine schedule(this, trelease)
Add a release time to the schedule.
subroutine advance(this, lines)
Refresh the schedule for the current time step.
subroutine log(this, iout)
Write the release schedule to the given output unit.
integer function count(this)
Return the number of releases scheduled.
type(releasescheduletype) function, pointer, public create_release_schedule(tol)
Create a new release schedule object.
subroutine deallocate(this)
Deallocate the release schedule.
logical function any(this)
Check if any releases are scheduled.
logical(lgp), pointer, public endofperiod
flag indicating end of stress period
Definition: tdis.f90:27
real(dp), pointer, public totimc
simulation time at start of time step
Definition: tdis.f90:33
integer(i4b), pointer, public kstp
current time step number
Definition: tdis.f90:24
Specify times for some event to occur.
Definition: TimeSelect.f90:2
Time step selection module.
Particle release scheduling utility.
Represents a series of instants at which some event should occur.
Definition: TimeSelect.f90:30