parallel-3.2.2.0: Parallel programming library

Copyright(c) The University of Glasgow 2001-2010
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

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 a Source #

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 -> a infixl 0 Source #

Evaluate a value using the given Strategy.

x `using` s = runEval (s x)

withStrategy :: Strategy a -> a -> a Source #

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

usingIO :: a -> Strategy a -> IO a infixl 0 Source #

Evaluate a value using the given Strategy inside the IO monad. See also runEvalIO.

x `usingIO` s = runEvalIO (s x)

withStrategyIO :: Strategy a -> a -> IO a Source #

Evaluate a value using the given Strategy inside the IO monad. This is simply usingIO with the arguments reversed.

Composition of strategies

dot :: Strategy a -> Strategy a -> Strategy a infixr 9 Source #

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

For any strategies strat1, strat2, and strat3,

(strat1 `dot` strat2) `dot` strat3 == strat1 `dot` (strat2 `dot` strat3)
strat1 `dot` strat1 = strat1
strat1 `dot` r0 == strat1
strat2 `dot` strat1 == strat2 . withStrategy strat1

Basic strategies

r0 :: Strategy a Source #

r0 performs *no* evaluation.

r0 == evalSeq Control.Seq.r0

rseq :: Strategy a Source #

rseq evaluates its argument to weak head normal form.

rseq == evalSeq Control.Seq.rseq

rdeepseq :: NFData a => Strategy a Source #

rdeepseq fully evaluates its argument.

rdeepseq == evalSeq Control.Seq.rdeepseq

rpar :: Strategy a Source #

rpar sparks its argument (for evaluation in parallel).

rparWith :: Strategy a -> Strategy a Source #

Perform a computation in parallel using a strategy.

rparWith strat x

will spark strat x. Note that rparWith strat is not the same as rpar dot strat. Specifically, rpar dot strat always sparks a computation to reduce the result of the strategic computation to WHNF, while rparWith strat need not.

rparWith r0 = r0
rparWith rpar = rpar
rparWith rseq = rpar

rparWith rpar x creates a spark that immediately creates another spark to evaluate x. We consider this equivalent to rpar because there isn't any real additional parallelism. However, it is always less efficient because there's a bit of extra work to create the first (useless) spark. Similarly, rparWith r0 creates a spark that does precisely nothing. No real parallelism is added, but there is a bit of extra work to do nothing.

Injection of sequential strategies

evalSeq :: SeqStrategy a -> Strategy a Source #

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 a Source #

A name for Control.Seq.Strategy, for documentation 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. This nth is 0-based. For example, [1, 2, 3, 4, 5] using evalListNth 4 rseq will eval 5, not 4. 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 -> b Source #

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

($||) :: (a -> b) -> Strategy a -> a -> b Source #

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

(.|) :: (b -> c) -> Strategy b -> (a -> b) -> a -> c Source #

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 Source #

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 -> c Source #

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 Source #

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
Instances
Monad Eval Source # 
Instance details

Defined in Control.Parallel.Strategies

Methods

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

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

return :: a -> Eval a #

fail :: String -> Eval a #

Functor Eval Source # 
Instance details

Defined in Control.Parallel.Strategies

Methods

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

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

MonadFix Eval Source # 
Instance details

Defined in Control.Parallel.Strategies

Methods

mfix :: (a -> Eval a) -> Eval a #

Applicative Eval Source # 
Instance details

Defined in Control.Parallel.Strategies

Methods

pure :: a -> Eval a #

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

liftA2 :: (a -> b -> c) -> Eval a -> Eval b -> Eval c #

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

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

parEval :: Eval a -> Eval a Source #

parEval sparks the computation of its argument for evaluation in parallel. Unlike rpar . runEval, parEval

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

It is related to rparWith by the following equality:

parEval . strat = rparWith strat

runEval :: Eval a -> a Source #

Pull the result out of the monad.

runEvalIO :: Eval a -> IO a Source #

Run the evaluation in the IO monad. This allows sequencing of evaluations relative to IO actions.

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://community.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://community.haskell.org/~simonmar/papers/strategies.pdf

The major differences 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 #

Deprecated: The Strategy type is now a -> Eval a, not a -> Done

DEPRECCATED: replaced by the Eval monad

demanding :: a -> Done -> a Source #

Deprecated: Use pseq or $| instead

DEPRECATED: Use pseq or $| instead

sparking :: a -> Done -> a Source #

Deprecated: Use par or $|| instead

DEPRECATED: Use par or $|| instead

(>|) :: Done -> Done -> Done Source #

Deprecated: Use pseq or $| instead

DEPRECATED: Use pseq or $| instead

(>||) :: Done -> Done -> Done Source #

Deprecated: Use par or $|| instead

DEPRECATED: Use par or $|| instead

rwhnf :: Strategy a Source #

Deprecated: renamed to rseq

DEPRECATED: renamed to rseq

unEval :: Eval a -> a Source #

Deprecated: renamed to runEval

DEPRECATED: renamed to runEval

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

Deprecated: renamed to evalTraversable

DEPRECATED: renamed to evalTraversable

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

Deprecated: renamed to parTraversable

DEPRECATED: renamed to parTraversable

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

Deprecated: renamed to evalList

DEPRECATED: renamed to evalList

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

Deprecated: renamed to evalTuple2

DEPRECATED: renamed to evalTuple2

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

Deprecated: renamed to parTuple2

DEPRECATED: renamed to parTuple2

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

Deprecated: renamed to evalTuple3

DEPRECATED: renamed to evalTuple3

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

Deprecated: renamed to parTuple3

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.

Since: deepseq-1.1.0.0

Instances
NFData Bool 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Bool -> () #

NFData Char 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Char -> () #

NFData Double 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Double -> () #

