| Copyright | (c) The University of Glasgow 2001-2009 |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | [email protected] |
| Stability | stable |
| Portability | portable |
| Safe Haskell | Safe |
| Language | Haskell2010 |
This module provides overloaded functions, such as deepseq and rnf, 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
import Control.Exception (evaluate)
readFile' :: FilePath -> IO String
readFile' fn = do
h <- openFile fn ReadMode
s <- hGetContents h
evaluate (rnf s)
hClose h
return s
Note: The example above should rather be written in terms of bracket to ensure releasing file-descriptors in a timely matter (see the description of force for an example).
deepseq 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
A class of types that can be fully evaluated.
Since: 1.1.0.0
rnf should reduce its argument to normal form (that is, fully evaluate all sub-components), and then return '()'.
Generic NFData derivingStarting with GHC 7.2, you can automatically derive instances for types possessing a Generic instance.
Note: Generic1 can be auto-derived starting with GHC 7.4
{-# LANGUAGE DeriveGeneric #-}
import GHC.Generics (Generic, Generic1)
import Control.DeepSeq
data Foo a = Foo a String
deriving (Eq, Generic, Generic1)
instance NFData a => NFData (Foo a)
instance NFData1 Foo
data Colour = Red | Green | Blue
deriving Generic
instance NFData Colour
Starting 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, Generic1, NFData, NFData1)
data Colour = Red | Green | Blue
deriving (Generic, NFData)
deepseq versionsPrior 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
instance NFData Colour where rnf = rwhnf
or
{-# LANGUAGE BangPatterns #-}
instance NFData Colour where rnf !_ = ()
rnf :: (Generic a, GNFData Zero (Rep a)) => a -> () Source
rnf should reduce its argument to normal form (that is, fully evaluate all sub-components), and then return '()'.
Generic NFData derivingStarting with GHC 7.2, you can automatically derive instances for types possessing a Generic instance.
Note: Generic1 can be auto-derived starting with GHC 7.4
{-# LANGUAGE DeriveGeneric #-}
import GHC.Generics (Generic, Generic1)
import Control.DeepSeq
data Foo a = Foo a String
deriving (Eq, Generic, Generic1)
instance NFData a => NFData (Foo a)
instance NFData1 Foo
data Colour = Red | Green | Blue
deriving Generic
instance NFData Colour
Starting 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, Generic1, NFData, NFData1)
data Colour = Red | Green | Blue
deriving (Generic, NFData)
deepseq versionsPrior 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
instance NFData Colour where rnf = rwhnf
or
{-# LANGUAGE BangPatterns #-}
instance NFData Colour where rnf !_ = ()
| NFData Bool | |
| NFData Char | |
| NFData Double | |
| NFData Float | |
| NFData Int | |
| NFData Int8 | |
| NFData Int16 | |
| NFData Int32 | |
| NFData Int64 | |
| NFData Integer | |
| NFData Natural | Since: 1.4.0.0 |
| NFData Ordering | |
| NFData Word | |
| NFData Word8 | |
| NFData Word16 | |
| NFData Word32 | |
| NFData Word64 | |
| NFData CallStack | Since: 1.4.2.0 |
| NFData () | |
| NFData TyCon |
NOTE: Only defined for Since: 1.4.0.0 |
| NFData Void |
Since: 1.4.0.0 |
| NFData Unique | Since: 1.4.0.0 |
| NFData Version | Since: 1.3.0.0 |
| NFData ThreadId | Since: 1.4.0.0 |
| NFData ExitCode | Since: 1.4.2.0 |
| NFData TypeRep |
NOTE: Only defined for Since: 1.4.0.0 |
| NFData All | Since: 1.4.0.0 |
| NFData Any | Since: 1.4.0.0 |
| NFData CChar | Since: 1.4.0.0 |
| NFData CSChar | Since: 1.4.0.0 |
| NFData CUChar | Since: 1.4.0.0 |
| NFData CShort | Since: 1.4.0.0 |
| NFData CUShort | Since: 1.4.0.0 |
| NFData CInt | Since: 1.4.0.0 |
| NFData CUInt | Since: 1.4.0.0 |
| NFData CLong | Since: 1.4.0.0 |
| NFData CULong | Since: 1.4.0.0 |
| NFData CLLong | Since: 1.4.0.0 |
| NFData CULLong | Since: 1.4.0.0 |
| NFData CBool | Since: 1.4.3.0 |
| NFData CFloat | Since: 1.4.0.0 |
| NFData CDouble | Since: 1.4.0.0 |
| NFData CPtrdiff | Since: 1.4.0.0 |
| NFData CSize | Since: 1.4.0.0 |
| NFData CWchar | Since: 1.4.0.0 |
| NFData CSigAtomic | Since: 1.4.0.0 |
| NFData CClock | Since: 1.4.0.0 |
| NFData CTime | Since: 1.4.0.0 |
| NFData CUSeconds | Since: 1.4.0.0 |
| NFData CSUSeconds | Since: 1.4.0.0 |
| NFData CFile | Since: 1.4.0.0 |
| NFData CFpos | Since: 1.4.0.0 |
| NFData CJmpBuf | Since: 1.4.0.0 |
| NFData CIntPtr | Since: 1.4.0.0 |
| NFData CUIntPtr | Since: 1.4.0.0 |
| NFData CIntMax | Since: 1.4.0.0 |
| NFData CUIntMax | Since: 1.4.0.0 |
| NFData Fingerprint | Since: 1.4.0.0 |
| NFData SrcLoc | Since: 1.4.2.0 |
| NFData a => NFData [a] | |
| NFData a => NFData (Maybe a) | |
| NFData a => NFData (Ratio a) | |
| NFData (Ptr a) | Since: 1.4.2.0 |
| NFData (FunPtr a) | Since: 1.4.2.0 |
| NFData a => NFData (Complex a) | |
| NFData (Fixed a) | Since: 1.3.0.0 |
| NFData a => NFData (Min a) | Since: 1.4.2.0 |
| NFData a => NFData (Max a) | Since: 1.4.2.0 |
| NFData a => NFData (First a) | Since: 1.4.2.0 |
| NFData a => NFData (Last a) | Since: 1.4.2.0 |
| NFData m => NFData (WrappedMonoid m) | Since: 1.4.2.0 |
| NFData a => NFData (Option a) | Since: 1.4.2.0 |
| NFData a => NFData (NonEmpty a) | Since: 1.4.2.0 |
| NFData (StableName a) | Since: 1.4.0.0 |
| NFData a => NFData (ZipList a) | Since: 1.4.0.0 |
| NFData a => NFData (Identity a) | Since: 1.4.0.0 |
| NFData (IORef a) |
NOTE: Only strict in the reference and not the referenced value. Since: 1.4.2.0 |
| NFData a => NFData (Dual a) | Since: 1.4.0.0 |
| NFData a => NFData (Sum a) | Since: 1.4.0.0 |
| NFData a => NFData (Product a) | Since: 1.4.0.0 |
| NFData a => NFData (First a) | Since: 1.4.0.0 |
| NFData a => NFData (Last a) | Since: 1.4.0.0 |
| NFData a => NFData (Down a) | Since: 1.4.0.0 |
| NFData (MVar a) |
NOTE: Only strict in the reference and not the referenced value. Since: 1.4.2.0 |
| NFData (a -> b) |
This instance is for convenience and consistency with Since: 1.3.0.0 |
| (NFData a, NFData b) => NFData (Either a b) | |
| (NFData a, NFData b) => NFData (a, b) | |
| (NFData a, NFData b) => NFData (Array a b) | |
| (NFData a, NFData b) => NFData (Arg a b) | Since: 1.4.2.0 |
| NFData (Proxy k a) | Since: 1.4.0.0 |
| NFData (STRef s a) |
NOTE: Only strict in the reference and not the referenced value. Since: 1.4.2.0 |
| (NFData a1, NFData a2, NFData a3) => NFData (a1, a2, a3) | |
| NFData a => NFData (Const k a b) | Since: 1.4.0.0 |
| NFData ((:~:) k a b) | Since: 1.4.3.0 |
| (NFData a1, NFData a2, NFData a3, NFData a4) => NFData (a1, a2, a3, a4) | |
| (NFData1 f, NFData1 g, NFData a) => NFData (Product * f g a) | Since: 1.4.3.0 |
| (NFData1 f, NFData1 g, NFData a) => NFData (Sum * f g a) | Since: 1.4.3.0 |
| NFData ((:~~:) k1 k2 a b) | Since: 1.4.3.0 |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => NFData (a1, a2, a3, a4, a5) | |
| (NFData1 f, NFData1 g, NFData a) => NFData (Compose * * f g a) | Since: 1.4.3.0 |
| (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) | |
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
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 ()
Finally, here's an exception safe variant of the readFile' example:
readFile' :: FilePath -> IO String
readFile' fn = bracket (openFile fn ReadMode) hClose $ \h ->
evaluate . force =<< hGetContents h
Since: 1.2.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
(<$!!>) :: (Monad m, NFData b) => (a -> b) -> m a -> m b infixl 4 Source
Deeply strict version of <$>.
Since: 1.4.3.0
Reduce to weak head normal form
Equivalent to \x -> seq x ().
Useful for defining NFData for types for which NF=WHNF holds.
data T = C1 | C2 | C3 instance NFData T where rnf = rwhnf
Since: 1.4.3.0
A class of functors that can be fully evaluated.
Since: 1.4.3.0
liftRnf :: (a -> ()) -> f a -> () Source
liftRnf should reduce its argument to normal form (that is, fully evaluate all sub-components), given an argument to reduce a arguments, and then return '()'.
See rnf for the generic deriving.
liftRnf :: (Generic1 f, GNFData One (Rep1 f)) => (a -> ()) -> f a -> () Source
liftRnf should reduce its argument to normal form (that is, fully evaluate all sub-components), given an argument to reduce a arguments, and then return '()'.
See rnf for the generic deriving.
| NFData1 [] | Since: 1.4.3.0 |
| NFData1 Maybe | Since: 1.4.3.0 |
| NFData1 Ratio |
Available on Since: 1.4.3.0 |
| NFData1 Ptr | Since: 1.4.3.0 |
| NFData1 FunPtr | Since: 1.4.3.0 |
| NFData1 Fixed | Since: 1.4.3.0 |
| NFData1 Min | Since: 1.4.3.0 |
| NFData1 Max | Since: 1.4.3.0 |
| NFData1 First | Since: 1.4.3.0 |
| NFData1 Last | Since: 1.4.3.0 |
| NFData1 WrappedMonoid | Since: 1.4.3.0 |
| NFData1 Option | Since: 1.4.3.0 |
| NFData1 NonEmpty | Since: 1.4.3.0 |
| NFData1 StableName | Since: 1.4.3.0 |
| NFData1 ZipList | Since: 1.4.3.0 |
| NFData1 Identity | Since: 1.4.3.0 |
| NFData1 IORef | Since: 1.4.3.0 |
| NFData1 Dual | Since: 1.4.3.0 |
| NFData1 Sum | Since: 1.4.3.0 |
| NFData1 Product | Since: 1.4.3.0 |
| NFData1 First | Since: 1.4.3.0 |
| NFData1 Last | Since: 1.4.3.0 |
| NFData1 Down | Since: 1.4.3.0 |
| NFData1 MVar | Since: 1.4.3.0 |
| NFData a => NFData1 (Either a) | Since: 1.4.3.0 |
| NFData a => NFData1 ((,) a) | Since: 1.4.3.0 |
| NFData a => NFData1 (Array a) | Since: 1.4.3.0 |
| NFData a => NFData1 (Arg a) | Since: 1.4.3.0 |
| NFData1 (Proxy *) | Since: 1.4.3.0 |
| NFData1 (STRef s) | Since: 1.4.3.0 |
| (NFData a1, NFData a2) => NFData1 ((,,) a1 a2) | Since: 1.4.3.0 |
| NFData a => NFData1 (Const * a) | Since: 1.4.3.0 |
| NFData1 ((:~:) * a) | Since: 1.4.3.0 |
| (NFData a1, NFData a2, NFData a3) => NFData1 ((,,,) a1 a2 a3) | Since: 1.4.3.0 |
| (NFData1 f, NFData1 g) => NFData1 (Product * f g) | Since: 1.4.3.0 |
| (NFData1 f, NFData1 g) => NFData1 (Sum * f g) | Since: 1.4.3.0 |
| NFData1 ((:~~:) k1 * a) | Since: 1.4.3.0 |
| (NFData a1, NFData a2, NFData a3, NFData a4) => NFData1 ((,,,,) a1 a2 a3 a4) | Since: 1.4.3.0 |
| (NFData1 f, NFData1 g) => NFData1 (Compose * * f g) | Since: 1.4.3.0 |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => NFData1 ((,,,,,) a1 a2 a3 a4 a5) | Since: 1.4.3.0 |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => NFData1 ((,,,,,,) a1 a2 a3 a4 a5 a6) | Since: 1.4.3.0 |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => NFData1 ((,,,,,,,) a1 a2 a3 a4 a5 a6 a7) | Since: 1.4.3.0 |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8) => NFData1 ((,,,,,,,,) a1 a2 a3 a4 a5 a6 a7 a8) | Since: 1.4.3.0 |
rnf1 :: (NFData1 f, NFData a) => f a -> () Source
Lift the standard rnf function through the type constructor.
Since: 1.4.3.0
A class of bifunctors that can be fully evaluated.
Since: 1.4.3.0
liftRnf2 :: (a -> ()) -> (b -> ()) -> p a b -> () Source
liftRnf2 should reduce its argument to normal form (that is, fully evaluate all sub-components), given functions to reduce a and b arguments respectively, and then return '()'.
Note: Unlike for the unary liftRnf, there is currently no support for generically deriving liftRnf2.
| NFData2 Either | Since: 1.4.3.0 |
| NFData2 (,) | Since: 1.4.3.0 |
| NFData2 Array | Since: 1.4.3.0 |
| NFData2 Arg | Since: 1.4.3.0 |
| NFData2 STRef | Since: 1.4.3.0 |
| NFData a1 => NFData2 ((,,) a1) | Since: 1.4.3.0 |
| NFData2 (Const *) | Since: 1.4.3.0 |
| NFData2 ((:~:) *) | Since: 1.4.3.0 |
| (NFData a1, NFData a2) => NFData2 ((,,,) a1 a2) | Since: 1.4.3.0 |
| NFData2 ((:~~:) * *) | Since: 1.4.3.0 |
| (NFData a1, NFData a2, NFData a3) => NFData2 ((,,,,) a1 a2 a3) | Since: 1.4.3.0 |
| (NFData a1, NFData a2, NFData a3, NFData a4) => NFData2 ((,,,,,) a1 a2 a3 a4) | Since: 1.4.3.0 |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => NFData2 ((,,,,,,) a1 a2 a3 a4 a5) | Since: 1.4.3.0 |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => NFData2 ((,,,,,,,) a1 a2 a3 a4 a5 a6) | Since: 1.4.3.0 |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => NFData2 ((,,,,,,,,) a1 a2 a3 a4 a5 a6 a7) | Since: 1.4.3.0 |
rnf2 :: (NFData2 p, NFData a, NFData b) => p a b -> () Source
Lift the standard rnf function through the type constructor.
Since: 1.4.3.0
© The University of Glasgow and others
Licensed under a BSD-style license (see top of the page).
https://downloads.haskell.org/~ghc/8.2.1/docs/html/libraries/deepseq-1.4.3.0/Control-DeepSeq.html