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

CopyrightAndrew G. Seniuk 2014-2015
LicenseBSD-style (see the LICENSE file)
MaintainerAndrew Seniuk <[email protected]>
Stabilityprovisional
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Control.DeepSeq.Bounded.Generic

Contents

Description

Support for generic deriving (via Generics.SOP) of NFDataN and NFDataP instances. Also, SOP generic functions implementing Seqable without a class and instances.

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 ( NFDataN(..), grnfn, NFDataP(..), grnfp )
import Control.DeepSeq.Generic ( NFData(..), genericRnf )
import GHC.Generics ( Generic )    -- for deriving NFData
import Data.Typeable ( Typeable )  -- for name-constrained pattern nodes
import Control.DeepSeq.Bounded ( forcen, 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 = mainP
mainN = return $! forcen 3         (A1 (B2 undefined) A2) :: IO TA
mainP = return $! forcep "((!).)"  (A1 (B2 undefined) A2) :: IO TA
mainS = return $! force_ Propagate (A1 (force_ Propagate (B2 undefined)) A2) :: IO TA

Synopsis

Stratified Generic Forcing

grnfn :: (Generic a, All2 NFDataN (Code a)) => Int -> a -> () Source

Pattern-based Generic Forcing

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

"Molecular" Generic Forcing

grnf_ :: Generic a => SeqNode -> a -> () Source

gseq_ :: Generic a => SeqNode -> a -> b -> b Source

gforce_ :: Generic a => SeqNode -> a -> a Source