rhine-0.5.1.0: Functional Reactive Programming with type-level clocks

Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Schedule

Description

This module supplies a general purpose monad transformer that adds a syntactical "delay", or "waiting" side effect.

This allows for universal and deterministic scheduling of clocks that implement their waiting actions in ScheduleT. See Trans for more details.

Synopsis

Documentation

data Wait diff a Source #

A functor implementing a syntactical "waiting" action.

  • diff represents the duration to wait.
  • a is the encapsulated value.

Constructors

Wait diff a 
Instances
Functor (Wait diff) Source # 
Instance details

Defined in Control.Monad.Schedule

Methods

fmap :: (a -> b) -> Wait diff a -> Wait diff b #

(<$) :: a -> Wait diff b -> Wait diff a #

(Monad m, NonemptyNatList v) => Clock (ScheduleT Integer m) (Periodic v) Source # 
Instance details

Defined in FRP.Rhine.Clock.Periodic

Associated Types

type Time (Periodic v) :: Type Source #

type Tag (Periodic v) :: Type Source #

type ScheduleT diff = FreeT (Wait diff) Source #

Values in ScheduleT diff m are delayed computations with side effects in m. Delays can occur between any two side effects, with lengths specified by a diff value. These delays don't have any semantics, it can be given to them with runScheduleT.

wait :: Monad m => diff -> ScheduleT diff m () Source #

The side effect that waits for a specified amount.

runScheduleT :: Monad m => (diff -> m ()) -> ScheduleT diff m a -> m a Source #

Supply a semantic meaning to Wait. For every occurrence of Wait diff in the ScheduleT diff m a value, a waiting action is executed, depending on diff.

runScheduleIO :: (MonadIO m, Integral n) => ScheduleT n m a -> m a Source #

Run a ScheduleT value in a MonadIO, interpreting the times as milliseconds.

race :: (Ord diff, Num diff, Monad m) => ScheduleT diff m a -> ScheduleT diff m b -> ScheduleT diff m (Either (a, ScheduleT diff m b) (ScheduleT diff m a, b)) Source #

Runs two values in ScheduleT concurrently and returns the first one that yields a value (defaulting to the first argument), and a continuation for the other value.

async :: (Ord diff, Num diff, Monad m) => ScheduleT diff m a -> ScheduleT diff m b -> ScheduleT diff m (a, b) Source #

Runs both schedules concurrently and returns their results at the end.