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 <rasfar@gmail.com>
Stabilityprovisional
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Control.DeepSeq.Bounded.Generic.GNFDataN

Description

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

NFDataN does not have any superclasses.

It is also possible to derive instances using GHC.Generics, which avoids SOP and TH, but if you plan to use NFDataP then SOP is required. (SOP can be used without TH if necessary; the interested reader is referred to SOP documentation.)

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 GADTs #-}  -- for GHC < 7.8 (== 7.6.3)

import Generics.SOP.TH
import Control.DeepSeq.Bounded ( NFDataN(..), grnfn )
import GHC.Generics ( Generic )

import Control.DeepSeq.Bounded ( forcen )

data TA = A1 TB TA | A2  deriving ( Generic )
instance NFDataN TA where rnfn = grnfn

data TB = B1 Int | B2 TA  deriving ( Generic )
instance NFDataN TB where rnfn = grnfn

deriveGeneric ''TA
deriveGeneric ''TB

main = return $! forcen 3 (A1 (B2 undefined) A2)

Documentation

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