monad-par-0.3.4.8: A library for parallel programming based on a monad

Safe HaskellNone
LanguageHaskell98

Control.Monad.Par

Contents

Description

The monad-par package provides a family of Par monads, for speeding up pure computations using parallel processors. (for a similar programming model for use with IO, see Control.Monad.Par.IO.)

The result of a given Par computation is always the same - i.e. it is deterministic, but the computation may be performed more quickly if there are processors available to share the work.

For example, the following program fragment computes the values of (f x) and (g x) in parallel, and returns a pair of their results:

 runPar $ do
     fx <- spawnP (f x)  -- start evaluating (f x)
     gx <- spawnP (g x)  -- start evaluating (g x)
     a  <- get fx        -- wait for fx
     b  <- get gx        -- wait for gx
     return (a,b)        -- return results

Par can be used for specifying pure parallel computations in which the order of the computation is not known beforehand. The programmer specifies how information flows from one part of the computation to another, but not the order in which computations will be evaluated at runtime. Information flow is described using "variables" called IVars, which support put and get operations. For example, suppose you have a problem that can be expressed as a network with four nodes, where b and c require the value of a, and d requires the value of b and c:

                      a
                     / \               
                    b   c             
                     \ /  
                      d

Then you could express this in the Par monad like this:

  runPar $ do
      [a,b,c,d] <- sequence [new,new,new,new]
      fork $ do x <- get a; put b (x+1)
      fork $ do x <- get a; put c (x+2)
      fork $ do x <- get b; y <- get c; put d (x+y)
      fork $ do put a (3 :: Int)
      get d

The result of the above computation is always 9. The get operation waits until its input is available; multiple puts to the same IVar are not allowed, and result in a runtime error. Values stored in IVars are usually fully evaluated (although there are ways provided to pass lazy values if necessary).

In the above example, b and c will be evaluated in parallel. In practice the work involved at each node is too small here to see the benefits of parallelism though: typically each node should involve much more work. The granularity is completely under your control - too small and the overhead of the Par monad will outweigh any parallelism benefits, whereas if the nodes are too large then there might not be enough parallelism to use all the available processors.

Unlike Control.Parallel, in Control.Monad.Par parallelism is not combined with laziness, so sharing and granularity are completely under the control of the programmer. New units of parallel work are only created by fork and a few other combinators.

The default implementation is based on a work-stealing scheduler that divides the work as evenly as possible between the available processors at runtime. Other schedulers are available that are based on different policies and have different performance characteristics. To use one of these other schedulers, just import its module instead of Control.Monad.Par:

For more information on the programming model, please see these sources:

Synopsis

The Par Monad

data Par a #

Instances

Monad Par # 

Methods

(>>=) :: Par a -> (a -> Par b) -> Par b #

(>>) :: Par a -> Par b -> Par b #

return :: a -> Par a #

fail :: String -> Par a #

Functor Par # 

Methods

fmap :: (a -> b) -> Par a -> Par b #

(<$) :: a -> Par b -> Par a #

Applicative Par # 

Methods

pure :: a -> Par a #

(<*>) :: Par (a -> b) -> Par a -> Par b #

(*>) :: Par a -> Par b -> Par b #

(<*) :: Par a -> Par b -> Par a #

runPar :: Par a -> a #

Run a parallel, deterministic computation and return its result.

Note: you must NOT return an IVar in the output of the parallel computation. This is unfortunately not enforced, as it is with runST or with newer libraries that export a Par monad, such as lvish.

runParIO :: Par a -> IO a #

A version that avoids an internal unsafePerformIO for calling contexts that are already in the IO monad.

Returning any value containing IVar is still disallowed, as it can compromise type safety.

fork :: Par () -> Par () #

Forks a computation to happen in parallel. The forked computation may exchange values with other computations using IVars.

Communication: IVars

data IVar a #

Instances

ParFuture IVar ParIO # 

Methods

spawn :: NFData a => ParIO a -> ParIO (IVar a) #

spawn_ :: ParIO a -> ParIO (IVar a) #

get :: IVar a -> ParIO a #

spawnP :: NFData a => a -> ParIO (IVar a) #

ParIVar IVar ParIO # 

Methods

fork :: ParIO () -> ParIO () #

new :: ParIO (IVar a) #

put :: NFData a => IVar a -> a -> ParIO () #

put_ :: IVar a -> a -> ParIO () #

