deepseq-bounded-0.6.0.3: Bounded deepseq, including support for generic deriving

CopyrightAndrew G. Seniuk 2014-2015
LicenseBSD-style (see the LICENSE file)
MaintainerAndrew Seniuk <rasfar@gmail.com>
Stabilityprovisional
PortabilityGHC (uses SOP)
Safe HaskellNone
LanguageHaskell2010

Control.DeepSeq.Bounded.Generic.GNFDataP

Description

Support for generic deriving (via Generics.SOP) of NFDataP instances.

Note that NFDataP has superclasses NFDataN, NFData and Typeable.

This metaboilerplate is standard for using the generic deriving facilities of GHC.Generics and Generics.SOP. Consider seqaid for a turnkey solution.

{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GADTs #-}  -- for GHC < 7.8 (== 7.6.3)

import Generics.SOP.TH
import Control.DeepSeq.Bounded ( NFDataP(..), grnfp )
import Control.DeepSeq.Bounded ( NFDataN(..), grnfn )
import Control.DeepSeq.Generics ( NFData(..), genericRnf )
import GHC.Generics ( Generic )    -- for deriving NFData
import Data.Typeable ( Typeable )  -- for name-constrained pattern nodes

import Control.DeepSeq.Bounded ( forcep )

data TA = A1 TB TA | A2  deriving ( Generic, Typeable )
instance NFData  TA where rnf  = genericRnf
instance NFDataN TA where rnfn = grnfn
instance NFDataP TA where rnfp = grnfp

data TB = B1 Int | B2 TA  deriving ( Generic, Typeable )
instance NFData  TB where rnf  = genericRnf
instance NFDataN TB where rnfn = grnfn
instance NFDataP TB where rnfp = grnfp

deriveGeneric ''TA
deriveGeneric ''TB

main = return $! forcep "((!).)" (A1 (B2 undefined) A2)

Documentation

grnfp :: forall a. (Generic a, HasDatatypeInfo a, All2 NFDataP (Code a), NFDataP a) => Pattern -> a -> () Source