parallel-3.2.0.3: Parallel programming library

Portabilityportable
Stabilityexperimental
Maintainerlibraries@haskell.org
Safe HaskellSafe-Infered

Control.Parallel.Strategies

Contents

Description

Parallel Evaluation Strategies, or Strategies for short, provide ways to express parallel computations. Strategies have the following key features:

  • Strategies express deterministic parallelism: the result of the program is unaffected by evaluating in parallel. The parallel tasks evaluated by a Strategy may have no side effects. For non-deterministic parallel programming, see Control.Concurrent.
  • Strategies let you separate the description of the parallelism from the logic of your program, enabling modular parallelism. The basic idea is to build a lazy data structure representing the computation, and then write a Strategy that describes how to traverse the data structure and evaluate components of it sequentially or in parallel.
  • Strategies are compositional: larger strategies can be built by gluing together smaller ones.
  • Monad and Applicative instances are provided, for quickly building strategies that involve traversing structures in a regular way.

For API history and changes in this release, see Control.Parallel.Strategies.

Synopsis

The strategy type

type Strategy a = a -> Eval aSource

A Strategy is a function that embodies a parallel evaluation strategy. The function traverses (parts of) its argument, evaluating subexpressions in parallel or in sequence.

A Strategy may do an arbitrary amount of evaluation of its argument, but should not return a value different from the one it was passed.

Parallel computations may be discarded by the runtime system if the program no longer requires their result, which is why a Strategy function returns a new value equivalent to the old value. The intention is that the program applies the Strategy to a structure, and then uses the returned value, discarding the old value. This idiom is expressed by the using function.

Application of strategies

using :: a -> Strategy a -> aSource

Evaluate a value using the given Strategy.

 x `using` s = runEval (s x)

withStrategy :: Strategy a -> a -> aSource

evaluate a value using the given Strategy. This is simply using with the arguments reversed.

Composition of strategies

dot :: Strategy a -> Strategy a -> Strategy aSource

Compose two strategies sequentially. This is the analogue to function composition on strategies.

 strat2 `dot` strat1 == strat2 . withStrategy strat1

Basic strategies

r0 :: Strategy aSource

r0 performs *no* evaluation.

 r0 == evalSeq Control.Seq.r0

rseq :: Strategy aSource

rseq evaluates its argument to weak head normal form.

 rseq == evalSeq Control.Seq.rseq

rdeepseq :: NFData a => Strategy aSource

rdeepseq fully evaluates its argument.

 rdeepseq == evalSeq Control.Seq.rdeepseq

rpar :: a -> Eval aSource

rpar sparks its argument (for evaluation in parallel).

rparWith :: Strategy a -> Strategy aSource

instead of saying rpar dot strat, you can say rparWith strat. Compared to rpar, rparWith

  • does not exit the Eval monad
  • does not have a built-in rseq, so for example `rparWith r0` behaves as you might expect (it is a strategy that creates a spark that does no evaluation).

Injection of sequential strategies

evalSeq :: SeqStrategy a -> Strategy aSource

Inject a sequential strategy (ie. coerce a sequential strategy to a general strategy).

Thanks to evalSeq, the type Control.Seq.Strategy a is a subtype of Strategy a.

type SeqStrategy a = Strategy aSource

a name for Control.Seq.Strategy, for documetnation only.

Strategies for traversable data types

evalTraversable :: Traversable t => Strategy a -> Strategy (t a)Source

Evaluate the elements of a traversable data structure according to the given strategy.

parTraversable :: Traversable t => Strategy a -> Strategy (t a)Source

Like evalTraversable but evaluates all elements in parallel.

Strategies for lists

evalList :: Strategy a -> Strategy [a]Source

Evaluate each element of a list according to the given strategy. Equivalent to evalTraversable at the list type.

parList :: Strategy a -> Strategy [a]Source

Evaluate each element of a list in parallel according to given strategy. Equivalent to parTraversable at the list type.