newFull :: NFData a => a -> ParIO (IVar a) #

newFull_ :: a -> ParIO (IVar a) #

Eq (IVar a) #

Equality for IVars is physical equality, as with other reference types.

Methods

(==) :: IVar a -> IVar a -> Bool #

(/=) :: IVar a -> IVar a -> Bool #

NFData (IVar a) # 

Methods

rnf :: IVar a -> () #

new :: Par (IVar a) #

Creates a new IVar

newFull :: NFData a => a -> Par (IVar a) #

Creates a new IVar that contains a value

newFull_ :: a -> Par (IVar a) #

Creates a new IVar that contains a value (head-strict only)

get :: IVar a -> Par a #

Read the value in an IVar. The get operation can only return when the value has been written by a prior or parallel put to the same IVar.

put :: NFData a => IVar a -> a -> Par () #

Put a value into an IVar. Multiple puts to the same IVar are not allowed, and result in a runtime error.

put fully evaluates its argument, which therefore must be an instance of NFData. The idea is that this forces the work to happen when we expect it, rather than being passed to the consumer of the IVar and performed later, which often results in less parallelism than expected.

Sometimes partial strictness is more appropriate: see put_.

put_ :: IVar a -> a -> Par () #

Like put, but only head-strict rather than fully-strict.

Operations

spawn :: NFData a => Par a -> Par (IVar a) #

Like fork, but returns an IVar that can be used to query the result of the forked computataion. Therefore spawn provides futures or promises.

 spawn p = do
   r <- new
   fork (p >>= put r)
   return r

spawn_ :: Par a -> Par (IVar a) #

Like spawn, but the result is only head-strict, not fully-strict.

spawnP :: NFData a => a -> Par (IVar a) #

Spawn a pure (rather than monadic) computation. Fully-strict.

 spawnP = spawn . return

This module also reexports the Combinator library for backwards compatibility with version 0.1.

class NFData a #

A class of types that can be fully evaluated.

Since: 1.1.0.0

Instances

NFData Bool 

Methods

rnf :: Bool -> () #

NFData Char 

Methods

rnf :: Char -> () #

NFData Double 

Methods

rnf :: Double -> () #

NFData Float 

Methods

rnf :: Float -> () #

NFData Int 

Methods

rnf :: Int -> () #

NFData Int8 

Methods

rnf :: Int8 -> () #

NFData Int16 

Methods

rnf :: Int16 -> () #

NFData Int32 

Methods

rnf :: Int32 -> () #

NFData Int64 

Methods

rnf :: Int64 -> () #

NFData Integer 

Methods

rnf :: Integer -> () #

NFData Word 

Methods

rnf :: Word -> () #

NFData Word8 

Methods

rnf :: Word8 -> () #

NFData Word16 

Methods

rnf :: Word16 -> () #

NFData Word32 

Methods

rnf :: Word32 -> () #

NFData Word64 

Methods

rnf :: Word64 -> () #

NFData CallStack

Since: 1.4.2.0

Methods

rnf :: CallStack -> () #

NFData TypeRep

NOTE: Only defined for base-4.8.0.0 and later

Since: 1.4.0.0

Methods

rnf :: TypeRep -> () #

NFData () 

Methods

rnf :: () -> () #

NFData TyCon

NOTE: Only defined for base-4.8.0.0 and later

Since: 1.4.0.0

Methods

rnf :: TyCon -> () #

NFData Natural

Since: 1.4.0.0

Methods

rnf :: Natural -> () #

NFData Void

Defined as rnf = absurd.

Since: 1.4.0.0

Methods

rnf :: Void -> () #

NFData Version

Since: 1.3.0.0

Methods

rnf :: Version -> () #

NFData Unique

Since: 1.4.0.0

Methods

rnf :: Unique -> () #

NFData ThreadId

Since: 1.4.0.0

Methods

rnf :: ThreadId -> () #

NFData ExitCode

Since: 1.4.2.0

Methods

rnf :: ExitCode -> () #

NFData CChar

Since: 1.4.0.0

Methods

rnf :: CChar -> () #

NFData CSChar

Since: 1.4.0.0

Methods

rnf :: CSChar -> () #

NFData CUChar

Since: 1.4.0.0

Methods

rnf :: CUChar -> () #

NFData CShort

Since: 1.4.0.0

Methods

rnf :: CShort -> () #

