deepseq-th-0.0.0.0: Provides Template Haskell deriver for NFData instances

Control.DeepSeq.TH

Synopsis

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 whnfIsNf). For instance, consider the following type Foo:

 data Foo a = Foo1
            | Foo2 !Int !String
            | Foo3 (Foo a)
            | Foo4 { fX :: Int, fY :: Char }
            | Foo a :--: !Bool

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 (x :--: _) = x `deepseq` ()

Known issues/limitations:

  • TypeName must be a proper data typename (use the GeneralizedNewtypeDeriving extension for newtype 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 require NFData 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 TypeNames, e.g.:

 $(deriveNFData [''TypeName1, ''TypeName2, ''TypeName3])

whnfIsNf :: Type -> Maybe BoolSource

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 very limited knowledge and returns Nothing most of the time except for some primitive types.