Copyright | (c) 2012, Herbert Valerio Riedel |
---|---|
License | BSD-style (see the LICENSE file) |
Maintainer | Herbert Valerio Riedel <hvr@gnu.org> |
Stability | stable |
Portability | GHC |
Safe Haskell | Safe |
Language | Haskell2010 |
NOTE: Starting with deepseq-1.4.0.0
, NFData
gained support
for generic derivation via DefaultSignatures
. The new default
rnf
method implementation is then equivalent to
instance NFData MyType wherernf
=genericRnfV1
See documentation of rnf
for more details on how to use the new
built-in Generic
support.
- genericRnf :: (Generic a, GNFData (Rep a)) => a -> ()
- genericRnfV1 :: (Generic a, GNFDataV1 (Rep a)) => a -> ()
Documentation
genericRnf :: (Generic a, GNFData (Rep a)) => a -> () Source
GHC.Generics-based rnf
implementation
This provides a generic rnf
implementation for one type at a
time. If the type of the value genericRnf
is asked to reduce to
NF contains values of other types, those types have to provide
NFData
instances. This also means that recursive types can only
be used with genericRnf
if a NFData
instance has been defined
as well (see examples below).
The typical usage for genericRnf
is for reducing boilerplate code
when defining NFData
instances for ordinary algebraic
datatypes. See the code below for some simple usage examples:
{-# LANGUAGE DeriveGeneric #-} import Control.DeepSeq import Control.DeepSeq.Generics (genericRnf) import GHC.Generics -- simple record data Foo = Foo AccountId Name Address deriving Generic type Address = [String] type Name = String newtype AccountId = AccountId Int instance NFData AccountId instance NFData Foo where rnf = genericRnf -- recursive list-like type data N = Z | S N deriving Generic instance NFData N where rnf = genericRnf -- parametric & recursive type data Bar a = Bar0 | Bar1 a | Bar2 (Bar a) deriving Generic instance NFData a => NFData (Bar a) where rnf = genericRnf
NOTE: The GNFData
type-class showing up in the type-signature is
used internally and not exported.
genericRnfV1 :: (Generic a, GNFDataV1 (Rep a)) => a -> () Source
Variant of genericRnf
which supports derivation for uninhabited types.
For instance, the type
data TagFoo deriving Generic
would cause a compile-time error with genericRnf
, but with
genericRnfV1
the error is deferred to run-time:
Prelude> genericRnf (undefined :: TagFoo) <interactive>:1:1: No instance for (GNFData V1) arising from a use of `genericRnf' Possible fix: add an instance declaration for (GNFData V1) In the expression: genericRnf (undefined :: TagFoo) In an equation for `it': it = genericRnf (undefined :: TagFoo) Prelude> genericRnfV1 (undefined :: TagFoo) *** Exception: Control.DeepSeq.Generics.genericRnfV1: uninhabited type
genericRnfV1
corresponds to deepseq-1.4.0.0
's default rnf
method implementation.
NOTE: The GNFDataV1
type-class showing up in the type-signature is
used internally and not exported.
Since: 0.1.1.0