Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module defines classes of monads that can perform multiple computations in parallel and, more importantly, combine the results of those parallel computations.
There are two classes exported by this module, MonadParallel
and MonadFork
. The former is more generic, but the
latter is easier to use: when invoking any expensive computation that could be performed in parallel, simply wrap the
call in forkExec
. The function immediately returns a handle to the running computation. The handle can be used to
obtain the result of the computation when needed:
do child <- forkExec expensive otherStuff result <- child
In this example, the computations expensive and otherStuff would be performed in parallel. When using the
MonadParallel
class, both parallel computations must be specified at once:
bindM2 (\ childResult otherResult -> ...) expensive otherStuff
In either case, for best results the costs of the two computations should be roughly equal.
Any monad that is an instance of the MonadFork
class is also an instance of the MonadParallel
class, and the
following law should hold:
bindM2 f ma mb = do {a' <- forkExec ma; b <- mb; a <- a'; f a b}
When operating with monads free of side-effects, such as Identity
or Maybe
, forkExec
is equivalent to return
and bindM2
is equivalent to \ f ma mb -> do {a <- ma; b <- mb; f a b}
— the only difference is in the
resource utilisation. With the IO
monad, on the other hand, there may be visible difference in the results because
the side effects of ma and mb may be arbitrarily reordered.
- class Monad m => MonadParallel m where
- bindM2 :: (a -> b -> m c) -> m a -> m b -> m c
- class MonadParallel m => MonadFork m where
- forkExec :: m a -> m (m a)
- bindM3 :: MonadParallel m => (a -> b -> c -> m d) -> m a -> m b -> m c -> m d
- liftM2 :: MonadParallel m => (a -> b -> c) -> m a -> m b -> m c
- liftM3 :: MonadParallel m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r
- ap :: MonadParallel m => m (a -> b) -> m a -> m b
- sequence :: MonadParallel m => [m a] -> m [a]
- sequence_ :: MonadParallel m => [m a] -> m ()
- mapM :: MonadParallel m => (a -> m b) -> [a] -> m [b]
- replicateM :: MonadParallel m => Int -> m a -> m [a]
- replicateM_ :: MonadParallel m => Int -> m a -> m ()
Classes
class Monad m => MonadParallel m where Source
Class of monads that can perform two computations in parallel and bind their results together.
Nothing
bindM2 :: (a -> b -> m c) -> m a -> m b -> m c Source
Perform two monadic computations in parallel; when they are both finished, pass the results to the function.
Apart from the possible ordering of side effects, this function is equivalent to
\f ma mb-> do {a <- ma; b <- mb; f a b}
MonadParallel [] | |
MonadParallel IO | IO is parallelizable by |
MonadParallel Maybe | |
MonadParallel Identity | Any monad that allows the result value to be extracted, such as |
MonadParallel ((->) r) | |
MonadParallel m => MonadParallel (MaybeT m) | |
MonadParallel m => MonadParallel (ListT m) | |
MonadParallel m => MonadParallel (IdentityT m) | |
MonadParallel m => MonadParallel (ExceptT e m) | |
MonadParallel m => MonadParallel (ReaderT r m) |
class MonadParallel m => MonadFork m where Source
Class of monads that can fork a parallel computation.
Nothing
bindM3 :: MonadParallel m => (a -> b -> c -> m d) -> m a -> m b -> m c -> m d Source
Perform three monadic computations in parallel; when they are all finished, pass their results to the function.
Control.Monad equivalents
liftM2 :: MonadParallel m => (a -> b -> c) -> m a -> m b -> m c Source
Like liftM2
, but evaluating its two monadic arguments in parallel.
liftM3 :: MonadParallel m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r Source
Like liftM3
, but evaluating its three monadic arguments in parallel.
ap :: MonadParallel m => m (a -> b) -> m a -> m b Source
Like ap
, but evaluating the function and its argument in parallel.
sequence :: MonadParallel m => [m a] -> m [a] Source
Like sequence
, but executing the actions in parallel.
sequence_ :: MonadParallel m => [m a] -> m () Source
Like sequence_
, but executing the actions in parallel.
mapM :: MonadParallel m => (a -> m b) -> [a] -> m [b] Source
Like mapM
, but applying the function to the individual list items in parallel.
replicateM :: MonadParallel m => Int -> m a -> m [a] Source
Like replicateM
, but executing the action multiple times in parallel.
replicateM_ :: MonadParallel m => Int -> m a -> m () Source
Like replicateM_
, but executing the action multiple times in parallel.