-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Parallel programming library -- -- This package provides a library for parallel programming. @package parallel @version 3.2.0.3 -- | Parallel Constructs module Control.Parallel -- | Indicates that it may be beneficial to evaluate the first argument in -- parallel with the second. Returns the value of the second argument. -- -- a `par` b is exactly equivalent semantically to -- b. -- -- par is generally used when the value of a is likely -- to be required later, but not immediately. Also it is a good idea to -- ensure that a is not a trivial computation, otherwise the -- cost of spawning it in parallel overshadows the benefits obtained by -- running it in parallel. -- -- Note that actual parallelism is only supported by certain -- implementations (GHC with the -threaded option, and GPH, for -- now). On other implementations, par a b = b. par :: a -> b -> b -- | Semantically identical to seq, but with a subtle operational -- difference: seq is strict in both its arguments, so the -- compiler may, for example, rearrange a `seq` b into -- b `seq` a `seq` b. This is normally no problem -- when using seq to express strictness, but it can be a problem -- when annotating code for parallelism, because we need more control -- over the order of evaluation; we may want to evaluate a -- before b, because we know that b has already been -- sparked in parallel with par. -- -- This is why we have pseq. In contrast to seq, -- pseq is only strict in its first argument (as far as the -- compiler is concerned), which restricts the transformations that the -- compiler can do, and ensures that the user can retain control of the -- evaluation order. pseq :: a -> b -> b -- | Sequential strategies provide ways to compositionally specify the -- degree of evaluation of a data type between the extremes of no -- evaluation and full evaluation. Sequential strategies may be viewed as -- complimentary to the parallel ones (see module -- Control.Parallel.Strategies). module Control.Seq -- | The type Strategy a is a -> (). Thus, a -- strategy is a function whose sole purpose it is to evaluate its -- argument (either in full or in part). type Strategy a = a -> () -- | Evaluate a value using the given strategy. using :: a -> Strategy a -> a -- | Evaluate a value using the given strategy. This is simply using -- with arguments reversed. withStrategy :: Strategy a -> a -> a -- | r0 performs *no* evaluation. r0 :: Strategy a -- | rseq evaluates its argument to weak head normal form. rseq :: Strategy a -- | rdeepseq fully evaluates its argument. Relies on class -- NFData from module Control.DeepSeq. rdeepseq :: NFData a => Strategy a -- | Evaluate each element of a list according to the given strategy. This -- function is a specialisation of seqFoldable to lists. seqList :: Strategy a -> Strategy [a] -- | Evaluate the first n elements of a list according to the given -- strategy. seqListN :: Int -> Strategy a -> Strategy [a] -- | 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. seqListNth :: Int -> Strategy a -> Strategy [a] -- | Evaluate the elements of a foldable data structure according to the -- given strategy. seqFoldable :: Foldable t => Strategy a -> Strategy (t a) -- | Evaluate the keys and values of a map according to the given -- strategies. seqMap :: Strategy k -> Strategy v -> Strategy (Map k v) -- | Evaluate the elements of an array according to the given strategy. -- Evaluation of the array bounds may be triggered as a side effect. seqArray :: Ix i => Strategy a -> Strategy (Array i a) -- | Evaluate the bounds of an array according to the given strategy. seqArrayBounds :: Ix i => Strategy i -> Strategy (Array i a) seqTuple2 :: Strategy a -> Strategy b -> Strategy (a, b) seqTuple3 :: Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c) seqTuple4 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy (a, b, c, d) seqTuple5 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy (a, b, c, d, e) seqTuple6 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy (a, b, c, d, e, f) seqTuple7 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy g -> Strategy (a, b, c, d, e, f, g) seqTuple8 :: 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) seqTuple9 :: 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) -- | Parallel Evaluation Strategies, or Strategies for short, provide ways -- to express parallel computations. Strategies have the following key -- features: -- -- -- -- For API history and changes in this release, see -- Control.Parallel.Strategies#history. module Control.Parallel.Strategies -- | 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. type Strategy a = a -> Eval a -- | Evaluate a value using the given Strategy. -- --
--   x `using` s = runEval (s x)
--   
using :: a -> Strategy a -> a -- | evaluate a value using the given Strategy. This is simply -- using with the arguments reversed. withStrategy :: Strategy a -> a -> a -- | Compose two strategies sequentially. This is the analogue to function -- composition on strategies. -- --
--   strat2 `dot` strat1 == strat2 . withStrategy strat1
--   
dot :: Strategy a -> Strategy a -> Strategy a -- | r0 performs *no* evaluation. -- --
--   r0 == evalSeq Control.Seq.r0
--   
r0 :: Strategy a -- | rseq evaluates its argument to weak head normal form. -- --
--   rseq == evalSeq Control.Seq.rseq
--   
rseq :: Strategy a -- | rdeepseq fully evaluates its argument. -- --
--   rdeepseq == evalSeq Control.Seq.rdeepseq
--   
rdeepseq :: NFData a => Strategy a -- | rpar sparks its argument (for evaluation in parallel). rpar :: a -> Eval a -- | instead of saying rpar dot strat, you can say -- rparWith strat. Compared to rpar, rparWith -- -- rparWith :: Strategy a -> Strategy a -- | 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. evalSeq :: SeqStrategy a -> Strategy a -- | a name for Control.Seq.Strategy, for documetnation only. type SeqStrategy a = Strategy a -- | Evaluate the elements of a traversable data structure according to the -- given strategy. evalTraversable :: Traversable t => Strategy a -> Strategy (t a) -- | Like evalTraversable but evaluates all elements in parallel. parTraversable :: Traversable t => Strategy a -> Strategy (t a) -- | Evaluate each element of a list according to the given strategy. -- Equivalent to evalTraversable at the list type. evalList :: Strategy a -> Strategy [a] -- | Evaluate each element of a list in parallel according to given -- strategy. Equivalent to parTraversable at the list type. parList :: Strategy a -> Strategy [a] -- | Evaluate the first n elements of a list according to the given -- strategy. evalListN :: Int -> Strategy a -> Strategy [a] -- | Like evalListN but evaluates the first n elements in parallel. parListN :: Int -> Strategy a -> Strategy [a] -- | 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. evalListNth :: Int -> Strategy a -> Strategy [a] -- | Like evalListN but evaluates the nth element in parallel. parListNth :: Int -> Strategy a -> Strategy [a] -- | evaListSplitAt n stratPref stratSuff evaluates the -- prefix (of length n) of a list according to -- stratPref and its the suffix according to stratSuff. evalListSplitAt :: Int -> Strategy [a] -> Strategy [a] -> Strategy [a] -- | Like evalListSplitAt but evaluates both sublists in parallel. parListSplitAt :: Int -> Strategy [a] -> Strategy [a] -> Strategy [a] -- | 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 parListChunk :: Int -> Strategy a -> Strategy [a] -- | A combination of parList and map, encapsulating a common -- pattern: -- --
--   parMap strat f = withStrategy (parList strat) . map f
--   
parMap :: Strategy b -> (a -> b) -> [a] -> [b] -- | 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
--   
evalBuffer :: Int -> Strategy a -> Strategy [a] -- | Like evalBuffer but evaluates the list elements in parallel -- when pushing them into the buffer. parBuffer :: Int -> Strategy a -> Strategy [a] evalTuple2 :: Strategy a -> Strategy b -> Strategy (a, b) evalTuple3 :: Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c) evalTuple4 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy (a, b, c, d) evalTuple5 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy (a, b, c, d, e) evalTuple6 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy (a, b, c, d, e, f) evalTuple7 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy g -> Strategy (a, b, c, d, e, f, g) 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) 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) parTuple2 :: Strategy a -> Strategy b -> Strategy (a, b) parTuple3 :: Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c) parTuple4 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy (a, b, c, d) parTuple5 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy (a, b, c, d, e) parTuple6 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy (a, b, c, d, e, f) parTuple7 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy g -> Strategy (a, b, c, d, e, f, g) 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) 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) -- | Sequential function application. The argument is evaluated using the -- given strategy before it is given to the function. ($|) :: (a -> b) -> Strategy a -> a -> b -- | Parallel function application. The argument is evaluated using the -- given strategy, in parallel with the function application. ($||) :: (a -> b) -> Strategy a -> a -> b -- | 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 -> c) -- | Parallel function composition. The result of the second function is -- evaluated using the given strategy, in parallel with the application -- of the first function. (.||) :: (b -> c) -> Strategy b -> (a -> b) -> (a -> c) -- | 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 -> c) -- | 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. (-||) :: (a -> b) -> Strategy b -> (b -> c) -> (a -> c) -- | 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
--   
data Eval a -- | Pull the result out of the monad. runEval :: Eval a -> a -- | DEPRECCATED: replaced by the Eval monad type Done = () -- | DEPRECATED: Use pseq or $| instead demanding :: a -> Done -> a -- | DEPRECATED: Use par or $|| instead sparking :: a -> Done -> a -- | DEPRECATED: Use pseq or $| instead (>|) :: Done -> Done -> Done -- | DEPRECATED: Use par or $|| instead (>||) :: Done -> Done -> Done -- | DEPRECATED: renamed to rseq rwhnf :: Strategy a -- | DEPRECATED: renamed to runEval unEval :: Eval a -> a -- | DEPRECATED: renamed to evalTraversable seqTraverse :: Traversable t => Strategy a -> Strategy (t a) -- | DEPRECATED: renamed to parTraversable parTraverse :: Traversable t => Strategy a -> Strategy (t a) -- | DEPRECATED: renamed to evalList seqList :: Strategy a -> Strategy [a] -- | DEPRECATED: renamed to evalTuple2 seqPair :: Strategy a -> Strategy b -> Strategy (a, b) -- | DEPRECATED: renamed to parTuple2 parPair :: Strategy a -> Strategy b -> Strategy (a, b) -- | DEPRECATED: renamed to evalTuple3 seqTriple :: Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c) -- | DEPRECATED: renamed to parTuple3 parTriple :: Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c) -- | A class of types that can be fully evaluated. class NFData a instance Applicative Eval instance Functor Eval instance Monad Eval