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

-- |
-- Module      :  Control.DeepSeq.Bounded.Generics
-- Copyright   :  (c) 2014, Andrew G. Seniuk
-- License     :  BSD-style (see the LICENSE file)
--
-- Maintainer  :  Andrew Seniuk <rasfar@gmail.com>
-- Stability   :  provisional
-- Portability :  GHC
--
-- Support for generic deriving (via "Generics.SOP") of 'NFDataN' and 'NFDataP' instances.
--
-- This metaboilerplate is standard for using the generic deriving
-- facilities of GHC.Generics and Generics.SOP.  Consider
-- <http://hackage.haskell.org/package/seqaid seqaid> for
-- a turnkey solution.
--
-- > {-# LANGUAGE TemplateHaskell #-}
-- > {-# LANGUAGE DataKinds #-}
-- > {-# LANGUAGE TypeFamilies #-}
-- > {-# LANGUAGE DeriveGeneric #-}
-- > {-# LANGUAGE DeriveDataTypeable #-}
-- > 
-- > import Generics.SOP.TH
-- > import Control.DeepSeq.Bounded ( NFDataN(..), grnfn, NFDataP(..), grnfp )
-- > 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 ( 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

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

  module Control.DeepSeq.Bounded.Generics (

#if USE_SOP
      grnf_
    , gseq_
    , gforce_
#endif

#if USE_SOP
    , grnfn
#else
    , genericRnfn
--  , genericRnfnV1
#endif

#if USE_SOP
#if USE_SOP
    , grnfp
#else
#if 1
    , genericRnfp
#if 0
    , genericRnfpV1
#endif
#endif
#endif
#endif

#if 0
      -- * "Control.DeepSeq" re-exports
    , deepseq
    , force
    , NFData(rnf)
    , ($!!)
#endif

  ) where

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

  -- In its own category, relative to GNFDataN and GNFDataP.
  -- A GHC.Generics alternative is also quite possible?
  -- Both these still require SOP instances to be derived
  -- for user data types, however, which ... well, so does
  -- the current version of Seqable (require NFDataN instances)...
#if USE_SOP
  import Control.DeepSeq.Bounded.Generics.GSeqable
#endif

  import Control.DeepSeq.Bounded.Generics.GNFDataN
#if USE_SOP
  import Control.DeepSeq.Bounded.Generics.GNFDataP
#endif

--import Control.DeepSeq.Bounded
--import Control.DeepSeq  -- needed?
--import GHC.Generics

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