haskell / 9 / libraries / deepseq-1.4.8.0 / control-deepseq.html

Control.DeepSeq

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

Description

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: deepseq-1.1.0.0

NFData class

class NFData a where Source

A class of types that can be fully evaluated.

Since: deepseq-1.1.0.0

Minimal complete definition

Nothing

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.

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)

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

instance NFData Colour where rnf = rwhnf

or

{-# LANGUAGE BangPatterns #-}
instance NFData Colour where rnf !_ = ()

default rnf :: (Generic a, GNFData Zero (Rep a)) => a -> () Source

Instances
Instances details
NFData ByteArray Source

Since: deepseq-1.4.7.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: ByteArray -> () Source

NFData All Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: All -> () Source

NFData Any Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Any -> () Source

NFData TypeRep Source

NOTE: Prior to deepseq-1.4.4.0 this instance was 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 -> () Source

NFData Unique Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Unique -> () Source

NFData Version Source

Since: deepseq-1.3.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Version -> () Source

NFData Void Source

Defined as rnf = absurd.

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Void -> () Source

NFData CBool Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CBool -> () Source

NFData CChar Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CChar -> () Source

NFData CClock Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CClock -> () Source

NFData CDouble Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CDouble -> () Source

NFData CFile Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CFile -> () Source

NFData CFloat Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CFloat -> () Source

NFData CFpos Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CFpos -> () Source

NFData CInt Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CInt -> () Source

NFData CIntMax Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CIntMax -> () Source

NFData CIntPtr Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CIntPtr -> () Source

NFData CJmpBuf Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CJmpBuf -> () Source

NFData CLLong Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CLLong -> () Source

NFData CLong Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CLong -> () Source

NFData CPtrdiff Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CPtrdiff -> () Source

NFData CSChar Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CSChar -> () Source

NFData CSUSeconds Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CSUSeconds -> () Source

NFData CShort Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CShort -> () Source

NFData CSigAtomic Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CSigAtomic -> () Source

NFData CSize Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CSize -> () Source

NFData CTime Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CTime -> () Source

NFData CUChar Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUChar -> () Source

NFData CUInt Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUInt -> () Source

NFData CUIntMax Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUIntMax -> () Source

NFData CUIntPtr Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUIntPtr -> () Source

NFData CULLong Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CULLong -> () Source

NFData CULong Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CULong -> () Source

NFData CUSeconds Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUSeconds -> () Source

NFData CUShort Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUShort -> () Source

NFData CWchar Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CWchar -> () Source

NFData ThreadId Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: ThreadId -> () Source

NFData Fingerprint Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Fingerprint -> () Source

NFData MaskingState Source

Since: deepseq-1.4.4.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: MaskingState -> () Source

NFData ExitCode Source

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: ExitCode -> () Source

NFData Int16 Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int16 -> () Source

NFData Int32 Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int32 -> () Source

NFData Int64 Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int64 -> () Source

NFData Int8 Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int8 -> () Source

NFData CallStack Source

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CallStack -> () Source

NFData SrcLoc Source

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: SrcLoc -> () Source

NFData Word16 Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word16 -> () Source

NFData Word32 Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word32 -> () Source

NFData Word64 Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word64 -> () Source

NFData Word8 Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word8 -> () Source

NFData Ordering Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Ordering -> () Source

NFData TyCon Source

NOTE: Prior to deepseq-1.4.4.0 this instance was 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 -> () Source

NFData Integer Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Integer -> () Source

NFData Natural Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Natural -> () Source

NFData () Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: () -> () Source

NFData Bool Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Bool -> () Source

NFData Char Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Char -> () Source

NFData Double Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Double -> () Source

NFData Float Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Float -> () Source

NFData Int Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int -> () Source

NFData Word Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word -> () Source

NFData a => NFData (ZipList a) Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: ZipList a -> () Source

NFData (MutableByteArray s) Source

Since: deepseq-1.4.8.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: MutableByteArray s -> () Source

NFData a => NFData (Complex a) Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Complex a -> () Source

NFData a => NFData (Identity a) Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Identity a -> () Source

NFData a => NFData (First a) Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: First a -> () Source

NFData a => NFData (Last a) Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Last a -> () Source

NFData a => NFData (Down a) Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Down a -> () Source

NFData a => NFData (First a) Source

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: First a -> () Source

NFData a => NFData (Last a) Source

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Last a -> () Source

NFData a => NFData (Max a) Source

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Max a -> () Source

NFData a => NFData (Min a) Source

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Min a -> () Source

NFData m => NFData (WrappedMonoid m) Source

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: WrappedMonoid m -> () Source

NFData a => NFData (Dual a) Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Dual a -> () Source

NFData a => NFData (Product a) Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Product a -> () Source

NFData a => NFData (Sum a) Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Sum a -> () Source

NFData (IORef a) Source

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 -> () Source

NFData (MVar a) Source

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 -> () Source

NFData (FunPtr a) Source

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: FunPtr a -> () Source

NFData (Ptr a) Source

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Ptr a -> () Source

NFData a => NFData (Ratio a) Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Ratio a -> () Source

NFData (StableName a) Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: StableName a -> () Source

NFData a => NFData (NonEmpty a) Source

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: NonEmpty a -> () Source

NFData a => NFData (Maybe a) Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Maybe a -> () Source

NFData a => NFData (a) Source

Since: deepseq-1.4.6.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: (a) -> () Source

NFData a => NFData [a] Source
Instance details

Defined in Control.DeepSeq

Methods

rnf :: [a] -> () Source

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

Defined in Control.DeepSeq

Methods

rnf :: Either a b -> () Source

NFData (Fixed a) Source

Since: deepseq-1.3.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Fixed a -> () Source

NFData (Proxy a) Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Proxy a -> () Source

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

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Arg a b -> () Source

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

Defined in Control.DeepSeq

Methods

rnf :: Array a b -> () Source

NFData (STRef s a) Source

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 -> () Source

NFData (a -> b) Source

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) -> () Source

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

