data-basic-0.3.0.0: A database library with a focus on ease of use, type safety and useful error messages

Safe HaskellNone
LanguageHaskell2010

Internal.Data.Basic.Foreign

Documentation

class ForeignKeyConstraint fk => ForeignKeyFieldsMatch (fk :: Symbol) (fromFields :: [Symbol]) (toFields :: [Symbol]) where Source #

Minimal complete definition

foreignKeyFieldsMatch, foreignKeyFieldsSet

Instances

((~) * from (ForeignKeyFrom fk), (~) * to (ForeignKeyTo fk), TableField to toField, TableField from fromField, (~) * (TableFieldType to toField) (TableFieldType from fromField), ToField (TableFieldType from fromField), Ord (TableFieldType to toField), ForeignKeyFieldsMatch fk ((:) Symbol f1 f1s) ((:) Symbol f2 f2s), (~) ExpressionKind (KindOfDbExp (TableFieldType from fromField)) LiteralExp) => ForeignKeyFieldsMatch fk ((:) Symbol fromField ((:) Symbol f1 f1s)) ((:) Symbol toField ((:) Symbol f2 f2s)) Source # 
(ForeignKeyConstraint fk, (~) * from (ForeignKeyFrom fk), (~) * to (ForeignKeyTo fk), TableField to toField, TableField from fromField, (~) * (TableFieldType to toField) (TableFieldType from fromField), ToField (TableFieldType from fromField), Ord (TableFieldType to toField), (~) ExpressionKind (KindOfDbExp (TableFieldType from fromField)) LiteralExp) => ForeignKeyFieldsMatch fk ((:) Symbol fromField ([] Symbol)) ((:) Symbol toField ([] Symbol)) Source # 

foreignKeyLensGet :: forall fk m proxy. ForeignKeyLensGet fk m => proxy fk -> Getter' (Entity (FromDb Live) (ForeignKeyFrom fk)) (m (Entity (FromDb Live) (ForeignKeyTo fk))) Source #

foreignKeyLensSet :: forall fk entKind c proxy. ForeignKeyLensSet fk => proxy fk -> PolyOptic Identity (Entity entKind (ForeignKeyFrom fk)) (Entity (WithFieldsSet (ForeignKeyFromFields fk) entKind) (ForeignKeyFrom fk)) () (Entity (FromDb c) (ForeignKeyTo fk)) Source #

class ForeignKeyLensProxy t where Source #

Minimal complete definition

foreignKeyLensProxy

Instances

((ForeignKeyConstraint fk, ForeignKeyFieldsMatch fk (ForeignKeyFromFields fk) (ForeignKeyToFields fk)), (~) * t4 (Entity entKind (ForeignKeyFrom fk) -> Identity (Entity (WithFieldsSet (ForeignKeyFromFields fk) entKind) (ForeignKeyFrom fk))), (~) * t3 (Entity (FromDb c) (ForeignKeyTo fk)), (~) (* -> *) t2 ((->) LiftedRep LiftedRep ()), (~) (* -> * -> *) t1 ((->) LiftedRep LiftedRep), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy fk))) => ForeignKeyLensProxy (t0 (t1 (t2 (Identity t3)) t4)) Source # 

Methods

foreignKeyLensProxy :: t0 (t1 (t2 (Identity t3)) t4) Source #

((ForeignKeyConstraint fk, ForeignKeyFieldsMatch fk (ForeignKeyFromFields fk) (ForeignKeyToFields fk)), (~) * t3 (Entity (WithFieldsSet (ForeignKeyFromFields fk) entKind) (ForeignKeyFrom fk)), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (Entity entKind (ForeignKeyFrom fk))), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (() -> Identity (Entity (FromDb c) (ForeignKeyTo fk)))), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy fk))) => ForeignKeyLensProxy (t0 (t1 (t2 (Identity t3)))) Source # 

Methods

foreignKeyLensProxy :: t0 (t1 (t2 (Identity t3))) Source #

((ForeignKeyConstraint fk, MonadEffect Basic m, Table (ForeignKeyFrom fk), Table (ForeignKeyTo fk), ForeignKeyFieldsMatch fk (ForeignKeyFromFields fk) (ForeignKeyToFields fk)), (~) * t6 (Entity (FromDb Live) (ForeignKeyFrom fk) -> Const * (m (Entity (FromDb Live) (ForeignKeyTo fk))) (Entity (FromDb Live) (ForeignKeyFrom fk))), (~) * t5 (m (Entity (FromDb Live) (ForeignKeyTo fk))), (~) * t4 (m (Entity (FromDb Live) (ForeignKeyTo fk))), (~) (* -> * -> *) t3 (Const *), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (m (Entity (FromDb Live) (ForeignKeyTo fk)))), (~) (* -> * -> *) t1 ((->) LiftedRep LiftedRep), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy fk))) => ForeignKeyLensProxy (t0 (t1 (t2 (t3 t4 t5)) t6)) Source # 

Methods

foreignKeyLensProxy :: t0 (t1 (t2 (t3 t4 t5)) t6) Source #

((ForeignKeyConstraint fk, MonadEffect Basic m, Table (ForeignKeyFrom fk), Table (ForeignKeyTo fk), ForeignKeyFieldsMatch fk (ForeignKeyFromFields fk) (ForeignKeyToFields fk)), (~) * t5 (Entity (FromDb Live) (ForeignKeyFrom fk)), (~) * t4 (m (Entity (FromDb Live) (ForeignKeyTo fk))), (~) (* -> * -> *) t3 (Const *), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (Entity (FromDb Live) (ForeignKeyFrom fk))), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (m (Entity (FromDb Live) (ForeignKeyTo fk)) -> Const * (m (Entity (FromDb Live) (ForeignKeyTo fk))) (m (Entity (FromDb Live) (ForeignKeyTo fk))))), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy fk))) => ForeignKeyLensProxy (t0 (t1 (t2 (t3 t4 t5)))) Source # 

Methods

foreignKeyLensProxy :: t0 (t1 (t2 (t3 t4 t5))) Source #

foreignKeyLens :: forall name o. ForeignKeyLensProxy (Proxy name -> o) => o Source #