{-|
Copyright  :  (C) 2018, Google Inc.
License    :  BSD2 (see the file LICENSE)
Maintainer :  Christiaan Baaij <christiaan.baaij@gmail.com>

Using /ANN/ pragma's you can tell the Clash compiler to use a custom
bit representation for a data type. See @DataReprAnn@ for documentation.

-}

{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric      #-}
{-# LANGUAGE DeriveLift         #-}
{-# LANGUAGE RankNTypes         #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell    #-}

{-# OPTIONS_GHC -Wno-orphans #-}

module Clash.Annotations.BitRepresentation
 (
 -- * Data structures to express a custom bit representation
   DataReprAnn(..)
 , ConstrRepr(..)
 -- * Convenience type synonyms for Integer
 , BitMask
 , Value
 , Size
 , FieldAnn

 -- * Functions
 , liftQ
 ) where

import           Data.Data                  (Data)
import           Data.Typeable              (Typeable)
import           Language.Haskell.TH.Instances ()
import qualified Language.Haskell.TH.Lift   ()
import qualified Language.Haskell.TH.Syntax as TH
import           GHC.Generics               (Generic)

type BitMask  = Integer
type Value    = Integer
type Size     = Int

type FieldAnn = BitMask

-- | Lift values inside of 'TH.Q' to a Template Haskell expression
liftQ :: TH.Lift a => TH.Q a -> TH.Q TH.Exp
liftQ :: Q a -> Q Exp
liftQ = (Q a -> (a -> Q Exp) -> Q Exp
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> Q Exp
forall t. Lift t => t -> Q Exp
TH.lift)

-- NOTE: The following instances are imported from Language.Haskell.TH.Lift.
-- This module also implements 'instance Lift Exp', which might make debugging
-- template haskell more difficult. Please uncomment these instances and the
-- import of TH.Lift whenever it suits you.
--
--deriving instance TH.Lift TH.Name
--deriving instance TH.Lift TH.OccName
--deriving instance TH.Lift TH.NameFlavour
--deriving instance TH.Lift TH.ModName
--deriving instance TH.Lift TH.NameSpace
--deriving instance TH.Lift TH.PkgName


-- | Annotation for custom bit representations of data types
--
-- Using /ANN/ pragma's you can tell the Clash compiler to use a custom
-- bit-representation for a data type.
--
-- For example:
--
-- @
-- data Color = R | G | B
-- {-# ANN module (DataReprAnn
--                   $(liftQ [t|Color|])
--                   2
--                   [ ConstrRepr 'R 0b11 0b00 []
--                   , ConstrRepr 'G 0b11 0b01 []
--                   , ConstrRepr 'B 0b11 0b10 []
--                   ]) #-}
-- @
--
-- This specifies that @R@ should be encoded as 0b00, @G@ as 0b01, and
-- @B@ as 0b10. The first binary value in every @ConstrRepr@ in this example
-- is a mask, indicating which bits in the data type are relevant. In this case
-- all of the bits are.
--
-- Or if we want to annotate @Maybe Color@:
--
-- @
-- {-# ANN module ( DataReprAnn
--                    $(liftQ [t|Maybe Color|])
--                    2
--                    [ ConstrRepr 'Nothing 0b11 0b11 []
--                    , ConstrRepr 'Just 0b00 0b00 [0b11]
--                    ] ) #-}
-- @
--
-- By default, @Maybe Color@ is a data type which consumes 3 bits. A single bit
-- to indicate the constructor (either @Just@ or @Nothing@), and two bits to encode
-- the first field of @Just@. Notice that we saved a single bit by exploiting
-- the fact that @Color@ only uses three values (0, 1, 2), but takes two bits
-- to encode it. We can therefore use the last - unused - value (3), to encode
-- one of the constructors of @Maybe@. We indicate which bits encode the
-- underlying @Color@ field of @Just@ by passing /[0b11]/ to ConstrRepr. This
-- indicates that the first field is encoded in the first and second bit of the
-- whole datatype (0b11).
data DataReprAnn =
  DataReprAnn
    -- Type this annotation is for:
    TH.Type
    -- Size of type:
    Size
    -- Constructors:
    [ConstrRepr]
      deriving (Int -> DataReprAnn -> ShowS
[DataReprAnn] -> ShowS
DataReprAnn -> String
(Int -> DataReprAnn -> ShowS)
-> (DataReprAnn -> String)
-> ([DataReprAnn] -> ShowS)
-> Show DataReprAnn
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DataReprAnn] -> ShowS
$cshowList :: [DataReprAnn] -> ShowS
show :: DataReprAnn -> String
$cshow :: DataReprAnn -> String
showsPrec :: Int -> DataReprAnn -> ShowS
$cshowsPrec :: Int -> DataReprAnn -> ShowS
Show, Typeable DataReprAnn
DataType
Constr
Typeable DataReprAnn =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> DataReprAnn -> c DataReprAnn)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c DataReprAnn)
-> (DataReprAnn -> Constr)
-> (DataReprAnn -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c DataReprAnn))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c DataReprAnn))
-> ((forall b. Data b => b -> b) -> DataReprAnn -> DataReprAnn)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> DataReprAnn -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> DataReprAnn -> r)
-> (forall u. (forall d. Data d => d -> u) -> DataReprAnn -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> DataReprAnn -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> DataReprAnn -> m DataReprAnn)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> DataReprAnn -> m DataReprAnn)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> DataReprAnn -> m DataReprAnn)
-> Data DataReprAnn
DataReprAnn -> DataType
DataReprAnn -> Constr
(forall b. Data b => b -> b) -> DataReprAnn -> DataReprAnn
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DataReprAnn -> c DataReprAnn
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DataReprAnn
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> DataReprAnn -> u
forall u. (forall d. Data d => d -> u) -> DataReprAnn -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DataReprAnn -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DataReprAnn -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DataReprAnn -> m DataReprAnn
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DataReprAnn -> m DataReprAnn
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DataReprAnn
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DataReprAnn -> c DataReprAnn
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DataReprAnn)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c DataReprAnn)
$cDataReprAnn :: Constr
$tDataReprAnn :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> DataReprAnn -> m DataReprAnn
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DataReprAnn -> m DataReprAnn
gmapMp :: (forall d. Data d => d -> m d) -> DataReprAnn -> m DataReprAnn
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DataReprAnn -> m DataReprAnn
gmapM :: (forall d. Data d => d -> m d) -> DataReprAnn -> m DataReprAnn
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DataReprAnn -> m DataReprAnn
gmapQi :: Int -> (forall d. Data d => d -> u) -> DataReprAnn -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> DataReprAnn -> u
gmapQ :: (forall d. Data d => d -> u) -> DataReprAnn -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> DataReprAnn -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DataReprAnn -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DataReprAnn -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DataReprAnn -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DataReprAnn -> r
gmapT :: (forall b. Data b => b -> b) -> DataReprAnn -> DataReprAnn
$cgmapT :: (forall b. Data b => b -> b) -> DataReprAnn -> DataReprAnn
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c DataReprAnn)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c DataReprAnn)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c DataReprAnn)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DataReprAnn)
dataTypeOf :: DataReprAnn -> DataType
$cdataTypeOf :: DataReprAnn -> DataType
toConstr :: DataReprAnn -> Constr
$ctoConstr :: DataReprAnn -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DataReprAnn
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DataReprAnn
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DataReprAnn -> c DataReprAnn
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DataReprAnn -> c DataReprAnn
$cp1Data :: Typeable DataReprAnn
Data, Typeable, DataReprAnn -> DataReprAnn -> Bool
(DataReprAnn -> DataReprAnn -> Bool)
-> (DataReprAnn -> DataReprAnn -> Bool) -> Eq DataReprAnn
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DataReprAnn -> DataReprAnn -> Bool
$c/= :: DataReprAnn -> DataReprAnn -> Bool
== :: DataReprAnn -> DataReprAnn -> Bool
$c== :: DataReprAnn -> DataReprAnn -> Bool
Eq, (forall x. DataReprAnn -> Rep DataReprAnn x)
-> (forall x. Rep DataReprAnn x -> DataReprAnn)
-> Generic DataReprAnn
forall x. Rep DataReprAnn x -> DataReprAnn
forall x. DataReprAnn -> Rep DataReprAnn x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DataReprAnn x -> DataReprAnn
$cfrom :: forall x. DataReprAnn -> Rep DataReprAnn x
Generic, DataReprAnn -> Q Exp
(DataReprAnn -> Q Exp) -> Lift DataReprAnn
forall t. (t -> Q Exp) -> Lift t
lift :: DataReprAnn -> Q Exp
$clift :: DataReprAnn -> Q Exp
TH.Lift)