Defined in Control.DeepSeq

Methods

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

NFData a => NFData (Const a b) Source

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Const a b -> () Source

NFData (a :~: b) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

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

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

Defined in Control.DeepSeq

Methods

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

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

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

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

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

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

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

NFData (a :~~: b) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

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

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

Defined in Control.DeepSeq

Methods

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

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

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

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

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

Defined in Control.DeepSeq

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

Defined in Control.DeepSeq

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

Defined in Control.DeepSeq

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

Defined in Control.DeepSeq

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

Defined in Control.DeepSeq

Methods

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

Helper functions

deepseq :: NFData a => a -> b -> b infixr 0 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: deepseq-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: deepseq-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: deepseq-1.2.0.0

(<$!!>) :: (Monad m, NFData b) => (a -> b) -> m a -> m b infixl 4 Source

Deeply strict version of <$>.

Since: deepseq-1.4.3.0

rwhnf :: a -> () Source

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: deepseq-1.4.3.0

Liftings of the NFData class

For unary constructors

class NFData1 f where Source

A class of functors that can be fully evaluated.

Since: deepseq-1.4.3.0

Minimal complete definition

Nothing

Methods

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.

default liftRnf :: (Generic1 f, GNFData One (Rep1 f)) => (a -> ()) -> f a -> () Source

Instances
Instances details
NFData1 ZipList Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> ZipList a -> () Source

NFData1 Identity Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Identity a -> () Source

NFData1 First Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> First a -> () Source

NFData1 Last Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Last a -> () Source

NFData1 Down Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Down a -> () Source

NFData1 First Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> First a -> () Source

NFData1 Last Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Last a -> () Source

NFData1 Max Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Max a -> () Source

NFData1 Min Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Min a -> () Source

NFData1 WrappedMonoid Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> WrappedMonoid a -> () Source

NFData1 Dual Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Dual a -> () Source

NFData1 Product Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Product a -> () Source

NFData1 Sum Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Sum a -> () Source

NFData1 IORef Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> IORef a -> () Source

NFData1 MVar Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> MVar a -> () Source

NFData1 FunPtr Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> FunPtr a -> () Source

NFData1 Ptr Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Ptr a -> () Source

NFData1 Ratio Source

Available on base >=4.9

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Ratio a -> () Source

NFData1 StableName Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> StableName a -> () Source

NFData1 NonEmpty Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> NonEmpty a -> () Source

NFData1 Maybe Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Maybe a -> () Source

NFData1 Solo Source

Since: deepseq-1.4.6.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Solo a -> () Source

NFData1 [] Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> [a] -> () Source

NFData a => NFData1 (Either a) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a0 -> ()) -> Either a a0 -> () Source

