deepseq-1.4.3.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

Contents

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

Synopsis

NFData class

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.

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 !_ = ()

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 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 !_ = ()

Instances

NFData Bool Source # 

Methods

rnf :: Bool -> () Source #

NFData Char Source # 

Methods

rnf :: Char -> () Source #

NFData Double Source # 

Methods

rnf :: Double -> () Source #

NFData Float Source # 

Methods

rnf :: Float -> () Source #

NFData Int Source # 

Methods

rnf :: Int -> () Source #

NFData Int8 Source # 

Methods

rnf :: Int8 -> () Source #

NFData Int16 Source # 

Methods

rnf :: Int16 -> () Source #

NFData Int32 Source # 

Methods

rnf :: Int32 -> () Source #

NFData Int64 Source # 

Methods

rnf :: Int64 -> () Source #

NFData Integer Source # 

Methods

rnf :: Integer -> () Source #

NFData Natural Source #

Since: 1.4.0.0

Methods

rnf :: Natural -> () Source #

NFData Ordering Source # 

Methods

rnf :: Ordering -> () Source #

NFData Word Source # 

Methods

rnf :: Word -> () Source #

NFData Word8 Source # 

Methods

rnf :: Word8 -> () Source #

NFData Word16 Source # 

Methods

rnf :: Word16 -> () Source #

NFData Word32 Source # 

Methods

rnf :: Word32 -> () Source #

NFData Word64 Source # 

Methods

rnf :: Word64 -> () Source #

NFData CallStack Source #

Since: 1.4.2.0

Methods

rnf :: CallStack -> () Source #

NFData () Source # 

Methods

rnf :: () -> () Source #

NFData TyCon Source #

NOTE: Only defined for base-4.8.0.0 and later

Since: 1.4.0.0

Methods

rnf :: TyCon -> () Source #

NFData Void Source #

Defined as rnf = absurd.

Since: 1.4.0.0

Methods

rnf :: Void -> () Source #

NFData Unique Source #

Since: 1.4.0.0

Methods

rnf :: Unique -> () Source #

NFData Version Source #

Since: 1.3.0.0

Methods

rnf :: Version -> () Source #

NFData ThreadId Source #

Since: 1.4.0.0

Methods

rnf :: ThreadId -> () Source #

NFData ExitCode Source #

Since: 1.4.2.0

Methods

rnf :: ExitCode -> () Source #

NFData TypeRep Source #

NOTE: Only defined for base-4.8.0.0 and later

Since: 1.4.0.0

Methods

rnf :: TypeRep -> () Source #

NFData All Source #

Since: 1.4.0.0

Methods

rnf :: All -> () Source #

NFData Any Source #

Since: 1.4.0.0

Methods

rnf :: Any -> () Source #

NFData CChar Source #

Since: 1.4.0.0

Methods

rnf :: CChar -> () Source #

NFData CSChar Source #

Since: 1.4.0.0

Methods

rnf :: CSChar -> () Source #

NFData CUChar Source #

Since: 1.4.0.0

Methods

rnf :: CUChar -> () Source #

NFData CShort Source #

Since: 1.4.0.0

Methods

rnf :: CShort -> () Source #

NFData CUShort Source #

Since: 1.4.0.0

Methods

rnf :: CUShort -> () Source #

NFData CInt Source #

Since: 1.4.0.0

Methods

rnf :: CInt -> () Source #

NFData CUInt Source #

Since: 1.4.0.0

Methods

rnf :: CUInt -> () Source #

NFData CLong Source #

Since: 1.4.0.0

Methods

rnf :: CLong -> () Source #

NFData CULong Source #

Since: 1.4.0.0

Methods

rnf :: CULong -> () Source #

NFData CLLong Source #

Since: 1.4.0.0

Methods

rnf :: CLLong -> () Source #

NFData CULLong Source #

Since: 1.4.0.0

Methods

rnf :: CULLong -> () Source #

NFData CBool Source #

Since: 1.4.3.0

Methods

rnf :: CBool -> () Source #

NFData CFloat Source #

Since: 1.4.0.0

Methods

rnf :: CFloat -> () Source #

NFData CDouble Source #

Since: 1.4.0.0

Methods

rnf :: CDouble -> () Source #

NFData CPtrdiff Source #

Since: 1.4.0.0

Methods

rnf :: CPtrdiff -> () Source #

NFData CSize Source #

Since: 1.4.0.0

Methods

rnf :: CSize -> () Source #

NFData CWchar Source #

Since: 1.4.0.0

Methods

rnf :: CWchar -> () Source #

NFData CSigAtomic Source #

Since: 1.4.0.0

Methods

rnf :: CSigAtomic -> () Source #

NFData CClock Source #

Since: 1.4.0.0

Methods