evalListN :: Int -> Strategy a -> Strategy [a]Source

Evaluate the first n elements of a list according to the given strategy.

parListN :: Int -> Strategy a -> Strategy [a]Source

Like evalListN but evaluates the first n elements in parallel.

evalListNth :: Int -> Strategy a -> Strategy [a]Source

Evaluate the nth element of a list (if there is such) according to the given strategy. The spine of the list up to the nth element is evaluated as a side effect.

parListNth :: Int -> Strategy a -> Strategy [a]Source

Like evalListN but evaluates the nth element in parallel.

evalListSplitAt :: Int -> Strategy [a] -> Strategy [a] -> Strategy [a]Source

evaListSplitAt n stratPref stratSuff evaluates the prefix (of length n) of a list according to stratPref and its the suffix according to stratSuff.

parListSplitAt :: Int -> Strategy [a] -> Strategy [a] -> Strategy [a]Source

Like evalListSplitAt but evaluates both sublists in parallel.

parListChunk :: Int -> Strategy a -> Strategy [a]Source

Divides a list into chunks, and applies the strategy evalList strat to each chunk in parallel.

It is expected that this function will be replaced by a more generic clustering infrastructure in the future.

If the chunk size is 1 or less, parListChunk is equivalent to parList

parMap :: Strategy b -> (a -> b) -> [a] -> [b]Source

A combination of parList and map, encapsulating a common pattern:

 parMap strat f = withStrategy (parList strat) . map f

Strategies for lazy lists

evalBuffer :: Int -> Strategy a -> Strategy [a]Source

evalBuffer is a rolling buffer strategy combinator for (lazy) lists.

evalBuffer is not as compositional as the type suggests. In fact, it evaluates list elements at least to weak head normal form, disregarding a strategy argument r0.

 evalBuffer n r0 == evalBuffer n rseq

parBuffer :: Int -> Strategy a -> Strategy [a]Source

Like evalBuffer but evaluates the list elements in parallel when pushing them into the buffer.

Strategies for tuples

Evaluate the components of a tuple according to the given strategies.

evalTuple3 :: Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c)Source

evalTuple4 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy (a, b, c, d)Source

evalTuple5 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy (a, b, c, d, e)Source

evalTuple6 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy (a, b, c, d, e, f)Source

evalTuple7 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy g -> Strategy (a, b, c, d, e, f, g)Source

evalTuple8 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy g -> Strategy h -> Strategy (a, b, c, d, e, f, g, h)Source

evalTuple9 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy g -> Strategy h -> Strategy i -> Strategy (a, b, c, d, e, f, g, h, i)Source

Evaluate the components of a tuple in parallel according to the given strategies.

parTuple3 :: Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c)Source

parTuple4 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy (a, b, c, d)Source

parTuple5 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy (a, b, c, d, e)Source

parTuple6 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy (a, b, c, d, e, f)Source

parTuple7 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy g -> Strategy (a, b, c, d, e, f, g)Source

parTuple8 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy g -> Strategy h -> Strategy (a, b, c, d, e, f, g, h)Source

parTuple9 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy g -> Strategy h -> Strategy i -> Strategy (a, b, c, d, e, f, g, h, i)Source

Strategic function application

($|) :: (a -> b) -> Strategy a -> a -> bSource

Sequential function application. The argument is evaluated using the given strategy before it is given to the function.

($||) :: (a -> b) -> Strategy a -> a -> bSource

Parallel function application. The argument is evaluated using the given strategy, in parallel with the function application.

(.|) :: (b -> c) -> Strategy b -> (a -> b) -> a -> cSource

Sequential function composition. The result of the second function is evaluated using the given strategy, and then given to the first function.

(.||) :: (b -> c) -> Strategy b -> (a -> b) -> a -> cSource

Parallel function composition. The result of the second function is evaluated using the given strategy, in parallel with the application of the first function.

(-|) :: (a -> b) -> Strategy b -> (b -> c) -> a -> cSource

