Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class MonadSchedule m where
- scheduleAndFinish :: (Monad m, MonadSchedule m) => NonEmpty (m a) -> m (NonEmpty a)
- sequenceScheduling :: (Monad m, MonadSchedule m) => NonEmpty (m a) -> m (NonEmpty a)
- race :: (Monad m, MonadSchedule m) => m a -> m b -> m (Either (a, m b) (m a, b))
- async :: (Monad m, MonadSchedule m) => m a -> m b -> m (a, b)
- apSchedule :: (MonadSchedule m, Monad m) => m (a -> b) -> m a -> m b
- scheduleWith :: (MonadSchedule m, Monad m) => m a -> m b -> m b
Documentation
class MonadSchedule m where Source #
Monad
s in which actions can be scheduled concurrently.
is expected to run schedule
actionsactions
concurrently,
whatever that means for a particular monad m
.
schedule
does not return before at least one value has finished,
and the returned values
are all those that finish first.
The actions NonEmpty
a[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 preserve pure values.
Applying schedule
to values like
will eventually return exactly these values.pure
a
schedule
thus can be thought of as a concurrency-utilizing version of sequence
.
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
MonadSchedule Identity Source # | When there are no effects, return all values immediately |
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 Caution: Using |
MonadIO m => MonadSchedule (ConcurrentlyT m) Source # | Like |
Defined in Control.Monad.Schedule.FreeAsync schedule :: NonEmpty (ConcurrentlyT m a) -> ConcurrentlyT m (NonEmpty a, [ConcurrentlyT m a]) Source # | |
MonadIO m => MonadSchedule (FreeAsyncT m) Source # | Concurrently wait for the completion of |
Defined in Control.Monad.Schedule.FreeAsync schedule :: NonEmpty (FreeAsyncT m a) -> FreeAsyncT m (NonEmpty a, [FreeAsyncT m a]) Source # | |
(KnownNat n, (1 <=? n) ~ 'True) => MonadSchedule (OSThreadPool n) Source # | |
Defined in Control.Monad.Schedule.OSThreadPool schedule :: NonEmpty (OSThreadPool n a) -> OSThreadPool n (NonEmpty a, [OSThreadPool n a]) Source # | |
Monad m => MonadSchedule (RoundRobinT m) Source # | Execute only the first action, and leave the others for later, preserving the order. |
Defined in Control.Monad.Schedule.RoundRobin schedule :: NonEmpty (RoundRobinT m a) -> RoundRobinT m (NonEmpty a, [RoundRobinT m a]) Source # | |
Monad m => MonadSchedule (SequenceT m) Source # | Execute all actions in sequence and return their result when all of them are done.
Essentially, this is |
Ord diff => MonadSchedule (Wait diff) Source # | |
(Monad m, MonadSchedule m) => MonadSchedule (MaybeT m) 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. |
(Monoid w, Monad m, MonadSchedule m) => MonadSchedule (AccumT w m) Source # | Combination of |
(Monad m, MonadSchedule m) => MonadSchedule (ExceptT e m) Source # | Schedule all actions according to |
(Functor m, MonadSchedule m) => MonadSchedule (IdentityT m) Source # | Pass through the scheduling functionality of the underlying monad |
(Monad m, MonadSchedule m) => MonadSchedule (ReaderT r m) Source # | Broadcast the same environment to all actions. The continuations keep this initial environment. |
(Monoid w, Functor m, MonadSchedule m) => MonadSchedule (WriterT w m) Source # | Write in the order of scheduling: The first actions to return write first. |
(Monoid w, Functor m, MonadSchedule m) => MonadSchedule (WriterT w m) Source # | Write in the order of scheduling: The first actions to return write first. |
(Monoid w, Functor m, MonadSchedule m) => MonadSchedule (WriterT w m) Source # | Write in the order of scheduling: The first actions to return write first. |
scheduleAndFinish :: (Monad m, MonadSchedule m) => NonEmpty (m a) -> m (NonEmpty a) Source #
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.
apSchedule :: (MonadSchedule m, Monad m) => m (a -> b) -> m a -> m b Source #
Run both actions concurrently and apply the first result to the second.
Use as a concurrent replacement for <*>
from Applicative
.
scheduleWith :: (MonadSchedule m, Monad m) => m a -> m b -> m b Source #
Concurrent replacement for *>
from Applicative
or >>
from Monad
.