rnf :: CClock -> () Source #

NFData CTime Source #

Since: 1.4.0.0

Methods

rnf :: CTime -> () Source #

NFData CUSeconds Source #

Since: 1.4.0.0

Methods

rnf :: CUSeconds -> () Source #

NFData CSUSeconds Source #

Since: 1.4.0.0

Methods

rnf :: CSUSeconds -> () Source #

NFData CFile Source #

Since: 1.4.0.0

Methods

rnf :: CFile -> () Source #

NFData CFpos Source #

Since: 1.4.0.0

Methods

rnf :: CFpos -> () Source #

NFData CJmpBuf Source #

Since: 1.4.0.0

Methods

rnf :: CJmpBuf -> () Source #

NFData CIntPtr Source #

Since: 1.4.0.0

Methods

rnf :: CIntPtr -> () Source #

NFData CUIntPtr Source #

Since: 1.4.0.0

Methods

rnf :: CUIntPtr -> () Source #

NFData CIntMax Source #

Since: 1.4.0.0

Methods

rnf :: CIntMax -> () Source #

NFData CUIntMax Source #

Since: 1.4.0.0

Methods

rnf :: CUIntMax -> () Source #

NFData Fingerprint Source #

Since: 1.4.0.0

Methods

rnf :: Fingerprint -> () Source #

NFData SrcLoc Source #

Since: 1.4.2.0

Methods

rnf :: SrcLoc -> () Source #

NFData a => NFData [a] Source # 

Methods

rnf :: [a] -> () Source #

NFData a => NFData (Maybe a) Source # 

Methods

rnf :: Maybe a -> () Source #

NFData a => NFData (Ratio a) Source # 

Methods

rnf :: Ratio a -> () Source #

NFData (Ptr a) Source #

Since: 1.4.2.0

Methods

rnf :: Ptr a -> () Source #

NFData (FunPtr a) Source #

Since: 1.4.2.0

Methods

rnf :: FunPtr a -> () Source #

NFData a => NFData (Complex a) Source # 

Methods

rnf :: Complex a -> () Source #

NFData (Fixed a) Source #

Since: 1.3.0.0

Methods

rnf :: Fixed a -> () Source #

NFData a => NFData (Min a) Source #

Since: 1.4.2.0

Methods

rnf :: Min a -> () Source #

NFData a => NFData (Max a) Source #

Since: 1.4.2.0

Methods

rnf :: Max a -> () Source #

NFData a => NFData (First a) Source #

Since: 1.4.2.0

Methods

rnf :: First a -> () Source #

NFData a => NFData (Last a) Source #

Since: 1.4.2.0

Methods

rnf :: Last a -> () Source #

NFData m => NFData (WrappedMonoid m) Source #

Since: 1.4.2.0

Methods

rnf :: WrappedMonoid m -> () Source #

NFData a => NFData (Option a) Source #

Since: 1.4.2.0

Methods

rnf :: Option a -> () Source #

NFData a => NFData (NonEmpty a) Source #

Since: 1.4.2.0

Methods

rnf :: NonEmpty a -> () Source #

NFData (StableName a) Source #

Since: 1.4.0.0

Methods

rnf :: StableName a -> () Source #

NFData a => NFData (ZipList a) Source #

Since: 1.4.0.0

Methods

rnf :: ZipList a -> () Source #

NFData a => NFData (Identity a) Source #

Since: 1.4.0.0

Methods

rnf :: Identity a -> () Source #

NFData (IORef a) Source #

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

Since: 1.4.0.0

Methods

rnf :: Dual a -> () Source #

NFData a => NFData (Sum a) Source #

Since: 1.4.0.0

Methods

rnf :: Sum a -> () Source #

NFData a => NFData (Product a) Source #

Since: 1.4.0.0

Methods

rnf :: Product a -> () Source #

NFData a => NFData (First a) Source #

Since: 1.4.0.0

Methods

rnf :: First a -> () Source #

NFData a => NFData (Last a) Source #

Since: 1.4.0.0

Methods

rnf :: Last a -> () Source #

NFData a => NFData (Down a) Source #

Since: 1.4.0.0

Methods

rnf :: Down a -> () Source #

NFData (MVar a) Source #

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

Since: 1.4.2.0

Methods

rnf :: MVar 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: 1.3.0.0

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Since: 1.4.2.0

Methods

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

NFData (Proxy k a) Source #

Since: 1.4.0.0

Methods

rnf :: Proxy k a -> () Source #

NFData (STRef s a) Source #

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

Since: 1.4.2.0

Methods

rnf :: STRef s a -> () Source #

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

Methods

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

NFData a => NFData (Const k a b) Source #

Since: 1.4.0.0

Methods

rnf :: Const k a b -> () Source #

NFData ((:~:) k a b) Source #