Sequential inverse function composition, for those who read their programs from left to right. The result of the first function is evaluated using the given strategy, and then given to the second function.

(-||) :: (a -> b) -> Strategy b -> (b -> c) -> a -> cSource

Parallel inverse function composition, for those who read their programs from left to right. The result of the first function is evaluated using the given strategy, in parallel with the application of the second function.

For Strategy programmers

data Eval a Source

Eval is a Monad that makes it easier to define parallel strategies. It is a strict identity monad: that is, in

 m >>= f

m is evaluated before the result is passed to f.

 instance Monad Eval where
   return  = Done
   m >>= k = case m of
               Done x -> k x

If you wanted to construct a Strategy for a pair that sparked the first component in parallel and then evaluated the second component, you could write

 myStrat :: Strategy (a,b)
 myStrat (a,b) = do { a' <- rpar a; b' <- rseq b; return (a',b') }

Alternatively, you could write this more compactly using the Applicative style as

 myStrat (a,b) = (,) <$> rpar a <*> rseq b

runEval :: Eval a -> aSource

Pull the result out of the monad.

API History

The strategies library has a long history. What follows is a summary of how the current design evolved, and is mostly of interest to those who are familiar with an older version, or need to adapt old code to use the newer API.

Version 1.x

The original Strategies design is described in Algorithm + Strategy = Parallelism http://www.macs.hw.ac.uk/~dsg/gph/papers/html/Strategies/strategies.html and the code was written by Phil Trinder, Hans-Wolfgang Loidl, Kevin Hammond et al.

Version 2.x

Later, during work on the shared-memory implementation of parallelism in GHC, we discovered that the original formulation of Strategies had some problems, in particular it lead to space leaks and difficulties expressing speculative parallelism. Details are in the paper Runtime Support for Multicore Haskell http://www.haskell.org/~simonmar/papers/multicore-ghc.pdf.

This module has been rewritten in version 2. The main change is to the 'Strategy a' type synonym, which was previously a -> Done and is now a -> Eval a. This change helps to fix the space leak described in "Runtime Support for Multicore Haskell". The problem is that the runtime will currently retain the memory referenced by all sparks, until they are evaluated. Hence, we must arrange to evaluate all the sparks eventually, just in case they aren't evaluated in parallel, so that they don't cause a space leak. This is why we must return a "new" value after applying a Strategy, so that the application can evaluate each spark created by the Strategy.

The simple rule is this: you must use the result of applying a Strategy if the strategy creates parallel sparks, and you should probably discard the the original value. If you don't do this, currently it may result in a space leak. In the future (GHC 6.14), it will probably result in lost parallelism instead, as we plan to change GHC so that unreferenced sparks are discarded rather than retained (we can't make this change until most code is switched over to this new version of Strategies, because code using the old verison of Strategies would be broken by the change in policy).

The other changes in version 2.x are:

  • Strategies can now be defined using a convenient Monad/Applicative type, Eval. e.g. parList s = traverse (Par . (`using` s))
  • parList has been generalised to parTraverse, which works on any Traversable type, and similarly seqList has been generalised to seqTraverse
  • parList and parBuffer have versions specialised to rwhnf, and there are transformation rules that automatically translate e.g. parList rwnhf into a call to the optimised version.
  • NFData has been moved to Control.DeepSeq in the deepseq package. Note that since the Strategy type changed, rnf is no longer a Strategy: use rdeepseq instead.

Version 2.1 moved NFData into a separate package, deepseq.

Version 2.2 changed the type of Strategy to a -> Eval a, and re-introduced the r0 strategy which was missing in version 2.1.

Version 2.3 simplified the Eval type, so that Eval is now just the strict identity monad. This change and various other improvements and refactorings are thanks to Patrick Maier who noticed that Eval didn't satisfy the monad laws, and that a simpler version would fix that problem.

(version 2.3 was not released on Hackage).

Version 3 introduced a major overhaul of the API, to match what is presented in the paper

