{-# LANGUAGE RankNTypes #-}
{-# 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 :: forall a. Lift a => Q a -> Q Exp
liftQ = (Q a -> (a -> Q Exp) -> Q Exp
forall a b. Q a -> (a -> Q b) -> Q b
forall (m :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> Q Exp
forall t (m :: Type -> Type). (Lift t, Quote m) => t -> m Exp
forall (m :: Type -> Type). Quote m => a -> m 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
$cshowsPrec :: Int -> DataReprAnn -> ShowS
showsPrec :: Int -> DataReprAnn -> ShowS
$cshow :: DataReprAnn -> String
show :: DataReprAnn -> String
$cshowList :: [DataReprAnn] -> ShowS
showList :: [DataReprAnn] -> ShowS
Show, Typeable DataReprAnn
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 -> Constr
DataReprAnn -> DataType
(forall b. Data b => b -> b) -> DataReprAnn -> 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)
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DataReprAnn -> c DataReprAnn
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DataReprAnn -> 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
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DataReprAnn
$ctoConstr :: DataReprAnn -> Constr
toConstr :: DataReprAnn -> Constr
$cdataTypeOf :: DataReprAnn -> DataType
dataTypeOf :: DataReprAnn -> DataType
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DataReprAnn)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> 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)
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c DataReprAnn)
$cgmapT :: (forall b. Data b => b -> b) -> DataReprAnn -> DataReprAnn
gmapT :: (forall b. Data b => b -> b) -> DataReprAnn -> DataReprAnn
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DataReprAnn -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DataReprAnn -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> DataReprAnn -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> DataReprAnn -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> DataReprAnn -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> DataReprAnn -> u
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> DataReprAnn -> m DataReprAnn
gmapM :: forall (m :: Type -> Type).
Monad m =>
(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
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(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
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DataReprAnn -> m DataReprAnn
Data, Typeable, DataReprAnn -> DataReprAnn -> Bool
(DataReprAnn -> DataReprAnn -> Bool)
-> (DataReprAnn -> DataReprAnn -> Bool) -> Eq DataReprAnn
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataReprAnn -> DataReprAnn -> Bool
== :: DataReprAnn -> DataReprAnn -> Bool
$c/= :: DataReprAnn -> DataReprAnn -> Bool
/= :: 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
$cfrom :: forall x. DataReprAnn -> Rep DataReprAnn x
from :: forall x. DataReprAnn -> Rep DataReprAnn x
$cto :: forall x. Rep DataReprAnn x -> DataReprAnn
to :: forall x. Rep DataReprAnn x -> DataReprAnn
Generic, (forall (m :: Type -> Type). Quote m => DataReprAnn -> m Exp)
-> (forall (m :: Type -> Type).
Quote m =>
DataReprAnn -> Code m DataReprAnn)
-> Lift DataReprAnn
forall t.
(forall (m :: Type -> Type). Quote m => t -> m Exp)
-> (forall (m :: Type -> Type). Quote m => t -> Code m t) -> Lift t
forall (m :: Type -> Type). Quote m => DataReprAnn -> m Exp
forall (m :: Type -> Type).
Quote m =>
DataReprAnn -> Code m DataReprAnn
$clift :: forall (m :: Type -> Type). Quote m => DataReprAnn -> m Exp
lift :: forall (m :: Type -> Type). Quote m => DataReprAnn -> m Exp
$cliftTyped :: forall (m :: Type -> Type).
Quote m =>
DataReprAnn -> Code m DataReprAnn
liftTyped :: forall (m :: Type -> Type).
Quote m =>
DataReprAnn -> Code m DataReprAnn
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
$cshowsPrec :: Int -> ConstrRepr -> ShowS
showsPrec :: Int -> ConstrRepr -> ShowS
$cshow :: ConstrRepr -> String
show :: ConstrRepr -> String
$cshowList :: [ConstrRepr] -> ShowS
showList :: [ConstrRepr] -> ShowS
Show, Typeable ConstrRepr
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 -> Constr
ConstrRepr -> DataType
(forall b. Data b => b -> b) -> ConstrRepr -> 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)
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ConstrRepr -> c ConstrRepr
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ConstrRepr -> 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
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ConstrRepr
$ctoConstr :: ConstrRepr -> Constr
toConstr :: ConstrRepr -> Constr
$cdataTypeOf :: ConstrRepr -> DataType
dataTypeOf :: ConstrRepr -> DataType
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ConstrRepr)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> 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)
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConstrRepr)
$cgmapT :: (forall b. Data b => b -> b) -> ConstrRepr -> ConstrRepr
gmapT :: (forall b. Data b => b -> b) -> ConstrRepr -> ConstrRepr
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ConstrRepr -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ConstrRepr -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ConstrRepr -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ConstrRepr -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ConstrRepr -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ConstrRepr -> u
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> ConstrRepr -> m ConstrRepr
gmapM :: forall (m :: Type -> Type).
Monad m =>
(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
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(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
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ConstrRepr -> m ConstrRepr
Data, Typeable, ConstrRepr -> ConstrRepr -> Bool
(ConstrRepr -> ConstrRepr -> Bool)
-> (ConstrRepr -> ConstrRepr -> Bool) -> Eq ConstrRepr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConstrRepr -> ConstrRepr -> Bool
== :: ConstrRepr -> ConstrRepr -> Bool
$c/= :: ConstrRepr -> ConstrRepr -> Bool
/= :: 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
$cfrom :: forall x. ConstrRepr -> Rep ConstrRepr x
from :: forall x. ConstrRepr -> Rep ConstrRepr x
$cto :: forall x. Rep ConstrRepr x -> ConstrRepr
to :: forall x. Rep ConstrRepr x -> ConstrRepr
Generic, (forall (m :: Type -> Type). Quote m => ConstrRepr -> m Exp)
-> (forall (m :: Type -> Type).
Quote m =>
ConstrRepr -> Code m ConstrRepr)
-> Lift ConstrRepr
forall t.
(forall (m :: Type -> Type). Quote m => t -> m Exp)
-> (forall (m :: Type -> Type). Quote m => t -> Code m t) -> Lift t
forall (m :: Type -> Type). Quote m => ConstrRepr -> m Exp
forall (m :: Type -> Type).
Quote m =>
ConstrRepr -> Code m ConstrRepr
$clift :: forall (m :: Type -> Type). Quote m => ConstrRepr -> m Exp
lift :: forall (m :: Type -> Type). Quote m => ConstrRepr -> m Exp
$cliftTyped :: forall (m :: Type -> Type).
Quote m =>
ConstrRepr -> Code m ConstrRepr
liftTyped :: forall (m :: Type -> Type).
Quote m =>
ConstrRepr -> Code m ConstrRepr
TH.Lift)