-- | Annotation for constructors. Indicates how to match this constructor based
-- off of the whole datatype.
data ConstrRepr =
  ConstrRepr
    -- Constructor name:
    TH.Name
    -- Bits relevant for this constructor:
    BitMask
    -- data & mask should be equal to..:
    Value
    -- Masks for fields. Indicates where fields are stored:
    [FieldAnn]
      deriving (Int -> ConstrRepr -> ShowS
[ConstrRepr] -> ShowS
ConstrRepr -> String
(Int -> ConstrRepr -> ShowS)
-> (ConstrRepr -> String)
-> ([ConstrRepr] -> ShowS)
-> Show ConstrRepr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConstrRepr] -> ShowS
$cshowList :: [ConstrRepr] -> ShowS
show :: ConstrRepr -> String
$cshow :: ConstrRepr -> String
showsPrec :: Int -> ConstrRepr -> ShowS
$cshowsPrec :: Int -> ConstrRepr -> ShowS
Show, Typeable ConstrRepr
DataType
Constr
Typeable ConstrRepr =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> ConstrRepr -> c ConstrRepr)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ConstrRepr)
-> (ConstrRepr -> Constr)
-> (ConstrRepr -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c ConstrRepr))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c ConstrRepr))
-> ((forall b. Data b => b -> b) -> ConstrRepr -> ConstrRepr)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> ConstrRepr -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> ConstrRepr -> r)
-> (forall u. (forall d. Data d => d -> u) -> ConstrRepr -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> ConstrRepr -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> ConstrRepr -> m ConstrRepr)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ConstrRepr -> m ConstrRepr)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ConstrRepr -> m ConstrRepr)
-> Data ConstrRepr
ConstrRepr -> DataType
ConstrRepr -> Constr
(forall b. Data b => b -> b) -> ConstrRepr -> ConstrRepr
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ConstrRepr -> c ConstrRepr
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ConstrRepr
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ConstrRepr -> u
forall u. (forall d. Data d => d -> u) -> ConstrRepr -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ConstrRepr -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ConstrRepr -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ConstrRepr -> m ConstrRepr
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ConstrRepr -> m ConstrRepr
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ConstrRepr
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ConstrRepr -> c ConstrRepr
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ConstrRepr)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConstrRepr)
$cConstrRepr :: Constr
$tConstrRepr :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> ConstrRepr -> m ConstrRepr
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ConstrRepr -> m ConstrRepr
gmapMp :: (forall d. Data d => d -> m d) -> ConstrRepr -> m ConstrRepr
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ConstrRepr -> m ConstrRepr
gmapM :: (forall d. Data d => d -> m d) -> ConstrRepr -> m ConstrRepr
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ConstrRepr -> m ConstrRepr
gmapQi :: Int -> (forall d. Data d => d -> u) -> ConstrRepr -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ConstrRepr -> u
gmapQ :: (forall d. Data d => d -> u) -> ConstrRepr -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ConstrRepr -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ConstrRepr -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ConstrRepr -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ConstrRepr -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ConstrRepr -> r
gmapT :: (forall b. Data b => b -> b) -> ConstrRepr -> ConstrRepr
$cgmapT :: (forall b. Data b => b -> b) -> ConstrRepr -> ConstrRepr
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConstrRepr)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConstrRepr)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ConstrRepr)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ConstrRepr)
dataTypeOf :: ConstrRepr -> DataType
$cdataTypeOf :: ConstrRepr -> DataType
toConstr :: ConstrRepr -> Constr
$ctoConstr :: ConstrRepr -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ConstrRepr
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ConstrRepr
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ConstrRepr -> c ConstrRepr
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ConstrRepr -> c ConstrRepr
$cp1Data :: Typeable ConstrRepr
Data, Typeable, ConstrRepr -> ConstrRepr -> Bool
(ConstrRepr -> ConstrRepr -> Bool)
-> (ConstrRepr -> ConstrRepr -> Bool) -> Eq ConstrRepr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConstrRepr -> ConstrRepr -> Bool
$c/= :: ConstrRepr -> ConstrRepr -> Bool
== :: ConstrRepr -> ConstrRepr -> Bool
$c== :: ConstrRepr -> ConstrRepr -> Bool
Eq, (forall x. ConstrRepr -> Rep ConstrRepr x)
-> (forall x. Rep ConstrRepr x -> ConstrRepr) -> Generic ConstrRepr
forall x. Rep ConstrRepr x -> ConstrRepr
forall x. ConstrRepr -> Rep ConstrRepr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ConstrRepr x -> ConstrRepr
$cfrom :: forall x. ConstrRepr -> Rep ConstrRepr x
Generic, ConstrRepr -> Q Exp
(ConstrRepr -> Q Exp) -> Lift ConstrRepr
forall t. (t -> Q Exp) -> Lift t
lift :: ConstrRepr -> Q Exp
$clift :: ConstrRepr -> Q Exp
TH.Lift)