{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Clash.Annotations.BitRepresentation
(
DataReprAnn(..)
, ConstrRepr(..)
, BitMask
, Value
, Size
, FieldAnn
, 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
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 :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> Q Exp
forall t. Lift t => t -> Q Exp
TH.lift)
data DataReprAnn =
DataReprAnn
TH.Type
Size
[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 :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DataReprAnn -> c DataReprAnn)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DataReprAnn)
-> (DataReprAnn -> Constr)
-> (DataReprAnn -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DataReprAnn))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
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 :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> DataReprAnn -> m DataReprAnn)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DataReprAnn -> m DataReprAnn)
-> (forall (m :: Type -> Type).
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 :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
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 :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
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 :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> DataReprAnn -> m DataReprAnn
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DataReprAnn -> m DataReprAnn
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DataReprAnn
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DataReprAnn -> c DataReprAnn
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DataReprAnn)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
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 :: Type -> Type).
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 :: Type -> Type).
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 :: Type -> Type).
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 :: Type -> Type -> Type) (c :: Type -> Type).
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 :: Type -> Type) (c :: Type -> Type).
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 :: Type -> Type).
(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 :: Type -> Type).
(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 (TExp DataReprAnn)
(DataReprAnn -> Q Exp)
-> (DataReprAnn -> Q (TExp DataReprAnn)) -> Lift DataReprAnn
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: DataReprAnn -> Q (TExp DataReprAnn)
$cliftTyped :: DataReprAnn -> Q (TExp DataReprAnn)
lift :: DataReprAnn -> Q Exp
$clift :: DataReprAnn -> Q Exp
TH.Lift)
data ConstrRepr =
ConstrRepr
TH.Name
BitMask
Value
[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 :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ConstrRepr -> c ConstrRepr)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ConstrRepr)
-> (ConstrRepr -> Constr)
-> (ConstrRepr -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ConstrRepr))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
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 :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> ConstrRepr -> m ConstrRepr)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ConstrRepr -> m ConstrRepr)
-> (forall (m :: Type -> Type).
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 :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
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 :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
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 :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> ConstrRepr -> m ConstrRepr
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ConstrRepr -> m ConstrRepr
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ConstrRepr
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ConstrRepr -> c ConstrRepr
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ConstrRepr)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
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 :: Type -> Type).
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 :: Type -> Type).
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 :: Type -> Type).
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 :: Type -> Type -> Type) (c :: Type -> Type).
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 :: Type -> Type) (c :: Type -> Type).
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 :: Type -> Type).
(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 :: Type -> Type).
(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 (TExp ConstrRepr)
(ConstrRepr -> Q Exp)
-> (ConstrRepr -> Q (TExp ConstrRepr)) -> Lift ConstrRepr
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: ConstrRepr -> Q (TExp ConstrRepr)
$cliftTyped :: ConstrRepr -> Q (TExp ConstrRepr)
lift :: ConstrRepr -> Q Exp
$clift :: ConstrRepr -> Q Exp
TH.Lift)