NFData1 (Fixed :: Type -> Type) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Fixed a -> () Source

NFData1 (Proxy :: Type -> Type) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Proxy a -> () Source

NFData a => NFData1 (Arg a) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a0 -> ()) -> Arg a a0 -> () Source

NFData a => NFData1 (Array a) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a0 -> ()) -> Array a a0 -> () Source

NFData1 (STRef s) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> STRef s a -> () Source

NFData a => NFData1 ((,) a) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a0 -> ()) -> (a, a0) -> () Source

NFData a => NFData1 (Const a :: Type -> Type) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a0 -> ()) -> Const a a0 -> () Source

NFData1 ((:~:) a) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a0 -> ()) -> (a :~: a0) -> () Source

(NFData a1, NFData a2) => NFData1 ((,,) a1 a2) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> (a1, a2, a) -> () Source

(NFData1 f, NFData1 g) => NFData1 (Product f g) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Product f g a -> () Source

(NFData1 f, NFData1 g) => NFData1 (Sum f g) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Sum f g a -> () Source

NFData1 ((:~~:) a :: Type -> Type) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a0 -> ()) -> (a :~~: a0) -> () Source

(NFData a1, NFData a2, NFData a3) => NFData1 ((,,,) a1 a2 a3) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> (a1, a2, a3, a) -> () Source

(NFData1 f, NFData1 g) => NFData1 (Compose f g) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Compose f g a -> () Source

(NFData a1, NFData a2, NFData a3, NFData a4) => NFData1 ((,,,,) a1 a2 a3 a4) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> (a1, a2, a3, a4, a) -> () Source

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

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> (a1, a2, a3, a4, a5, a) -> () Source

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => NFData1 ((,,,,,,) a1 a2 a3 a4 a5 a6) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> (a1, a2, a3, a4, a5, a6, a) -> () Source

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => NFData1 ((,,,,,,,) a1 a2 a3 a4 a5 a6 a7) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> (a1, a2, a3, a4, a5, a6, a7, a) -> () Source

(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) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> (a1, a2, a3, a4, a5, a6, a7, a8, a) -> () Source

rnf1 :: (NFData1 f, NFData a) => f a -> () Source

Lift the standard rnf function through the type constructor.

Since: deepseq-1.4.3.0

For binary constructors

class NFData2 p where Source

A class of bifunctors that can be fully evaluated.

Since: deepseq-1.4.3.0

Methods

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.

Instances
Instances details
NFData2 Either Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> Either a b -> () Source

NFData2 Arg Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> Arg a b -> () Source

NFData2 Array Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> Array a b -> () Source

NFData2 STRef Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> STRef a b -> () Source

NFData2 (,) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

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

NFData2 (Const :: Type -> Type -> Type) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> Const a b -> () Source

NFData2 ((:~:) :: Type -> Type -> Type) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> (a :~: b) -> () Source

NFData a1 => NFData2 ((,,) a1) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> (a1, a, b) -> () Source

NFData2 ((:~~:) :: Type -> Type -> Type) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> (a :~~: b) -> () Source

(NFData a1, NFData a2) => NFData2 ((,,,) a1 a2) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> (a1, a2, a, b) -> () Source

(NFData a1, NFData a2, NFData a3) => NFData2 ((,,,,) a1 a2 a3) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> (a1, a2, a3, a, b) -> () Source

(NFData a1, NFData a2, NFData a3, NFData a4) => NFData2 ((,,,,,) a1 a2 a3 a4) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> (a1, a2, a3, a4, a, b) -> () Source

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

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> (a1, a2, a3, a4, a5, a, b) -> () Source

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => NFData2 ((,,,,,,,) a1 a2 a3 a4 a5 a6) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> (a1, a2, a3, a4, a5, a6, a, b) -> () Source

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => NFData2 ((,,,,,,,,) a1 a2 a3 a4 a5 a6 a7) Source

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> (a1, a2, a3, a4, a5, a6, a7, a, b) -> () Source

rnf2 :: (NFData2 p, NFData a, NFData b) => p a b -> () Source

Lift the standard rnf function through the type constructor.

Since: deepseq-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/9.4.2/docs/libraries/deepseq-1.4.8.0/Control-DeepSeq.html