monad-schedule-0.1.0.0: A new, simple, composable concurrency abstraction.
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Schedule.Trans

Description

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

Synopsis

Waiting action

data Wait diff a Source #

A functor implementing a syntactical "waiting" action.

Constructors

Wait 

Fields

  • getDiff :: diff

    The duration to wait.

  • awaited :: a

    The encapsulated value.

Instances

Instances details
Functor (Wait diff) Source # 
Instance details

Defined in Control.Monad.Schedule.Trans

Methods

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

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

Eq diff => Eq1 (Wait diff) Source # 
Instance details

Defined in Control.Monad.Schedule.Trans

Methods

liftEq :: (a -> b -> Bool) -> Wait diff a -> Wait diff b -> Bool #

Ord diff => MonadSchedule (Wait diff) Source # 
Instance details

Defined in Control.Monad.Schedule.Trans

Methods

schedule :: NonEmpty (Wait diff a) -> Wait diff (NonEmpty a, [Wait diff a]) Source #

(Eq diff, Eq a) => Eq (Wait diff a) Source # 
Instance details

Defined in Control.Monad.Schedule.Trans

Methods

(==) :: Wait diff a -> Wait diff a -> Bool #

(/=) :: Wait diff a -> Wait diff a -> Bool #

(Show diff, Show a) => Show (Wait diff a) Source # 
Instance details

Defined in Control.Monad.Schedule.Trans

Methods

showsPrec :: Int -> Wait diff a -> ShowS #

show :: Wait diff a -> String #

showList :: [Wait diff a] -> ShowS #

(Ord diff, TimeDifference diff, Monad m, MonadSchedule m) => MonadSchedule (ScheduleT diff m) Source #

Run each action one step until it is discovered which action(s) are pure, or yield next. If there is a pure action, it is returned, otherwise all actions are shifted to the time when the earliest action yields.

Instance details

Defined in Control.Monad.Schedule.Trans

Methods

schedule :: NonEmpty (ScheduleT diff m a) -> ScheduleT diff m (NonEmpty a, [ScheduleT diff m a]) Source #

compareWait :: Ord diff => Wait diff a -> Wait diff a -> Ordering Source #

Compare by the time difference, regardless of the value.

ScheduleT

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.

execScheduleT :: Monad m => ScheduleT diff m a -> m (a, [diff]) Source #

Formally execute all waiting actions, returning the final value and all moments when the schedule would have waited.