-------------------------------------------------------------------------------

{-  LANGUAGE CPP #-}

-------------------------------------------------------------------------------

-- |
-- Module      :  Control.DeepSeq.Bounded.Generic.GNFDataP
-- Copyright   :  Andrew G. Seniuk 2014-2015
-- License     :  BSD-style (see the LICENSE file)
--
-- Maintainer  :  Andrew Seniuk <rasfar@gmail.com>
-- Stability   :  provisional
-- Portability :  GHC (uses SOP)
--
-- Support for generic deriving (via <http://hackage.haskell.org/package/generics-sop/docs/Generics-SOP.html 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 <http://hackage.haskell.org/package/generics-sop/docs/Generics-SOP.html Generics.SOP>.
-- Consider <http://hackage.haskell.org/package/seqaid 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)

-------------------------------------------------------------------------------

  module Control.DeepSeq.Bounded.Generic.GNFDataP
  (

#if NEW_IMPROVED_PATTERN_GRAMMAR
    module Control.DeepSeq.Bounded.Generic.GNFDataP_new_grammar  ,
#else
    module Control.DeepSeq.Bounded.Generic.GNFDataP_old_grammar  ,
#endif

  )
  where

-------------------------------------------------------------------------------

  -- for Haddock!
  import Control.DeepSeq.Bounded.NFDataP ( NFDataP )
  import Control.DeepSeq.Bounded.NFDataN ( NFDataN )
  import Control.DeepSeq ( NFData )
  import Data.Typeable ( Typeable )

#if NEW_IMPROVED_PATTERN_GRAMMAR
  import Control.DeepSeq.Bounded.Generic.GNFDataP_new_grammar
#else
  import Control.DeepSeq.Bounded.Generic.GNFDataP_old_grammar
#endif

-------------------------------------------------------------------------------