parallel-2.0.0.0: Parallel programming library

Portabilityportable
Stabilityexperimental
Maintainerlibraries@haskell.org

Control.Parallel.Strategies

Contents

Description

Parallel Evaluation Strategies, or Strategies for short, specify a way to evaluate a structure with components in sequence or in parallel.

Strategies are for expressing deterministic parallelism: the result of the program is unaffected by evaluating in parallel. For non-deterministic parallel programming, see Control.Concurrent.

Strategies let you separate the description of parallelism from the logic of your program, enabling modular parallelism.

Version 1.x

The original Strategies design is described in 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 -> 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 Applicative type Eval. e.g. parList s = unEval $ traverse (Par . s)
  • parList has been generalised to parTraverse, which works on any Traversable type.
  • 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 is deprecated; please use the DeepSeq class in the deepseq package instead. Note that since the Strategy type changed, rnf is no longer a Strategy: use rdeepseq instead.

Synopsis

Strategy type and basic operations

type Strategy a = a -> 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.

using :: a -> Strategy a -> aSource

evaluate a value using the given Strategy.

 using x s = s x

withStrategy :: Strategy a -> a -> aSource

evaluate a value using the given Strategy. This is simply using with the arguments reversed, and is equal to '($)'.

rwhnf :: Strategy aSource

A Strategy that simply evaluates its argument to Weak Head Normal Form (i.e. evaluates it as far as the topmost constructor).

rdeepseq :: DeepSeq a => Strategy aSource

A Strategy that fully evaluates its argument

 rdeepseq a = deepseq a `pseq` a

Tuple strategies

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

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

General traversals

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

A strategy that traverses a container data type with an instance of Traversable, and evaluates each of the elements in left-to-right sequence using the supplied strategy.

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

A strategy that traverses a container data type with an instance of Traversable, and sparks each of the elements using the supplied strategy.

List strategies

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

Spark each of the elements of a list using the given strategy. Equivalent to parTraverse at the list type.

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

Evaluate each of the elements of a list sequentially from left to right using the given strategy. Equivalent to seqTraverse at the list type.

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

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

Applies a strategy to the nth element of list when the head is demanded. More precisely:

  • semantics: parBuffer n s = id :: [a] -> [a]
  • dynamic behaviour: evalutates the nth element of the list when the head is demanded.

The idea is to provide a `rolling buffer' of length n. It is a better than parList for a lazy stream, because parList will evaluate the entire list, whereas parBuffer will only evaluate a fixed number of elements ahead.

Simple list strategies

parListWHNF :: Strategy [a]Source

version of parList specialised to rwhnf. This version is much simpler, and may be faster than 'parList rwhnf'. You should never need to use this directly, since 'parList rwhnf' is automatically optimised to parListWHNF. It is here for experimentation purposes only.

parBufferWHNF :: Int -> Strategy [a]Source

version of parBuffer specialised to rwhnf. You should never need to use this directly, since 'parBuffer rwhnf' is automatically optimised to parBufferWHNF. It is here for experimentation purposes only.

Strategy composition operators

($|) :: (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.

Building strategies

data Eval a Source

Eval is an Applicative Functor that makes it easier to define parallel strategies that involve traversing structures.

a Seq value will be evaluated strictly in sequence in its context, whereas a Par value wraps an expression that may be evaluated in parallel. The Applicative instance allows sequential composition, making it possible to describe an evaluateion strategy by composing Par and Seq with <*>.

For example,

 parList :: Strategy a -> Strategy [a]
 parList strat = unEval . traverse (Par . strat)
 seqPair :: Strategy a -> Strategy b -> Strategy (a,b)
 seqPair f g (a,b) = unEval $ (,) <$> Seq (f a) <*> Seq (g b)

Constructors

Seq a 
Par a 
Lazy a 

unEval :: Eval a -> aSource

Deprecated functionality

class NFData a whereSource

Methods

rnf :: a -> ()Source

Reduces its argument to (head) normal form.

Instances

NFData Bool 
NFData Char 
NFData Double 
NFData Float 
NFData Int 
NFData Int8 
NFData Int16 
NFData Int32 
NFData Int64 
NFData Integer 
NFData Word8 
NFData Word16 
NFData Word32 
NFData Word64 
NFData () 
NFData IntSet 
NFData a => NFData [a] 
(Integral a, NFData a) => NFData (Ratio a) 
(RealFloat a, NFData a) => NFData (Complex a) 
NFData a => NFData (Maybe a) 
NFData a => NFData (Tree a) 
NFData a => NFData (IntMap a) 
NFData a => NFData (Set a) 
(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) 

type Done = ()Source

demanding :: a -> Done -> aSource

sparking :: a -> Done -> aSource

r0 :: a -> ()Source