reproject-0.2.0.0: Define and combine "materialized" projections

Safe HaskellNone
LanguageHaskell2010

Data.Reproject

Contents

Synopsis

Documentation

class Proj label ty where Source #

A named projection on a type. Very similar to Has but w/o a setter

Minimal complete definition

applyProj

Associated Types

type ProjTy label ty Source #

Methods

applyProj :: LblProxy label -> ty -> ProjTy label ty Source #

data Projection t a where Source #

A list of projections to be applied to a type

Constructors

ProjNil :: Projection t '[] 
Combine :: (KnownSymbol a, Proj a t) => LblProxy (a :: Symbol) -> Projection t b -> Projection t (a ': b) 

Instances

Eq (Projection t a) Source # 

Methods

(==) :: Projection t a -> Projection t a -> Bool #

(/=) :: Projection t a -> Projection t a -> Bool #

(Proj a t, KnownSymbol a, Read (Projection t as)) => Read (Projection t ((:) Symbol a as)) Source # 

Methods

readsPrec :: Int -> ReadS (Projection t ((Symbol ': a) as)) #

readList :: ReadS [Projection t ((Symbol ': a) as)] #

readPrec :: ReadPrec (Projection t ((Symbol ': a) as)) #

readListPrec :: ReadPrec [Projection t ((Symbol ': a) as)] #

Read (Projection t ([] Symbol)) Source # 
Show (Projection t a) Source # 

Methods

showsPrec :: Int -> Projection t a -> ShowS #

show :: Projection t a -> String #

showList :: [Projection t a] -> ShowS #

type family HasProj (a :: [Symbol]) t = (r :: Constraint) where ... Source #

Construct a constraint that asserts that for all labels a projection for type t exists

Equations

HasProj '[] t = True ~ True 
HasProj (x ': xs) t = (Proj x t, HasProj xs t) 

proj :: forall t lbls. HasProj lbls t => Projection t lbls -> t -> Rec t lbls Source #

Apply all projections to a type and return them in a Labels compatible tuple. USe projVal to read single projections from it. Using OverloadedLabels is advised.

projVal :: forall label key more v t. ReadRec label (IsEqLabel key label) (Rec t (key ': more)) v => LblProxy label -> Rec t (key ': more) -> v Source #

Read a projection from a projection record

(@@) :: (KnownSymbol a, Proj a t) => LblProxy (a :: Symbol) -> Projection t b -> Projection t (a ': b) infixr 5 Source #

Infix alias for Combine

Type lifting

data AnyProj t Source #

Constructors

(Typeable x, HasProj x t) => AnyProj 

Fields

Instances

Typeable * t => Eq (AnyProj t) Source # 

Methods

(==) :: AnyProj t -> AnyProj t -> Bool #

(/=) :: AnyProj t -> AnyProj t -> Bool #

Show (AnyProj t) Source # 

Methods

showsPrec :: Int -> AnyProj t -> ShowS #

show :: AnyProj t -> String #

showList :: [AnyProj t] -> ShowS #

data AnyRec t Source #

Constructors

Typeable x => AnyRec 

Fields

anyToTypedProj :: forall t x. (HasProj x t, Typeable x, Typeable t) => (AnyProj t -> AnyRec t) -> Projection t x -> Rec t x Source #

anyToTypedProjM :: forall m t x. (Monad m, HasProj x t, Typeable x, Typeable t) => (AnyProj t -> m (AnyRec t)) -> Projection t x -> m (Rec t x) Source #

Internal helpers

data LblProxy t Source #

Constructors

LblProxy 

Instances

class ReadRec label eq r v | label r -> v where Source #

Minimal complete definition

projVal'

Methods

projVal' :: LblProxy label -> p eq -> r -> v Source #

Instances

((~) * (RecValTy label t ((:) Symbol key more)) v, ReadRec label (IsEqLabel key label) (Rec t ((:) Symbol key more)) v) => ReadRec label False (Rec t ((:) Symbol l1 ((:) Symbol key more))) v Source # 

Methods

projVal' :: LblProxy label -> p False -> Rec t ((Symbol ': l1) ((Symbol ': key) more)) -> v Source #

(~) * (ProjTy key t) v => ReadRec label True (Rec t ((:) Symbol key more)) v Source # 

Methods

projVal' :: LblProxy label -> p True -> Rec t ((Symbol ': key) more) -> v Source #

type family RecValTy label (t :: *) (lbls :: [Symbol]) where ... Source #

Equations

RecValTy label t lbls = RecValTyH label lbls (RecTys t lbls) 

type family IsEqLabel (label :: Symbol) (label2 :: Symbol) = (r :: Bool) where ... Source #

Equations

IsEqLabel l l = True 
IsEqLabel l l2 = False 

data Rec t labels where Source #

Constructors

RNil :: Rec t '[] 
RCons :: KnownSymbol s => LblProxy s -> ProjTy s t -> Rec t ss -> Rec t (s ': ss) 

Instances

((~) * (RecValTy label t ((:) Symbol key more)) v, ReadRec label (IsEqLabel key label) (Rec t ((:) Symbol key more)) v) => ReadRec label False (Rec t ((:) Symbol l1 ((:) Symbol key more))) v Source # 

Methods

projVal' :: LblProxy label -> p False -> Rec t ((Symbol ': l1) ((Symbol ': key) more)) -> v Source #

(~) * (ProjTy key t) v => ReadRec label True (Rec t ((:) Symbol key more)) v Source # 

Methods

projVal' :: LblProxy label -> p True -> Rec t ((Symbol ': key) more) -> v Source #

(Eq (Rec t ls), Eq (ProjTy l t)) => Eq (Rec t ((:) Symbol l ls)) Source # 

Methods

(==) :: Rec t ((Symbol ': l) ls) -> Rec t ((Symbol ': l) ls) -> Bool #

(/=) :: Rec t ((Symbol ': l) ls) -> Rec t ((Symbol ': l) ls) -> Bool #

Eq (Rec c ([] Symbol)) Source # 

Methods

(==) :: Rec c [Symbol] -> Rec c [Symbol] -> Bool #

(/=) :: Rec c [Symbol] -> Rec c [Symbol] -> Bool #

(Show (ProjTy l t), Show (Rec t ls)) => Show (Rec t ((:) Symbol l ls)) Source # 

Methods

showsPrec :: Int -> Rec t ((Symbol ': l) ls) -> ShowS #

show :: Rec t ((Symbol ': l) ls) -> String #

showList :: [Rec t ((Symbol ': l) ls)] -> ShowS #

Show (Rec c ([] Symbol)) Source # 

Methods

showsPrec :: Int -> Rec c [Symbol] -> ShowS #

show :: Rec c [Symbol] -> String #

showList :: [Rec c [Symbol]] -> ShowS #