Copyright | (c) The University of Glasgow 2001-2010 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
- The strategy type
- Application of strategies
- Composition of strategies
- Basic strategies
- Injection of sequential strategies
- Strategies for traversable data types
- Strategies for lists
- Strategies for tuples
- Strategic function application
- For Strategy programmers
- API History
- Backwards compatibility
- For API completeness
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
andApplicative
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
- type Strategy a = a -> Eval a
- using :: a -> Strategy a -> a
- withStrategy :: Strategy a -> a -> a
- usingIO :: a -> Strategy a -> IO a
- withStrategyIO :: Strategy a -> a -> IO a
- dot :: Strategy a -> Strategy a -> Strategy a
- r0 :: Strategy a
- rseq :: Strategy a
- rdeepseq :: NFData a => Strategy a
- rpar :: Strategy a
- rparWith :: Strategy a -> Strategy a
- evalSeq :: SeqStrategy a -> Strategy a
- type SeqStrategy a = Strategy a
- evalTraversable :: Traversable t => Strategy a -> Strategy (t a)
- parTraversable :: Traversable t => Strategy a -> Strategy (t a)
- evalList :: Strategy a -> Strategy [a]
- parList :: Strategy a -> Strategy [a]
- evalListN :: Int -> Strategy a -> Strategy [a]
- parListN :: Int -> Strategy a -> Strategy [a]
- evalListNth :: Int -> Strategy a -> Strategy [a]
- parListNth :: Int -> Strategy a -> Strategy [a]
- evalListSplitAt :: Int -> Strategy [a] -> Strategy [a] -> Strategy [a]
- parListSplitAt :: Int -> Strategy [a] -> Strategy [a] -> Strategy [a]
- parListChunk :: Int -> Strategy a -> Strategy [a]
- parMap :: Strategy b -> (a -> b) -> [a] -> [b]
- evalBuffer :: Int -> Strategy a -> Strategy [a]
- 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)
- ($|) :: (a -> b) -> Strategy a -> a -> b
- ($||) :: (a -> b) -> Strategy a -> a -> b
- (.|) :: (b -> c) -> Strategy b -> (a -> b) -> a -> c
- (.||) :: (b -> c) -> Strategy b -> (a -> b) -> a -> c
- (-|) :: (a -> b) -> Strategy b -> (b -> c) -> a -> c
- (-||) :: (a -> b) -> Strategy b -> (b -> c) -> a -> c
- data Eval a
- parEval :: Eval a -> Eval a
- runEval :: Eval a -> a
- runEvalIO :: Eval a -> IO a
- type Done = ()
- demanding :: a -> Done -> a
- sparking :: a -> Done -> a
- (>|) :: Done -> Done -> Done
- (>||) :: Done -> Done -> Done
- rwhnf :: Strategy a
- unEval :: Eval a -> a
- seqTraverse :: Traversable t => Strategy a -> Strategy (t a)
- parTraverse :: Traversable t => Strategy a -> Strategy (t a)
- seqList :: Strategy a -> Strategy [a]
- seqPair :: Strategy a -> Strategy b -> Strategy (a, b)
- parPair :: Strategy a -> Strategy b -> Strategy (a, b)
- seqTriple :: Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c)
- parTriple :: Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c)
- class NFData a
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 #
withStrategyIO :: Strategy a -> a -> IO a Source #
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
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
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
. Specifically, dot
stratrpar
always sparks a computation to reduce the result of the
strategic computation to WHNF, while dot
stratrparWith 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 #
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]
will eval using
evalListNth 4 rseq5
, 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 #
evaluates the prefix
(of length evaListSplitAt
n stratPref stratSuffn
) 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
to each chunk in parallel.evalList
strat
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
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.
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.
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
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
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
behaves as you might expect (it creates a spark that does no evaluation).parEval
(r0
x)
It is related to rparWith
by the following equality:
parEval . strat = rparWith strat
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 toparTraverse
, which works on anyTraversable
type, and similarlyseqList
has been generalised toseqTraverse
parList
andparBuffer
have versions specialised torwhnf
, and there are transformation rules that automatically translate e.g.parList rwnhf
into a call to the optimised version.NFData
has been moved toControl.DeepSeq
in thedeepseq
package. Note that since theStrategy
type changed,rnf
is no longer aStrategy
: userdeepseq
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 addition of Sequential strategies (Control.Seq) as a composable means for specifying sequential evaluation.
- Changes to the naming scheme:
rwhnf
renamed torseq
,seqList
renamed toevalList
,seqPair
renamed toevalTuple2
,
The naming scheme is now as follows:
- Basic polymorphic strategies (of type
) are calledStrategy
ar...
. Examples:r0
,rseq
,rpar
,rdeepseq
. - A strategy combinator for a particular type constructor
or constructor class
T
is calledevalT...
,parT...
orseqT...
. - 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 correspondingseqT...
combinator might be a better choice.) Examples:evalTuple2
,evalListN
,evalTraversable
. - The
parT...
combinators, which are derived from theirevalT...
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
andparBuffer
, 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.
Deprecated: The Strategy type is now a -> Eval a, not a -> Done
DEPRECCATED: replaced by the Eval
monad
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:
A class of types that can be fully evaluated.
Since: deepseq-1.1.0.0
Instances
NFData ByteArray | Since: deepseq-1.4.7.0 |
Defined in Control.DeepSeq | |
NFData All | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData Any | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData TypeRep | NOTE: Prior to Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData Unique | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData Version | Since: deepseq-1.3.0.0 |
Defined in Control.DeepSeq | |
NFData CBool | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
NFData CChar | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CClock | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CDouble | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CFile | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CFloat | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CFpos | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CInt | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CIntMax | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CIntPtr | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CJmpBuf | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CLLong | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CLong | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CPtrdiff | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CSChar | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CSUSeconds | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq rnf :: CSUSeconds -> () # | |
NFData CShort | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CSigAtomic | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq rnf :: CSigAtomic -> () # | |
NFData CSize | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CTime | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CUChar | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CUInt | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CUIntMax | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CUIntPtr | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CULLong | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CULong | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CUSeconds | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CUShort | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData CWchar | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData Void | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData ThreadId | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData Fingerprint | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq rnf :: Fingerprint -> () # | |
NFData MaskingState | Since: deepseq-1.4.4.0 |
Defined in Control.DeepSeq rnf :: MaskingState -> () # | |
NFData ExitCode | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
NFData Int16 | |
Defined in Control.DeepSeq | |
NFData Int32 | |
Defined in Control.DeepSeq | |
NFData Int64 | |
Defined in Control.DeepSeq | |
NFData Int8 | |
Defined in Control.DeepSeq | |
NFData CallStack | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
NFData SrcLoc | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
NFData Word16 | |
Defined in Control.DeepSeq | |
NFData Word32 | |
Defined in Control.DeepSeq | |
NFData Word64 | |
Defined in Control.DeepSeq | |
NFData Word8 | |
Defined in Control.DeepSeq | |
NFData IntSet | |
Defined in Data.IntSet.Internal | |
NFData Module | Since: deepseq-1.4.8.0 |
Defined in Control.DeepSeq | |
NFData Ordering | |
Defined in Control.DeepSeq | |
NFData TyCon | NOTE: Prior to Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData Integer | |
Defined in Control.DeepSeq | |
NFData Natural | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData () | |
Defined in Control.DeepSeq | |
NFData Bool | |
Defined in Control.DeepSeq | |
NFData Char | |
Defined in Control.DeepSeq | |
NFData Double | |
Defined in Control.DeepSeq | |
NFData Float | |
Defined in Control.DeepSeq | |
NFData Int | |
Defined in Control.DeepSeq | |
NFData Word | |
Defined in Control.DeepSeq | |
NFData a => NFData (ZipList a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData (MutableByteArray s) | Since: deepseq-1.4.8.0 |
Defined in Control.DeepSeq rnf :: MutableByteArray s -> () # | |
NFData a => NFData (Complex a) | |
Defined in Control.DeepSeq | |
NFData a => NFData (Identity a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData a => NFData (First a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData a => NFData (Last a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData a => NFData (Down a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData a => NFData (First a) | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
NFData a => NFData (Last a) | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
NFData a => NFData (Max a) | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
NFData a => NFData (Min a) | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
NFData m => NFData (WrappedMonoid m) | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq rnf :: WrappedMonoid m -> () # | |
NFData a => NFData (Dual a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData a => NFData (Product a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData a => NFData (Sum a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData a => NFData (NonEmpty a) | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
NFData (IORef a) | NOTE: Only strict in the reference and not the referenced value. Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
NFData (MVar a) | NOTE: Only strict in the reference and not the referenced value. Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
NFData (FunPtr a) | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
NFData (Ptr a) | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
NFData a => NFData (Ratio a) | |
Defined in Control.DeepSeq | |
NFData (StableName a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq rnf :: StableName a -> () # | |
NFData a => NFData (SCC a) | |
Defined in Data.Graph | |
NFData a => NFData (IntMap a) | |
Defined in Data.IntMap.Internal | |
NFData a => NFData (Digit a) | |
Defined in Data.Sequence.Internal | |
NFData a => NFData (Elem a) | |
Defined in Data.Sequence.Internal | |
NFData a => NFData (FingerTree a) | |
Defined in Data.Sequence.Internal rnf :: FingerTree a -> () # | |
NFData a => NFData (Node a) | |
Defined in Data.Sequence.Internal | |
NFData a => NFData (Seq a) | |
Defined in Data.Sequence.Internal | |
NFData a => NFData (Set a) | |
Defined in Data.Set.Internal | |
NFData a => NFData (Tree a) | |
NFData a => NFData (Maybe a) | |
Defined in Control.DeepSeq | |
NFData a => NFData (Solo a) | Since: deepseq-1.4.6.0 |
Defined in Control.DeepSeq | |
NFData a => NFData [a] | |
Defined in Control.DeepSeq | |
(NFData a, NFData b) => NFData (Either a b) | |
Defined in Control.DeepSeq | |
NFData (Fixed a) | Since: deepseq-1.3.0.0 |
Defined in Control.DeepSeq | |
NFData (Proxy a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
(NFData a, NFData b) => NFData (Arg a b) | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
NFData (TypeRep a) | Since: deepseq-1.4.8.0 |
Defined in Control.DeepSeq | |
(NFData a, NFData b) => NFData (Array a b) | |
Defined in Control.DeepSeq | |
NFData (STRef s a) | NOTE: Only strict in the reference and not the referenced value. Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
(NFData k, NFData a) => NFData (Map k a) | |
Defined in Data.Map.Internal | |
(NFData a, NFData b) => NFData (a, b) | |
Defined in Control.DeepSeq | |
NFData (a -> b) | This instance is for convenience and consistency with Since: deepseq-1.3.0.0 |
Defined in Control.DeepSeq | |
NFData a => NFData (Const a b) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
NFData (a :~: b) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
(NFData a1, NFData a2, NFData a3) => NFData (a1, a2, a3) | |
Defined in Control.DeepSeq | |
(NFData (f a), NFData (g a)) => NFData (Product f g a) | Note: in Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
(NFData (f a), NFData (g a)) => NFData (Sum f g a) | Note: in Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
NFData (a :~~: b) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
(NFData a1, NFData a2, NFData a3, NFData a4) => NFData (a1, a2, a3, a4) | |
Defined in Control.DeepSeq | |
NFData (f (g a)) => NFData (Compose f g a) | Note: in Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => NFData (a1, a2, a3, a4, a5) | |
Defined in Control.DeepSeq | |
(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => NFData (a1, a2, a3, a4, a5, a6) | |
Defined in Control.DeepSeq | |
(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => NFData (a1, a2, a3, a4, a5, a6, a7) | |
Defined in Control.DeepSeq | |
(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) | |
Defined in Control.DeepSeq | |
(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) | |
Defined in Control.DeepSeq |