NFData CUShort

Since: 1.4.0.0

Methods

rnf :: CUShort -> () #

NFData CInt

Since: 1.4.0.0

Methods

rnf :: CInt -> () #

NFData CUInt

Since: 1.4.0.0

Methods

rnf :: CUInt -> () #

NFData CLong

Since: 1.4.0.0

Methods

rnf :: CLong -> () #

NFData CULong

Since: 1.4.0.0

Methods

rnf :: CULong -> () #

NFData CLLong

Since: 1.4.0.0

Methods

rnf :: CLLong -> () #

NFData CULLong

Since: 1.4.0.0

Methods

rnf :: CULLong -> () #

NFData CFloat

Since: 1.4.0.0

Methods

rnf :: CFloat -> () #

NFData CDouble

Since: 1.4.0.0

Methods

rnf :: CDouble -> () #

NFData CPtrdiff

Since: 1.4.0.0

Methods

rnf :: CPtrdiff -> () #

NFData CSize

Since: 1.4.0.0

Methods

rnf :: CSize -> () #

NFData CWchar

Since: 1.4.0.0

Methods

rnf :: CWchar -> () #

NFData CSigAtomic

Since: 1.4.0.0

Methods

rnf :: CSigAtomic -> () #

NFData CClock

Since: 1.4.0.0

Methods

rnf :: CClock -> () #

NFData CTime

Since: 1.4.0.0

Methods

rnf :: CTime -> () #

NFData CUSeconds

Since: 1.4.0.0

Methods

rnf :: CUSeconds -> () #

NFData CSUSeconds

Since: 1.4.0.0

Methods

rnf :: CSUSeconds -> () #

NFData CFile

Since: 1.4.0.0

Methods

rnf :: CFile -> () #

NFData CFpos

Since: 1.4.0.0

Methods

rnf :: CFpos -> () #

NFData CJmpBuf

Since: 1.4.0.0

Methods

rnf :: CJmpBuf -> () #

NFData CIntPtr

Since: 1.4.0.0

Methods

rnf :: CIntPtr -> () #

NFData CUIntPtr

Since: 1.4.0.0

Methods

rnf :: CUIntPtr -> () #

NFData CIntMax

Since: 1.4.0.0

Methods

rnf :: CIntMax -> () #

NFData CUIntMax

Since: 1.4.0.0

Methods

rnf :: CUIntMax -> () #

NFData All

Since: 1.4.0.0

Methods

rnf :: All -> () #

NFData Any

Since: 1.4.0.0

Methods

rnf :: Any -> () #

NFData Fingerprint

Since: 1.4.0.0

Methods

rnf :: Fingerprint -> () #

NFData SrcLoc

Since: 1.4.2.0

Methods

rnf :: SrcLoc -> () #

NFData a => NFData [a] 

Methods

rnf :: [a] -> () #

NFData a => NFData (Maybe a) 

Methods

rnf :: Maybe a -> () #

NFData a => NFData (Ratio a) 

Methods

rnf :: Ratio a -> () #

NFData (Ptr a)

Since: 1.4.2.0

Methods

rnf :: Ptr a -> () #

NFData (FunPtr a)

Since: 1.4.2.0

Methods

rnf :: FunPtr a -> () #

NFData a => NFData (Identity a)

Since: 1.4.0.0

Methods

rnf :: Identity a -> () #

NFData a => NFData (Min a)

Since: 1.4.2.0

Methods

rnf :: Min a -> () #

NFData a => NFData (Max a)

Since: 1.4.2.0

Methods

rnf :: Max a -> () #

NFData a => NFData (First a)

Since: 1.4.2.0

Methods

rnf :: First a -> () #

NFData a => NFData (Last a)

Since: 1.4.2.0

Methods

rnf :: Last a -> () #

NFData m => NFData (WrappedMonoid m)

Since: 1.4.2.0

Methods

rnf :: WrappedMonoid m -> () #

NFData a => NFData (Option a)

Since: 1.4.2.0

Methods

rnf :: Option a -> () #

NFData a => NFData (NonEmpty a)

Since: 1.4.2.0

Methods

rnf :: NonEmpty a -> () #

NFData (Fixed a)

Since: 1.3.0.0

Methods

rnf :: Fixed a -> () #

NFData a => NFData (Complex a) 

Methods

rnf :: Complex a -> () #

NFData (StableName a)

Since: 1.4.0.0