Seq no More: Better Strategies for Parallel Haskell http://www.haskell.org/~simonmar/papers/strategies.pdf

The major differenes in the API are:

The naming scheme is now as follows:

  • Basic polymorphic strategies (of type Strategy a) are called r.... Examples: r0, rseq, rpar, rdeepseq.
  • A strategy combinator for a particular type constructor or constructor class T is called evalT..., parT... or seqT....
  • The seqT... combinators (residing in module Control.Seq) yield sequential strategies. Thus, seqT... combinators cannot spark, nor can the sequential strategies to which they may be applied. Examples: seqTuple2, seqListN, seqFoldable.
  • The evalT... combinators do not spark themselves, yet they may be applied to strategies that do spark. (They may also be applied to non-sparking strategies; however, in that case the corresponding seqT... combinator might be a better choice.) Examples: evalTuple2, evalListN, evalTraversable.
  • The parT... combinators, which are derived from their evalT... counterparts, do spark. They may be applied to all strategies, whether sparking or not. Examples: parTuple2, parListN, parTraversable.
  • An exception to the type driven naming scheme are evalBuffer and parBuffer, which are not named after their type constructor (lists) but after their function (rolling buffer of fixed size).

Backwards compatibility

These functions and types are all deprecated, and will be removed in a future release. In all cases they have been either renamed or replaced with equivalent functionality.

type Done = ()Source

DEPRECCATED: replaced by the Eval monad

demanding :: a -> Done -> aSource

DEPRECATED: Use pseq or $| instead

sparking :: a -> Done -> aSource

DEPRECATED: Use par or $|| instead

(>|) :: Done -> Done -> DoneSource

DEPRECATED: Use pseq or $| instead

(>||) :: Done -> Done -> DoneSource

DEPRECATED: Use par or $|| instead

rwhnf :: Strategy aSource

DEPRECATED: renamed to rseq

unEval :: Eval a -> aSource

DEPRECATED: renamed to runEval

seqTraverse :: Traversable t => Strategy a -> Strategy (t a)Source

DEPRECATED: renamed to evalTraversable

parTraverse :: Traversable t => Strategy a -> Strategy (t a)Source

DEPRECATED: renamed to parTraversable

seqList :: Strategy a -> Strategy [a]Source

DEPRECATED: renamed to evalList

seqPair :: Strategy a -> Strategy b -> Strategy (a, b)Source

DEPRECATED: renamed to evalTuple2

parPair :: Strategy a -> Strategy b -> Strategy (a, b)Source

DEPRECATED: renamed to parTuple2

seqTriple :: Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c)Source

DEPRECATED: renamed to evalTuple3

parTriple :: Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c)Source

DEPRECATED: renamed to parTuple3

For API completeness

so users of rdeepseq aren't required to import Control.DeepSeq:

class NFData a

A class of types that can be fully evaluated.

Instances

NFData Bool 
NFData Char 
NFData Double 
NFData Float 
NFData Int 
NFData Int8 
NFData Int16 
NFData Int32 
NFData Int64 
NFData Integer 
NFData Word 
NFData Word8 
NFData Word16 
NFData Word32 
NFData Word64 
NFData () 
NFData Version 
NFData a => NFData [a] 
(Integral a, NFData a) => NFData (Ratio a) 
NFData (Fixed a) 
(RealFloat a, NFData a) => NFData (Complex a) 
NFData a => NFData (Maybe a) 
NFData (a -> b)

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

(NFData a, NFData b) => NFData (Either a b) 
(NFData a, NFData b) => NFData (a, b) 
(Ix a, NFData a, NFData b) => NFData (Array a b) 
(NFData k, NFData a) => NFData (Map k a) 
(NFData a, NFData b, NFData c) => NFData (a, b, c) 
(NFData a, NFData b, NFData c, NFData d) => NFData (a, b, c, d) 
(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => NFData (a1, a2, a3, a4, a5) 
(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => NFData (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) 
(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) 
(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)