monad-parallel-0.8: Parallel execution of monadic computations
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Parallel

Description

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.

Synopsis

Classes

class Monad m => MonadParallel m where Source #

Class of monads that can perform two computations in parallel and bind their results together.

Minimal complete definition

Nothing

Methods

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}

Instances

Instances details
MonadParallel [] Source # 
Instance details

Defined in Control.Monad.Parallel

Methods

bindM2 :: (a -> b -> [c]) -> [a] -> [b] -> [c] Source #

MonadParallel Maybe Source # 
Instance details

Defined in Control.Monad.Parallel

Methods

bindM2 :: (a -> b -> Maybe c) -> Maybe a -> Maybe b -> Maybe c Source #

MonadParallel IO Source #

IO is parallelizable by forkIO.

Instance details

Defined in Control.Monad.Parallel

Methods

bindM2 :: (a -> b -> IO c) -> IO a -> IO b -> IO c Source #

MonadParallel Identity Source #

Any monad that allows the result value to be extracted, such as Identity or Maybe monad, can implement bindM2 by using par.

Instance details

Defined in Control.Monad.Parallel

Methods

bindM2 :: (a -> b -> Identity c) -> Identity a -> Identity b -> Identity c Source #

MonadParallel m => MonadParallel (MaybeT m) Source # 
Instance details

Defined in Control.Monad.Parallel

Methods

bindM2 :: (a -> b -> MaybeT m c) -> MaybeT m a -> MaybeT m b -> MaybeT m c Source #

MonadParallel m => MonadParallel (ReaderT r m) Source # 
Instance details

Defined in Control.Monad.Parallel

Methods

bindM2 :: (a -> b -> ReaderT r m c) -> ReaderT r m a -> ReaderT r m b -> ReaderT r m c Source #

MonadParallel m => MonadParallel (IdentityT m) Source # 
Instance details

Defined in Control.Monad.Parallel

Methods

bindM2 :: (a -> b -> IdentityT m c) -> IdentityT m a -> IdentityT m b -> IdentityT m c Source #

MonadParallel m => MonadParallel (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Parallel

Methods

bindM2 :: (a -> b -> ExceptT e m c) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c Source #

MonadParallel ((->) r :: Type -> Type) Source # 
Instance details

Defined in Control.Monad.Parallel

Methods

bindM2 :: (a -> b -> r -> c) -> (r -> a) -> (r -> b) -> r -> c Source #

class MonadParallel m => MonadFork m where Source #

Class of monads that can fork a parallel computation.

Minimal complete definition

Nothing

Methods

forkExec :: m a -> m (m a) Source #

Fork a child monadic computation to be performed in parallel with the current one.

Instances

Instances details
MonadFork [] Source # 
Instance details

Defined in Control.Monad.Parallel

Methods

forkExec :: [a] -> [[a]] Source #

MonadFork Maybe Source # 
Instance details

Defined in Control.Monad.Parallel

Methods

forkExec :: Maybe a -> Maybe (Maybe a) Source #

MonadFork IO Source #

IO is forkable by forkIO.

Instance details

Defined in Control.Monad.Parallel

Methods

forkExec :: IO a -> IO (IO a) Source #

MonadFork m => MonadFork (MaybeT m) Source # 
Instance details

Defined in Control.Monad.Parallel

Methods

forkExec :: MaybeT m a -> MaybeT m (MaybeT m a) Source #

MonadFork m => MonadFork (ReaderT r m) Source # 
Instance details

Defined in Control.Monad.Parallel

Methods

forkExec :: ReaderT r m a -> ReaderT r m (ReaderT r m a) Source #

MonadFork m => MonadFork (IdentityT m) Source # 
Instance details

Defined in Control.Monad.Parallel

Methods

forkExec :: IdentityT m a -> IdentityT m (IdentityT m a) Source #

MonadFork m => MonadFork (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Parallel

Methods

forkExec :: ExceptT e m a -> ExceptT e m (ExceptT e m a) Source #

MonadFork ((->) r :: Type -> Type) Source # 
Instance details

Defined in Control.Monad.Parallel

Methods

forkExec :: (r -> a) -> r -> (r -> a) Source #

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

ap :: MonadParallel m => m (a -> b) -> m a -> m b Source #

Like ap, but evaluating the function and its argument in parallel.

forM :: MonadParallel m => [a] -> (a -> m b) -> m [b] Source #

Like forM, but applying the function to the individual list items in parallel.

forM_ :: MonadParallel m => [a] -> (a -> m b) -> m () Source #

Like forM_, but applying the function to the individual list items in parallel.

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.

mapM :: MonadParallel m => (a -> m b) -> [a] -> m [b] Source #

Like mapM, but applying the function to the individual list items in parallel.

mapM_ :: MonadParallel m => (a -> m b) -> [a] -> m () 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.

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.