Since: 1.4.3.0

Methods

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

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

Methods

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

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

Since: 1.4.3.0

Methods

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

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

Since: 1.4.3.0

Methods

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

NFData ((:~~:) k1 k2 a b) Source #

Since: 1.4.3.0

Methods

rnf :: (k1 :~~: k2) a b -> () Source #

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

Methods

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

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

Since: 1.4.3.0

Methods

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

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

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 # 

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 # 

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 # 

Methods

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

Helper functions

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

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

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.

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.

Instances

NFData1 [] Source #

Since: 1.4.3.0

Methods

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

NFData1 Maybe Source #

Since: 1.4.3.0

Methods

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

NFData1 Ratio Source #

Available on base >=4.9

Since: 1.4.3.0

Methods

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

NFData1 Ptr Source #

Since: 1.4.3.0

Methods

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

NFData1 FunPtr Source #

Since: 1.4.3.0

Methods

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

NFData1 Fixed Source #

Since: 1.4.3.0

Methods

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

NFData1 Min Source #

Since: 1.4.3.0

Methods

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

NFData1 Max Source #

Since: 1.4.3.0

Methods

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

NFData1 First Source #

Since: 1.4.3.0

Methods

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

NFData1 Last Source #

Since: 1.4.3.0

Methods

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

NFData1 WrappedMonoid Source #

Since: 1.4.3.0

Methods

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

NFData1 Option Source #

Since: 1.4.3.0

Methods

liftRnf :: (a -> ()) -> Option a -> () Source #

NFData1 NonEmpty Source #

Since: 1.4.3.0

Methods

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

NFData1 StableName Source #

Since: 1.4.3.0

Methods

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

NFData1 ZipList Source #

Since: 1.4.3.0

Methods

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

NFData1 Identity Source #

Since: 1.4.3.0

Methods

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

NFData1 IORef Source #

Since: 1.4.3.0

Methods

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

NFData1 Dual Source #

Since: 1.4.3.0

Methods

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

NFData1 Sum Source #

Since: 1.4.3.0

Methods

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

NFData1 Product Source #

Since: 1.4.3.0

Methods

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

NFData1 First Source #

Since: 1.4.3.0

Methods

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

NFData1 Last Source #

Since: 1.4.3.0

Methods

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

NFData1 Down Source #

Since: 1.4.3.0

Methods

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

NFData1 MVar Source #

Since: 1.4.3.0

Methods

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

NFData a => NFData1 (Either a) Source #

Since: 1.4.3.0

Methods

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

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

Since: 1.4.3.0

Methods

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

NFData a => NFData1 (Array a) Source #

Since: 1.4.3.0

Methods

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

NFData a => NFData1 (Arg a) Source #

Since: 1.4.3.0

Methods

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

NFData1 (Proxy *) Source #

Since: 1.4.3.0

Methods

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

NFData1 (STRef s) Source #

Since: 1.4.3.0

Methods

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

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

Since: 1.4.3.0

Methods

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

NFData a => NFData1 (Const * a) Source #

Since: 1.4.3.0

Methods

liftRnf :: (a -> ()) -> Const * a a -> () Source #

NFData1 ((:~:) * a) Source #

Since: 1.4.3.0

Methods

liftRnf :: (a -> ()) -> (* :~: a) a -> () Source #

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

Since: 1.4.3.0

Methods

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

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

Since: 1.4.3.0

Methods

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

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

Since: 1.4.3.0

Methods

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

NFData1 ((:~~:) k1 * a) Source #

Since: 1.4.3.0

Methods

liftRnf :: (a -> ()) -> (k1 :~~: *) a a -> () Source #

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

Since: 1.4.3.0

Methods

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

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

Since: 1.4.3.0

Methods

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

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

Since: 1.4.3.0

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

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

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

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

For binary constructors

class NFData2 p where Source #

A class of bifunctors that can be fully evaluated.

Since: 1.4.3.0

Minimal complete definition

liftRnf2

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

NFData2 Either Source #

Since: 1.4.3.0

Methods

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

NFData2 (,) Source #

Since: 1.4.3.0

Methods

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

NFData2 Array Source #

Since: 1.4.3.0

Methods

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

NFData2 Arg Source #

Since: 1.4.3.0

Methods

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

NFData2 STRef Source #

Since: 1.4.3.0

Methods

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

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

Since: 1.4.3.0

Methods

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

NFData2 (Const *) Source #

Since: 1.4.3.0

Methods

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

NFData2 ((:~:) *) Source #

Since: 1.4.3.0

Methods

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

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

Since: 1.4.3.0

Methods

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

NFData2 ((:~~:) * *) Source #

Since: 1.4.3.0

Methods

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

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

Since: 1.4.3.0

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

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

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

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

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