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

Control.Monad.Schedule.Class

Synopsis

Documentation

class MonadSchedule m where Source #

Monads in which actions can be scheduled concurrently.

schedule actions is expected to run actions concurrently, whatever that means for a particular monad m. schedule does not return before at least one value has finished, and the returned values NonEmpty a are all those that finish first. The actions [m a] (possibly empty) are the remaining, still running ones. Executing any of them is expected to be blocking, and awaits the return of the corresponding action.

A lawful instance is considered to satisfy these conditions:

  • The set of returned values is invariant under scheduling. In other words, sequence will result in the same set of values as scheduleAndFinish. schedule thus can be thought of as a concurrency-utilizing version of sequence.

Methods

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

Run the actions concurrently, and return the result of the first finishers, together with completions for the unfinished actions.

Instances

Instances details
MonadSchedule IO Source #

Fork all actions concurrently in separate threads and wait for the first one to complete.

Many monadic actions complete at nondeterministic times (such as event listeners), and it is thus impossible to schedule them deterministically with most other actions. Using concurrency, they can still be scheduled with all other actions in IO, by running them in separate GHC threads.

Instance details

Defined in Control.Monad.Schedule.Class

Methods

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

MonadSchedule Identity Source #

When there are no effects, return all values immediately

Instance details

Defined in Control.Monad.Schedule.Class

(Monad m, MonadSchedule m) => MonadSchedule (MaybeT m) Source # 
Instance details

Defined in Control.Monad.Schedule.Class

Methods

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

(KnownNat n, 1 <= n) => MonadSchedule (OSThreadPool n) Source # 
Instance details

Defined in Control.Monad.Schedule.OSThreadPool

Monad m => MonadSchedule (RoundRobinT m) Source #

Execute only the first action, and leave the others for later, preserving the order.

Instance details

Defined in Control.Monad.Schedule.RoundRobin

Monad m => MonadSchedule (SequenceT m) Source #

Execute all actions in sequence and return their result when all of them are done. Essentially, this is sequenceA.

Instance details

Defined in Control.Monad.Schedule.Sequence

Methods

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

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 #

(Functor m, MonadSchedule m) => MonadSchedule (IdentityT m) Source #

Pass through the scheduling functionality of the underlying monad

Instance details

Defined in Control.Monad.Schedule.Class

Methods

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

(Monad m, MonadSchedule m) => MonadSchedule (ExceptT e m) Source #

Schedule all actions according to m and in case of exceptions throw the first exception of the immediately returning actions.

Instance details

Defined in Control.Monad.Schedule.Class

Methods

schedule :: NonEmpty (ExceptT e m a) -> ExceptT e m (NonEmpty a, [ExceptT e m a]) Source #

(Monad m, MonadSchedule m) => MonadSchedule (ReaderT r m) Source #

Broadcast the same environment to all actions. The continuations keep this initial environment.

Instance details

Defined in Control.Monad.Schedule.Class

Methods

schedule :: NonEmpty (ReaderT r m a) -> ReaderT r m (NonEmpty a, [ReaderT r m a]) Source #

(Monoid w, Functor m, MonadSchedule m) => MonadSchedule (WriterT w m) Source #

Write in the order of scheduling: The first actions to return write first.

Instance details

Defined in Control.Monad.Schedule.Class

Methods

schedule :: NonEmpty (WriterT w m a) -> WriterT w m (NonEmpty a, [WriterT w m a]) Source #

(Monoid w, Functor m, MonadSchedule m) => MonadSchedule (WriterT w m) Source #

Write in the order of scheduling: The first actions to return write first.

Instance details

Defined in Control.Monad.Schedule.Class

Methods

schedule :: NonEmpty (WriterT w m a) -> WriterT w m (NonEmpty a, [WriterT w m a]) Source #

(Monoid w, Monad m, MonadSchedule m) => MonadSchedule (AccumT w m) Source #

Combination of WriterT and ReaderT. Pass the same initial environment to all actions and write to the log in the order of scheduling in m.

Instance details

Defined in Control.Monad.Schedule.Class

Methods

schedule :: NonEmpty (AccumT w m a) -> AccumT w m (NonEmpty a, [AccumT w m a]) Source #

(Monoid w, Functor m, MonadSchedule m) => MonadSchedule (WriterT w m) Source #

Write in the order of scheduling: The first actions to return write first.

Instance details

Defined in Control.Monad.Schedule.Class

Methods

schedule :: NonEmpty (WriterT w m a) -> WriterT w m (NonEmpty a, [WriterT w m a]) Source #

(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 #

scheduleAndFinish :: (Monad m, MonadSchedule m) => NonEmpty (m a) -> m (NonEmpty a) Source #

Keeps scheduleing actions until all are finished. Returns the same set of values as sequence, but utilises concurrency and may thus change the order of the values.

sequenceScheduling :: (Monad m, MonadSchedule m) => NonEmpty (m a) -> m (NonEmpty a) Source #

Uses scheduleAndFinish to execute all actions concurrently, then orders them again. Thus it behaves semantically like sequence, but leverages concurrency.

race :: (Monad m, MonadSchedule m) => m a -> m b -> m (Either (a, m b) (m a, b)) Source #

Runs two values in a MonadSchedule concurrently and returns the first one that yields a value and a continuation for the other value.

async :: (Monad m, MonadSchedule m) => m a -> m b -> m (a, b) Source #

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