-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Template Haskell based deriver for optimised NFData instances -- -- This package provides a Template Haskell based mechanism for deriving -- optimised NFData instances for custom data types. See documentation in -- Control.DeepSeq.TH for more information. -- -- See also the deepseq-generics package -- (http://hackage.haskell.org/package/deepseq-generics) for a -- less experimental approach. @package deepseq-th @version 0.1.0.4 -- | 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
--   
module Control.DeepSeq.TH -- | 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: -- -- deriveNFData :: Name -> Q [Dec] -- | 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])
--   
deriveNFDatas :: [Name] -> Q [Dec] -- | 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 typeWhnfIsNf :: Type -> Q (Maybe Bool) -- | 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: -- -- -- -- Known limitations: -- -- -- -- See also typeWhnfIsNf decWhnfIsNf :: Dec -> Q (Maybe Bool)