deepseq-1.4.2.0: Deep evaluation of data structures

Copyright(c) The University of Glasgow 2001-2009
LicenseBSD-style (see the file LICENSE)
Maintainerlibraries@haskell.org
Stabilitystable
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

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 s

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

Synopsis

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

class NFData a where Source

A class of types that can be fully evaluated.

Since: 1.1.0.0

Methods

rnf :: 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 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, 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

rnf a = seq a ()

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 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, 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

rnf a = seq a ()

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 

Methods

rnf :: Bool -> () Source

NFData Char 

Methods

rnf :: Char -> () Source

NFData Double 

Methods

rnf :: Double -> () Source

NFData Float 

Methods

rnf :: Float -> () Source

NFData Int 

Methods

rnf :: Int -> () Source

NFData Int8 

Methods

rnf :: Int8 -> () Source

NFData Int16 

Methods

rnf :: Int16 -> () Source

NFData Int32 

Methods

rnf :: Int32 -> () Source

NFData Int64 

Methods

rnf :: Int64 -> () Source

NFData Integer 

Methods

rnf :: Integer -> () Source

NFData Word 

Methods

rnf :: Word -> () Source

NFData Word8 

Methods

rnf :: Word8 -> () Source

NFData Word16 

Methods

rnf :: Word16 -> () Source

NFData Word32 

Methods

rnf :: Word32 -> () Source

NFData Word64 

Methods

rnf :: Word64 -> () Source

NFData TypeRep

NOTE: Only defined for base-4.8.0.0 and later

Since: 1.4.0.0

Methods

rnf :: TypeRep -> () Source

NFData () 

Methods

rnf :: () -> () Source

NFData TyCon

NOTE: Only defined for base-4.8.0.0 and later

Since: 1.4.0.0

Methods

rnf :: TyCon -> () Source

NFData Unique

Since: 1.4.0.0

Methods

rnf :: Unique -> () Source

NFData Void

Defined as rnf = absurd.

Since: 1.4.0.0

Methods

rnf :: Void -> () Source

NFData Natural

Since: 1.4.0.0

Methods

rnf :: Natural -> () Source

NFData Version

Since: 1.3.0.0

Methods

rnf :: Version -> () Source

NFData ThreadId

Since: 1.4.0.0

Methods

rnf :: ThreadId -> () Source

NFData ExitCode

Since: 1.4.2.0

Methods

rnf :: ExitCode -> () Source

NFData CChar

Since: 1.4.0.0

Methods

rnf :: CChar -> () Source

NFData CSChar

Since: 1.4.0.0

Methods

rnf :: CSChar -> () Source

NFData CUChar

Since: 1.4.0.0

Methods

rnf :: CUChar -> () Source

NFData CShort

Since: 1.4.0.0

Methods

rnf :: CShort -> () Source

NFData CUShort

Since: 1.4.0.0

Methods

rnf :: CUShort -> () Source

NFData CInt

Since: 1.4.0.0

Methods

rnf :: CInt -> () Source

NFData CUInt

Since: 1.4.0.0

Methods

rnf :: CUInt -> () Source

NFData CLong

Since: 1.4.0.0

Methods

rnf :: CLong -> () Source

NFData CULong

Since: 1.4.0.0

Methods

rnf :: CULong -> () Source

NFData CLLong

Since: 1.4.0.0

Methods

rnf :: CLLong -> () Source

NFData CULLong

Since: 1.4.0.0

Methods

rnf :: CULLong -> () Source

NFData CFloat

Since: 1.4.0.0

Methods

rnf :: CFloat -> () Source

NFData CDouble

Since: 1.4.0.0

Methods

rnf :: CDouble -> () Source

NFData CPtrdiff

Since: 1.4.0.0

Methods

rnf :: CPtrdiff -> () Source

NFData CSize

Since: 1.4.0.0

Methods

rnf :: CSize -> () Source

NFData CWchar

Since: 1.4.0.0

Methods

rnf :: CWchar -> () Source

NFData CSigAtomic

Since: 1.4.0.0

Methods

rnf :: CSigAtomic -> () Source

NFData CClock

Since: 1.4.0.0

Methods

rnf :: CClock -> () Source

NFData CTime

Since: 1.4.0.0

Methods

rnf :: CTime -> () Source

NFData CUSeconds

Since: 1.4.0.0

Methods

rnf :: CUSeconds -> () Source

NFData CSUSeconds

Since: 1.4.0.0

Methods

rnf :: CSUSeconds -> () Source

NFData CFile

Since: 1.4.0.0

Methods

rnf :: CFile -> () Source

NFData CFpos

Since: 1.4.0.0