NFData Float 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Float -> () #

NFData Int 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int -> () #

NFData Int8 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int8 -> () #

NFData Int16 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int16 -> () #

NFData Int32 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int32 -> () #

NFData Int64 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int64 -> () #

NFData Integer 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Integer -> () #

NFData Natural

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Natural -> () #

NFData Ordering 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Ordering -> () #

NFData Word 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word -> () #

NFData Word8 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word8 -> () #

NFData Word16 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word16 -> () #

NFData Word32 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word32 -> () #

NFData Word64 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word64 -> () #

NFData CallStack

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CallStack -> () #

NFData () 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: () -> () #

NFData TyCon

NOTE: Only defined for base-4.8.0.0 and later

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: TyCon -> () #

NFData Void

Defined as rnf = absurd.

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Void -> () #

NFData Unique

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Unique -> () #

NFData Version

Since: deepseq-1.3.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Version -> () #

NFData ThreadId

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: ThreadId -> () #

NFData ExitCode

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: ExitCode -> () #

NFData TypeRep

NOTE: Only defined for base-4.8.0.0 and later

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: TypeRep -> () #

NFData All

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: All -> () #

NFData Any

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Any -> () #

NFData CChar

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CChar -> () #

NFData CSChar

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CSChar -> () #

NFData CUChar

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUChar -> () #

NFData CShort

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CShort -> () #

NFData CUShort

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUShort -> () #

NFData CInt

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CInt -> () #

NFData CUInt

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUInt -> () #

NFData CLong

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CLong -> () #

NFData CULong

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CULong -> () #

NFData CLLong

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CLLong -> () #

NFData CULLong

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CULLong -> () #

NFData CBool

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CBool -> () #

NFData CFloat

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CFloat -> () #

NFData CDouble

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CDouble -> () #

NFData CPtrdiff

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CPtrdiff -> () #

NFData CSize

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CSize -> () #

NFData CWchar

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CWchar -> () #

NFData CSigAtomic

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CSigAtomic -> () #

NFData CClock

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CClock -> () #

NFData CTime

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CTime -> () #

NFData CUSeconds

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUSeconds -> () #

NFData CSUSeconds

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CSUSeconds -> () #

NFData CFile

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CFile -> () #

NFData CFpos

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CFpos -> () #

NFData CJmpBuf

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CJmpBuf -> () #

NFData CIntPtr

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CIntPtr -> () #

NFData CUIntPtr

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUIntPtr -> () #

NFData CIntMax

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CIntMax -> () #

NFData CUIntMax

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUIntMax -> () #

NFData Fingerprint

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Fingerprint -> () #

NFData SrcLoc

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: SrcLoc -> () #

NFData a => NFData [a] 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: [a] -> () #

NFData a => NFData (Maybe a) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Maybe a -> () #

NFData a => NFData (Ratio a) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Ratio a -> () #

NFData (Ptr a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Ptr a -> () #

NFData (FunPtr a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: FunPtr a -> () #

NFData a => NFData (Complex a) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Complex a -> () #

NFData (Fixed a)

Since: deepseq-1.3.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Fixed a -> () #

NFData a => NFData (Min a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Min a -> () #

NFData a => NFData (Max a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Max a -> () #

NFData a => NFData (First a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: First a -> () #

NFData a => NFData (Last a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Last a -> () #

NFData m => NFData (WrappedMonoid m)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: WrappedMonoid m -> () #

NFData a => NFData (Option a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Option a -> () #

NFData (StableName a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: StableName a -> () #

NFData a => NFData (ZipList a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: ZipList a -> () #

NFData a => NFData (Identity a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Identity a -> () #

NFData (IORef a)

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

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: IORef a -> () #

NFData a => NFData (First a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: First a -> () #

NFData a => NFData (Last a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Last a -> () #

NFData a => NFData (Dual a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Dual a -> () #

NFData a => NFData (Sum a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Sum a -> () #

NFData a => NFData (Product a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Product a -> () #

NFData a => NFData (Down a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Down a -> () #

NFData (MVar a)

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

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: MVar a -> () #

NFData a => NFData (NonEmpty a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: NonEmpty a -> () #

NFData (a -> b)

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

Since: deepseq-1.3.0.0

Instance details

Defined in Control.DeepSeq

Methods

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

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

Defined in Control.DeepSeq

Methods

rnf :: Either a b -> () #

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

Defined in Control.DeepSeq

Methods

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

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

Defined in Control.DeepSeq

Methods

rnf :: Array a b -> () #

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

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Arg a b -> () #

NFData (Proxy a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Proxy a -> () #

NFData (STRef s a)

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

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: STRef s a -> () #

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

Defined in Data.Map.Internal

Methods

rnf :: Map k a -> () #

(NFData a1, NFData a2, NFData a3) => NFData (a1, a2, a3) 
Instance details

Defined in Control.DeepSeq

Methods

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

NFData a => NFData (Const a b)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Const a b -> () #

NFData (a :~: b)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

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

(NFData a1, NFData a2, NFData a3, NFData a4) => NFData (a1, a2, a3, a4) 
Instance details

Defined in Control.DeepSeq

Methods

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

(NFData1 f, NFData1 g, NFData a) => NFData (Product f g a)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Product f g a -> () #

(NFData1 f, NFData1 g, NFData a) => NFData (Sum f g a)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Sum f g a -> () #

NFData (a :~~: b)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

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

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

Defined in Control.DeepSeq

Methods

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

(NFData1 f, NFData1 g, NFData a) => NFData (Compose f g a)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Compose f g a -> () #

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

Defined in Control.DeepSeq

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) 
Instance details

Defined in Control.DeepSeq

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) 
Instance details

Defined in Control.DeepSeq

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) 
Instance details

Defined in Control.DeepSeq

Methods

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