Safe Haskell | None |
---|---|
Language | Haskell2010 |
Device for running an action at (i.e. shortly after) a certain time, which can be used to implement things like time-based cache expiry.
This implementation avoids the use of polling and leans on Haskell's scheduler to achieve low-latency without lots of computational overhead.
The alarm can be set multiple times, and in this case the alarm will go off at the earliest requested time. If the alarm is set in the past, the action will run immediately. When the action runs, it clears all future alarms; the action can itself set the next alarm time.
To perform time-based cache expiry, create an AlarmClock
whose action flushes
any stale entries from the cache and then calls setAlarm
for the next time
that an entry will expire (if there are any). When expiring entries are added
to the cache, call setAlarm
to ensure that they will expire in a timely
fashion.
Synopsis
- data AlarmClock t
- newAlarmClock :: TimeScale t => (AlarmClock t -> IO ()) -> IO (AlarmClock t)
- newAlarmClock' :: TimeScale t => (AlarmClock t -> t -> IO ()) -> IO (AlarmClock t)
- destroyAlarmClock :: AlarmClock t -> IO ()
- withAlarmClock :: TimeScale t => (AlarmClock t -> t -> IO ()) -> (AlarmClock t -> IO a) -> IO a
- setAlarm :: TimeScale t => AlarmClock t -> t -> IO ()
- setAlarmSTM :: TimeScale t => AlarmClock t -> t -> STM ()
- setAlarmNow :: TimeScale t => AlarmClock t -> IO ()
- isAlarmSet :: AlarmClock t -> IO Bool
- isAlarmSetSTM :: AlarmClock t -> STM Bool
- class Eq t => TimeScale t
- newtype MonotonicTime = MonotonicTime TimeSpec
Documentation
data AlarmClock t Source #
An AlarmClock
is a device for running an action at (or shortly after) a certain time.
:: TimeScale t | |
=> (AlarmClock t -> IO ()) | Action to run when the alarm goes off. The action is provided the alarm clock
so it can set a new alarm if desired. Note that |
-> IO (AlarmClock t) |
Create a new AlarmClock
that runs the given action. Initially, there is
no wakeup time set: you must call setAlarm
for anything else to happen.
:: TimeScale t | |
=> (AlarmClock t -> t -> IO ()) | Action to run when the alarm goes off. The action is provided the alarm clock
so it can set a new alarm if desired, and the current time.
Note that |
-> IO (AlarmClock t) |
Create a new AlarmClock
that runs the given action. Initially, there is
no wakeup time set: you must call setAlarm
for anything else to happen.
destroyAlarmClock :: AlarmClock t -> IO () Source #
Destroy the AlarmClock
so no further alarms will occur. If the alarm is currently going off
then this will block until the action is finished.
withAlarmClock :: TimeScale t => (AlarmClock t -> t -> IO ()) -> (AlarmClock t -> IO a) -> IO a Source #
The action withAlarmClock onWakeUp inner
runs inner
with a new AlarmClock
which
is destroyed when inner
exits.
setAlarm :: TimeScale t => AlarmClock t -> t -> IO () Source #
Make the AlarmClock
go off at (or shortly after) the given time. This
can be called more than once; in which case, the alarm will go off at the
earliest given time.
setAlarmSTM :: TimeScale t => AlarmClock t -> t -> STM () Source #
Make the AlarmClock
go off at (or shortly after) the given time. This
can be called more than once; in which case, the alarm will go off at the
earliest given time.
setAlarmNow :: TimeScale t => AlarmClock t -> IO () Source #
Make the AlarmClock
go off right now.
isAlarmSet :: AlarmClock t -> IO Bool Source #
Is the alarm set - i.e. will it go off at some point in the future even if setAlarm
is not called?
isAlarmSetSTM :: AlarmClock t -> STM Bool Source #
Is the alarm set - i.e. will it go off at some point in the future even if setAlarm
is not called?
class Eq t => TimeScale t Source #
Abstraction that allows for a choice between the UTC timescale and a monotonic timescale, which differ in their handling of irregularities such as clock adjustments and leap seconds.
Alarms set using the UTCTime
timescale wait for the system clock to pass the
given time before going off, and account for the clock being adjusted
backwards and for (positive) leap seconds while waiting. If the clock is set
forwards, or a negative leap second occurs, then the alarm may go off later
than expected by an amount that is roughly equal to the adjustment. It is
possible to correct for this by setting the alarm again after the adjustment
has occurred.
The Monotonic
timescale cannot be so adjusted, which may be more suitable for
some applications.
Note that the timeliness of the alarm going off is very much on a "best effort" basis, and there are many environmental factors that could cause the alarm to go off later than expected.
Instances
newtype MonotonicTime Source #
Representation of system monotonic clock.
Instances
Eq MonotonicTime Source # | |
Defined in Control.Concurrent.AlarmClock.TimeScale (==) :: MonotonicTime -> MonotonicTime -> Bool # (/=) :: MonotonicTime -> MonotonicTime -> Bool # | |
Ord MonotonicTime Source # | |
Defined in Control.Concurrent.AlarmClock.TimeScale compare :: MonotonicTime -> MonotonicTime -> Ordering # (<) :: MonotonicTime -> MonotonicTime -> Bool # (<=) :: MonotonicTime -> MonotonicTime -> Bool # (>) :: MonotonicTime -> MonotonicTime -> Bool # (>=) :: MonotonicTime -> MonotonicTime -> Bool # max :: MonotonicTime -> MonotonicTime -> MonotonicTime # min :: MonotonicTime -> MonotonicTime -> MonotonicTime # | |
Show MonotonicTime Source # | |
Defined in Control.Concurrent.AlarmClock.TimeScale showsPrec :: Int -> MonotonicTime -> ShowS # show :: MonotonicTime -> String # showList :: [MonotonicTime] -> ShowS # | |
TimeScale MonotonicTime Source # | |
Defined in Control.Concurrent.AlarmClock.TimeScale |