schedule-0.0: Schedule sub-computations to run later, in a pure way

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Trans.Schedule.Internal

Contents

Description

Pure scheduled computations, as a monad transformer.

Synopsis

Documentation

type Tick = Sum Integer Source

The smallest discrete unit of time, in a pure scheduled computation.

data Clock c Source

A maybe-impure supplier of time, to a pure scheduled computation.

The type c is the computational context where clock operations occur, e.g. a Monad such as IO.

Clock implementations must be monotic. See System.Time.Monotonic for an example on how to wrap non-monotonic clocks. TODO: provide a generic monotonic wrapper.

Constructors

Clock 

Fields

clockNow :: c Tick

Get the current time.

clockDelay :: Tick -> c ()

Suspend the current computation for a given number of ticks.

Nothing else in the computation runs until the suspension is over. Afterwards, clockNow will give the expected value, i.e. for all n:

do
    old <- clockNow
    clockDelay n
    new <- clockNow
    let new' = assert (old + n <= new) new

The relation is <= not ==, because the computer might have slept during the mean time or something. On the other hand, if the underlying physical clock might delay for a shorter period than requested, then implementations of this function must loop-delay until the <= condition is satisfied.

The above is the only condition that scheduled computations should rely on, and any actual physical real delay is up to the implementation.

Pure scheduled computation

type ScheduleT c m = ComposeT (ReaderT (Clock c)) (StateT (TaskState c m)) m Source

A computation that can schedule sub-computations for later.

We use ComposeT so we need only one lift from the inner monad m.

TODO: There is an MFunctor instance for the underlying type ComposeT, but that's not what we want here - a hoist must also morph the TaskState. So we should probably wrap this in a newtype and define a proper MFunctor instance that isn't just hoist from ComposeT. However, this is probably impossible with how ScheduleT is currently defined; see Control.Monad.Trans.Schedule.ExampleMFunctor for details.

The solution would likely involve adding a s type parameter for the state that is independent of m. This would increase complexity; however a MFunctor instance is quite important for this monad to be composeable with other monads.

type Task c m = ScheduleT c m () Source

A task to run, in response to a tick event. This can be any computation.

In other programming contexts, this would be analogous to a callback, subscriber, observer, timeout, etc etc.

type TaskCancel c m = ScheduleT c m (Maybe (Task c m)) Source

Cancel a task.

Which task to cancel, is implicitly bound to each instance of this type. See after for more details.

data TaskState c m Source

The state of all scheduled pending tasks.

tickNow :: Monad m => ScheduleT c m Tick Source

Get the current tick, whose tasks have not yet run.

tickPrev :: Monad m => ScheduleT c m Tick Source

Get the previous tick, whose tasks have all already run.

runScheduleT_ :: Monad m => ScheduleT c m a -> Clock c -> m (a, TaskState c m) Source

Run a scheduled computation starting from tick 0.

after :: Monad m => Tick -> Task c m -> ScheduleT c m (TaskCancel c m) Source

Schedule a task to run after a given number of ticks.

renew :: Monad m => Tick -> TaskCancel c m -> ScheduleT c m (Maybe (TaskCancel c m)) Source

Re-schedule a task to instead run after a given number of ticks. If the task was already cancelled, do nothing.

Generic impure execution

type LiftClock c m = forall a. c a -> m a Source

Lift a clock computation into the scheduled computation's context.

We use a type synonym instead of a typeclass, so that we can avoid overlapping instances such as these:

instance MonadBase c m => MonadClock c m (ScheduleT c m)
instance MonadIO m => MonadClock IO m (ScheduleT IO m)

but still write generic code like runScheduleT' to be useful externally.

class MonadClock c m where Source

A monad that can lift clock operations.

Methods

liftClock :: LiftClock c m Source

defaultLiftClock :: (MonadClock c m, Monad m, MonadTrans t) => LiftClock c (t m) Source

Helps to derive new instances of MonadClock from base instances.

type LiftRT c n m = forall a. n a -> ScheduleT c m a Source

Lift some deeply-inner computation n into a scheduled computation, running tasks in parallel while the computation is still pending.

class MonadRT c b m where Source

A monad that can lift inner computations to run tasks in parallel.

Methods

liftRT :: LiftRT c b m Source

defaultLiftRT :: (MonadRT c b m, Monad m, MonadTrans t) => LiftRT c b (t m) Source

Helps to derive new instances of MonadRT from base instances. Don't use this yet, it's undefined right now.

getClockNow' :: Monad m => LiftClock c m -> ScheduleT c m Tick Source

Get the time from the clock.

runTasks' :: Monad m => LiftClock c m -> ScheduleT c m () Source

Run tasks up to but not including the current clock tick.

runScheduleT' :: Monad m => LiftClock c m -> ScheduleT c m a -> Clock c -> m (a, TaskState c m) Source

Run a scheduled computation, starting from the current clock time.