Methods

rnf :: CFpos -> () Source

NFData CJmpBuf

Since: 1.4.0.0

Methods

rnf :: CJmpBuf -> () Source

NFData CIntPtr

Since: 1.4.0.0

Methods

rnf :: CIntPtr -> () Source

NFData CUIntPtr

Since: 1.4.0.0

Methods

rnf :: CUIntPtr -> () Source

NFData CIntMax

Since: 1.4.0.0

Methods

rnf :: CIntMax -> () Source

NFData CUIntMax

Since: 1.4.0.0

Methods

rnf :: CUIntMax -> () Source

NFData Fingerprint

Since: 1.4.0.0

Methods

rnf :: Fingerprint -> () Source

NFData All

Since: 1.4.0.0

Methods

rnf :: All -> () Source

NFData Any

Since: 1.4.0.0

Methods

rnf :: Any -> () Source

NFData a => NFData [a] 

Methods

rnf :: [a] -> () Source

NFData a => NFData (Maybe a) 

Methods

rnf :: Maybe a -> () Source

NFData a => NFData (Ratio a) 

Methods

rnf :: Ratio a -> () Source

NFData (Ptr a)

Since: 1.4.2.0

Methods

rnf :: Ptr a -> () Source

NFData (FunPtr a)

Since: 1.4.2.0

Methods

rnf :: FunPtr a -> () Source

NFData (StableName a)

Since: 1.4.0.0

Methods

rnf :: StableName a -> () Source

NFData a => NFData (Identity a)

Since: 1.4.0.0

Methods

rnf :: Identity a -> () Source

NFData a => NFData (Min a)

Since: 1.4.2.0

Methods

rnf :: Min a -> () Source

NFData a => NFData (Max a)

Since: 1.4.2.0

Methods

rnf :: Max a -> () Source

NFData a => NFData (First a)

Since: 1.4.2.0

Methods

rnf :: First a -> () Source

NFData a => NFData (Last a)

Since: 1.4.2.0

Methods

rnf :: Last a -> () Source

NFData m => NFData (WrappedMonoid m)

Since: 1.4.2.0

Methods

rnf :: WrappedMonoid m -> () Source

NFData a => NFData (Option a)

Since: 1.4.2.0

Methods

rnf :: Option a -> () Source

NFData a => NFData (NonEmpty a)

Since: 1.4.2.0

Methods

rnf :: NonEmpty a -> () Source

NFData (Fixed a)

Since: 1.3.0.0

Methods

rnf :: Fixed a -> () Source

NFData a => NFData (Complex a) 

Methods

rnf :: Complex a -> () Source

NFData a => NFData (ZipList a)

Since: 1.4.0.0

Methods

rnf :: ZipList a -> () Source

NFData (IORef a)

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

Since: 1.4.2.0

Methods

rnf :: IORef a -> () Source

NFData a => NFData (Dual a)

Since: 1.4.0.0

Methods

rnf :: Dual a -> () Source

NFData a => NFData (Sum a)

Since: 1.4.0.0

Methods

rnf :: Sum a -> () Source

NFData a => NFData (Product a)

Since: 1.4.0.0

Methods

rnf :: Product a -> () Source

NFData a => NFData (First a)

Since: 1.4.0.0

Methods

rnf :: First a -> () Source

NFData a => NFData (Last a)

Since: 1.4.0.0

Methods

rnf :: Last a -> () Source

NFData a => NFData (Down a)

Since: 1.4.0.0

Methods

rnf :: Down a -> () Source

NFData (MVar a)

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

Since: 1.4.2.0

Methods

rnf :: MVar a -> () Source

NFData (a -> b)

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

Since: 1.3.0.0

Methods

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

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

Methods

rnf :: Either a b -> () Source

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

Methods

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

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

Methods

rnf :: Array a b -> () Source

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

Since: 1.4.2.0

Methods

rnf :: Arg a b -> () Source

NFData (Proxy k1 a)

Since: 1.4.0.0

Methods

rnf :: Proxy k1 a -> () Source

NFData (STRef s a)

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

Since: 1.4.2.0

Methods

rnf :: STRef s a -> () Source

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

Methods

rnf :: (a, b, c) -> () Source

NFData a => NFData (Const k1 a b)

Since: 1.4.0.0

Methods

rnf :: Const k1 a b -> () Source

(NFData a, NFData b, NFData c, NFData d) => NFData (a, b, c, d) 

Methods

rnf :: (a, b, c, d) -> () Source

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

Methods

rnf :: (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) 

Methods

rnf :: (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) 

Methods

rnf :: (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) 

Methods

rnf :: (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) 

Methods

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