Methods

rnf :: StableName a -> () #

NFData a => NFData (ZipList a)

Since: 1.4.0.0

Methods

rnf :: ZipList a -> () #

NFData a => NFData (Dual a)

Since: 1.4.0.0

Methods

rnf :: Dual a -> () #

NFData a => NFData (Sum a)

Since: 1.4.0.0

Methods

rnf :: Sum a -> () #

NFData a => NFData (Product a)

Since: 1.4.0.0

Methods

rnf :: Product a -> () #

NFData a => NFData (First a)

Since: 1.4.0.0

Methods

rnf :: First a -> () #

NFData a => NFData (Last a)

Since: 1.4.0.0

Methods

rnf :: Last a -> () #

NFData (IORef a)

NOTE: Only strict in the reference and not the referenced value.

Since: 1.4.2.0

Methods

rnf :: IORef a -> () #

NFData a => NFData (Down a)

Since: 1.4.0.0

Methods

rnf :: Down a -> () #

NFData (MVar a)

NOTE: Only strict in the reference and not the referenced value.

Since: 1.4.2.0

Methods

rnf :: MVar a -> () #

NFData a => NFData (Digit a) 

Methods

rnf :: Digit a -> () #

NFData a => NFData (Node a) 

Methods

rnf :: Node a -> () #

NFData a => NFData (Elem a) 

Methods

rnf :: Elem a -> () #

NFData a => NFData (FingerTree a) 

Methods

rnf :: FingerTree a -> () #

NFData a => NFData (Seq a) 

Methods

rnf :: Seq a -> () #

NFData a => NFData (Set a) 

Methods

rnf :: Set a -> () #

NFData (Vector a) 

Methods

rnf :: Vector a -> () #

NFData (Vector a) 

Methods

rnf :: Vector a -> () #

NFData (IVar a) # 

Methods

rnf :: IVar a -> () #

NFData (IVar a) # 

Methods

rnf :: IVar a -> () #

NFData (a -> b)

This instance is for convenience and consistency with seq. This assumes that WHNF is equivalent to NF for functions.

Since: 1.3.0.0

Methods

rnf :: (a -> b) -> () #

(NFData a, NFData b) => NFData (Either a b) 

Methods

rnf :: Either a b -> () #

(NFData a, NFData b) => NFData (a, b) 

Methods

rnf :: (a, b) -> () #

(NFData a, NFData b) => NFData (Array a b) 

Methods

rnf :: Array a b -> () #

(NFData a, NFData b) => NFData (Arg a b)

Since: 1.4.2.0

Methods

rnf :: Arg a b -> () #

NFData (Proxy k a)

Since: 1.4.0.0

Methods

rnf :: Proxy k a -> () #

NFData (STRef s a)

NOTE: Only strict in the reference and not the referenced value.

Since: 1.4.2.0

Methods

rnf :: STRef s a -> () #

(NFData k, NFData a) => NFData (Map k a) 

Methods

rnf :: Map k a -> () #

NFData (MVector s a) 

Methods

rnf :: MVector s a -> () #

NFData (MVector s a) 

Methods

rnf :: MVector s a -> () #

(NFData a, NFData b, NFData c) => NFData (a, b, c) 

Methods

rnf :: (a, b, c) -> () #

NFData a => NFData (Const k a b)

Since: 1.4.0.0

Methods

rnf :: Const k a b -> () #

(NFData a, NFData b, NFData c, NFData d) => NFData (a, b, c, d) 

Methods

rnf :: (a, b, c, d) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => NFData (a1, a2, a3, a4, a5) 

Methods

rnf :: (a1, a2, a3, a4, a5) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => NFData (a1, a2, a3, a4, a5, a6) 

Methods

rnf :: (a1, a2, a3, a4, a5, a6) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => NFData (a1, a2, a3, a4, a5, a6, a7) 

Methods

rnf :: (a1, a2, a3, a4, a5, a6, a7) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8) => NFData (a1, a2, a3, a4, a5, a6, a7, a8) 

Methods

rnf :: (a1, a2, a3, a4, a5, a6, a7, a8) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8, NFData a9) => NFData (a1, a2, a3, a4, a5, a6, a7, a8, a9) 

Methods

rnf :: (a1, a2, a3, a4, a5, a6, a7, a8, a9) -> () #

(0.3) Reexport NFData for fully-strict operators.