| Copyright | (c) The University of Glasgow 2001-2009 |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | libraries@haskell.org |
| Stability | stable |
| Portability | portable |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Control.DeepSeq
Description
This module provides an overloaded function, deepseq, for fully
evaluating data structures (that is, evaluating to "Normal Form").
A typical use is to prevent resource leaks in lazy IO programs, by forcing all characters from a file to be read. For example:
import System.IO
import Control.DeepSeq
main = do
h <- openFile "f" ReadMode
s <- hGetContents h
s `deepseq` hClose h
return sdeepseq differs from seq as it traverses data structures deeply,
for example, seq will evaluate only to the first constructor in
the list:
> [1,2,undefined] `seq` 3 3
While deepseq will force evaluation of all the list elements:
> [1,2,undefined] `deepseq` 3 *** Exception: Prelude.undefined
Another common use is to ensure any exceptions hidden within lazy fields of a data structure do not leak outside the scope of the exception handler, or to force evaluation of a data structure in one thread, before passing to another thread (preventing work moving to the wrong threads).
Since: 1.1.0.0
Documentation
deepseq :: NFData a => a -> b -> b Source #
deepseq: fully evaluates the first argument, before returning the
second.
The name deepseq is used to illustrate the relationship to seq:
where seq is shallow in the sense that it only evaluates the top
level of its argument, deepseq traverses the entire data structure
evaluating it completely.
deepseq can be useful for forcing pending exceptions,
eradicating space leaks, or forcing lazy I/O to happen. It is
also useful in conjunction with parallel Strategies (see the
parallel package).
There is no guarantee about the ordering of evaluation. The
implementation may evaluate the components of the structure in
any order or in parallel. To impose an actual order on
evaluation, use pseq from Control.Parallel in the
parallel package.
Since: 1.1.0.0
($!!) :: NFData a => (a -> b) -> a -> b infixr 0 Source #
the deep analogue of $!. In the expression f $!! x, x is
fully evaluated before the function f is applied to it.
Since: 1.2.0.0
force :: NFData a => a -> a Source #
a variant of deepseq that is useful in some circumstances:
force x = x `deepseq` x
force x fully evaluates x, and then returns it. Note that
force x only performs evaluation when the value of force x
itself is demanded, so essentially it turns shallow evaluation into
deep evaluation.
force can be conveniently used in combination with ViewPatterns:
{-# LANGUAGE BangPatterns, ViewPatterns #-}
import Control.DeepSeq
someFun :: ComplexData -> SomeResult
someFun (force -> !arg) = {- 'arg' will be fully evaluated -}Another useful application is to combine force with
evaluate in order to force deep evaluation
relative to other IO operations:
import Control.Exception (evaluate)
import Control.DeepSeq
main = do
result <- evaluate $ force $ pureComputation
{- 'result' will be fully evaluated at this point -}
return ()Since: 1.2.0.0
A class of types that can be fully evaluated.
Since: 1.1.0.0
Methods
rnf should reduce its argument to normal form (that is, fully
evaluate all sub-components), and then return '()'.
Generic NFData deriving
Starting with GHC 7.2, you can automatically derive instances
for types possessing a Generic instance.
{-# LANGUAGE DeriveGeneric #-}
import GHC.Generics (Generic)
import Control.DeepSeq
data Foo a = Foo a String
deriving (Eq, Generic)
instance NFData a => NFData (Foo a)
data Colour = Red | Green | Blue
deriving Generic
instance NFData ColourStarting with GHC 7.10, the example above can be written more
concisely by enabling the new DeriveAnyClass extension:
{-# LANGUAGE DeriveGeneric, DeriveAnyClass #-}
import GHC.Generics (Generic)
import Control.DeepSeq
data Foo a = Foo a String
deriving (Eq, Generic, NFData)
data Colour = Red | Green | Blue
deriving (Generic, NFData)
Compatibility with previous deepseq versions
Prior to version 1.4.0.0, the default implementation of the rnf
method was defined as
rnfa =seqa ()
However, starting with deepseq-1.4.0.0, the default
implementation is based on DefaultSignatures allowing for
more accurate auto-derived NFData instances. If you need the
previously used exact default rnf method implementation
semantics, use
instance NFData Colour where rnf x = seq x ()
or alternatively
{-# LANGUAGE BangPatterns #-}
instance NFData Colour where rnf !_ = ()rnf :: (Generic a, GNFData (Rep a)) => a -> () Source #
rnf should reduce its argument to normal form (that is, fully
evaluate all sub-components), and then return '()'.
Generic NFData deriving
Starting with GHC 7.2, you can automatically derive instances
for types possessing a Generic instance.
{-# LANGUAGE DeriveGeneric #-}
import GHC.Generics (Generic)
import Control.DeepSeq
data Foo a = Foo a String
deriving (Eq, Generic)
instance NFData a => NFData (Foo a)
data Colour = Red | Green | Blue
deriving Generic
instance NFData ColourStarting with GHC 7.10, the example above can be written more
concisely by enabling the new DeriveAnyClass extension:
{-# LANGUAGE DeriveGeneric, DeriveAnyClass #-}
import GHC.Generics (Generic)
import Control.DeepSeq
data Foo a = Foo a String
deriving (Eq, Generic, NFData)
data Colour = Red | Green | Blue
deriving (Generic, NFData)
Compatibility with previous deepseq versions
Prior to version 1.4.0.0, the default implementation of the rnf
method was defined as
rnfa =seqa ()
However, starting with deepseq-1.4.0.0, the default
implementation is based on DefaultSignatures allowing for
more accurate auto-derived NFData instances. If you need the
previously used exact default rnf method implementation
semantics, use
instance NFData Colour where rnf x = seq x ()
or alternatively
{-# LANGUAGE BangPatterns #-}
instance NFData Colour where rnf !_ = ()Instances
| NFData Bool Source # | |
| NFData Char Source # | |
| NFData Double Source # | |
| NFData Float Source # | |
| NFData Int Source # | |
| NFData Int8 Source # | |
| NFData Int16 Source # | |
| NFData Int32 Source # | |
| NFData Int64 Source # | |
| NFData Integer Source # | |
| NFData Word Source # | |
| NFData Word8 Source # | |
| NFData Word16 Source # | |
| NFData Word32 Source # | |
| NFData Word64 Source # | |
| NFData CallStack Source # | Since: 1.4.2.0 |
| NFData TypeRep Source # | NOTE: Only defined for Since: 1.4.0.0 |
| NFData () Source # | |
| NFData TyCon Source # | NOTE: Only defined for Since: 1.4.0.0 |
| NFData Natural Source # | Since: 1.4.0.0 |
| NFData Void Source # | Since: 1.4.0.0 |
| NFData Version Source # | Since: 1.3.0.0 |
| NFData Unique Source # | Since: 1.4.0.0 |
| NFData ThreadId Source # | Since: 1.4.0.0 |
| NFData ExitCode Source # | Since: 1.4.2.0 |
| NFData CChar Source # | Since: 1.4.0.0 |
| NFData CSChar Source # | Since: 1.4.0.0 |
| NFData CUChar Source # | Since: 1.4.0.0 |
| NFData CShort Source # | Since: 1.4.0.0 |
| NFData CUShort Source # | Since: 1.4.0.0 |
| NFData CInt Source # | Since: 1.4.0.0 |
| NFData CUInt Source # | Since: 1.4.0.0 |
| NFData CLong Source # | Since: 1.4.0.0 |
| NFData CULong Source # | Since: 1.4.0.0 |
| NFData CLLong Source # | Since: 1.4.0.0 |
| NFData CULLong Source # | Since: 1.4.0.0 |
| NFData CFloat Source # | Since: 1.4.0.0 |
| NFData CDouble Source # | Since: 1.4.0.0 |
| NFData CPtrdiff Source # | Since: 1.4.0.0 |
| NFData CSize Source # | Since: 1.4.0.0 |
| NFData CWchar Source # | Since: 1.4.0.0 |
| NFData CSigAtomic Source # | Since: 1.4.0.0 |
| NFData CClock Source # | Since: 1.4.0.0 |
| NFData CTime Source # | Since: 1.4.0.0 |
| NFData CUSeconds Source # | Since: 1.4.0.0 |
| NFData CSUSeconds Source # | Since: 1.4.0.0 |
| NFData CFile Source # | Since: 1.4.0.0 |
| NFData CFpos Source # | Since: 1.4.0.0 |
| NFData CJmpBuf Source # | Since: 1.4.0.0 |
| NFData CIntPtr Source # | Since: 1.4.0.0 |
| NFData CUIntPtr Source # | Since: 1.4.0.0 |
| NFData CIntMax Source # | Since: 1.4.0.0 |
| NFData CUIntMax Source # | Since: 1.4.0.0 |
| NFData All Source # | Since: 1.4.0.0 |
| NFData Any Source # | Since: 1.4.0.0 |
| NFData Fingerprint Source # | Since: 1.4.0.0 |
| NFData SrcLoc Source # | Since: 1.4.2.0 |
| NFData a => NFData [a] Source # | |
| NFData a => NFData (Maybe a) Source # | |
| NFData a => NFData (Ratio a) Source # | |
| NFData (Ptr a) Source # | Since: 1.4.2.0 |
| NFData (FunPtr a) Source # | Since: 1.4.2.0 |
| NFData a => NFData (Identity a) Source # | Since: 1.4.0.0 |
| NFData a => NFData (Min a) Source # | Since: 1.4.2.0 |
| NFData a => NFData (Max a) Source # | Since: 1.4.2.0 |
| NFData a => NFData (First a) Source # | Since: 1.4.2.0 |
| NFData a => NFData (Last a) Source # | Since: 1.4.2.0 |
| NFData m => NFData (WrappedMonoid m) Source # | Since: 1.4.2.0 |
| NFData a => NFData (Option a) Source # | Since: 1.4.2.0 |
| NFData a => NFData (NonEmpty a) Source # | Since: 1.4.2.0 |
| NFData (Fixed a) Source # | Since: 1.3.0.0 |
| NFData a => NFData (Complex a) Source # | |
| NFData (StableName a) Source # | Since: 1.4.0.0 |
| NFData a => NFData (ZipList a) Source # | Since: 1.4.0.0 |
| NFData a => NFData (Dual a) Source # | Since: 1.4.0.0 |
| NFData a => NFData (Sum a) Source # | Since: 1.4.0.0 |
| NFData a => NFData (Product a) Source # | Since: 1.4.0.0 |
| NFData a => NFData (First a) Source # | Since: 1.4.0.0 |
| NFData a => NFData (Last a) Source # | Since: 1.4.0.0 |
| NFData (IORef a) Source # | NOTE: Only strict in the reference and not the referenced value. Since: 1.4.2.0 |
| NFData a => NFData (Down a) Source # | Since: 1.4.0.0 |
| NFData (MVar a) Source # | NOTE: Only strict in the reference and not the referenced value. Since: 1.4.2.0 |
| NFData (a -> b) Source # | This instance is for convenience and consistency with Since: 1.3.0.0 |
| (NFData a, NFData b) => NFData (Either a b) Source # | |
| (NFData a, NFData b) => NFData (a, b) Source # | |
| (NFData a, NFData b) => NFData (Array a b) Source # | |
| (NFData a, NFData b) => NFData (Arg a b) Source # | Since: 1.4.2.0 |
| NFData (Proxy k a) Source # | Since: 1.4.0.0 |
| NFData (STRef s a) Source # | NOTE: Only strict in the reference and not the referenced value. Since: 1.4.2.0 |
| (NFData a, NFData b, NFData c) => NFData (a, b, c) Source # | |
| NFData a => NFData (Const k a b) Source # | Since: 1.4.0.0 |
| (NFData a, NFData b, NFData c, NFData d) => NFData (a, b, c, d) Source # | |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => NFData (a1, a2, a3, a4, a5) Source # | |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => NFData (a1, a2, a3, a4, a5, a6) Source # | |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => NFData (a1, a2, a3, a4, a5, a6, a7) Source # | |
| (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) Source # | |
| (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) Source # | |