Safe Haskell | None |
---|
Module providing Template Haskell based NFData
instance
generators and WHNF=NF type inspectors.
To use this module enable the TemplateHaskell
extension and
import Control.DeepSeq.TH:
{-# LANGUAGE TemplateHaskell #-} import Control.DeepSeq.TH
- deriveNFData :: Name -> Q [Dec]
- deriveNFDatas :: [Name] -> Q [Dec]
- typeWhnfIsNf :: Type -> Q (Maybe Bool)
- decWhnfIsNf :: Dec -> Q (Maybe Bool)
Documentation
deriveNFData :: Name -> Q [Dec]Source
Derive NFData
instance for simple Data
-declarations
Example usage for deriving NFData
instance for the type TypeName
:
$(deriveNFData ''TypeName)
The derivation tries to avoid evaluation of strict fields whose
types have the WHNF=NF property (see also typeWhnfIsNf
and
decWhnfIsNf
). For instance, consider the following types Foo
and Bar
:
data Foo a = Foo1 | Foo2 !Int !String | Foo3 (Foo a) | Foo4 { fX :: Int, fY :: Char } | Foo5 !Bar | Foo6 !(String -> Int) | Foo a :--: !Bool data Bar = Bar0 | Bar1 !Char | Bar2 !Int !Int | Bar3 !Bar
By invoking $(deriveNFData ''Foo)
the generated NFData
instance
will be equivalent to:
instance NFData a => NFData (Foo a) where rnf Foo1 = () rnf (Foo2 _ x) = x `deepseq` () rnf (Foo3 x) = x `deepseq` () rnf (Foo4 x y) = x `deepseq` y `deepseq` () rnf (Foo5 _) = () rnf (Foo6 _) = () rnf (x :--: _) = x `deepseq` ()
Whereas $(deriveNFData ''Bar)
generates the following default
NFData
instance since Bar
is inferred as a WHNF=NF type:
instance NFData Bar
Known issues/limitations:
-
TypeName
must be a properdata
typename (use theGeneralizedNewtypeDeriving
extension fornewtype
names) - Does not support existential types yet (i.e. use of the
forall
keyword) - Does not always detect phantom type variables (e.g. for
data Foo a = Foo0 | Foo1 (Foo a)
) which causes those to requireNFData
instances.
deriveNFDatas :: [Name] -> Q [Dec]Source
Plural version of deriveNFData
Convenience wrapper for deriveNFData
which allows to derive
multiple NFData
instances for a list of TypeName
s, e.g.:
$(deriveNFData [''TypeName1, ''TypeName2, ''TypeName3])
typeWhnfIsNf :: Type -> Q (Maybe Bool)Source
Try to infer whether Type
has the property that WHNF=NF for its
values.
A result of Nothing
means it is not known whether the
property holds for the given type. Just True
means that the
property holds.
This function has currently a rather limited knowledge and returns
Nothing
most of the time except for some primitive types and
other simple cases.
See also decWhnfIsNf
decWhnfIsNf :: Dec -> Q (Maybe Bool)Source
Try to infer whether a Dec
which defines a type which has the
property that WHNF=NF for its values. This property is derived
statically via the following simple rules:
-
newtype
s are WHNF=NF if the wrapped type is WHNF=NF -
type
s are WHNF=NF if the aliased type is WHNF=NF - Types defined by
data
are WHNF=NF if all constructors contain only strict fields with WHNF=NF types
Known limitations:
- Doesn't work properly with parametrized declarations (in which
case
Nothing
is returned) or existential types
See also typeWhnfIsNf