data-basic-0.2.0.2: 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 fromFields toFields 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 fk0, ForeignKeyFieldsMatch fk0 (ForeignKeyFromFields fk0) (ForeignKeyToFields fk0)), (~) * t4 (Entity entKind0 (ForeignKeyFrom fk0) -> Identity (Entity (WithFieldsSet (ForeignKeyFromFields fk0) entKind0) (ForeignKeyFrom fk0))), (~) * t3 (Entity (FromDb c0) (ForeignKeyTo fk0)), (~) (* -> *) t2 ((->) ()), (~) (* -> * -> *) t1 (->), (~) (* -> *) t0 ((->) (proxy0 fk0))) => ForeignKeyLensProxy (t0 (t1 (t2 (Identity t3)) t4)) Source # 

Methods

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

((ForeignKeyConstraint fk0, ForeignKeyFieldsMatch fk0 (ForeignKeyFromFields fk0) (ForeignKeyToFields fk0)), (~) * t3 (Entity (WithFieldsSet (ForeignKeyFromFields fk0) entKind0) (ForeignKeyFrom fk0)), (~) (* -> *) t2 ((->) (Entity entKind0 (ForeignKeyFrom fk0))), (~) (* -> *) t1 ((->) (() -> Identity (Entity (FromDb c0) (ForeignKeyTo fk0)))), (~) (* -> *) t0 ((->) (proxy0 fk0))) => ForeignKeyLensProxy (t0 (t1 (t2 (Identity t3)))) Source # 

Methods

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

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

Methods

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

((ForeignKeyConstraint fk0, MonadEffect Basic m0, Table (ForeignKeyFrom fk0), Table (ForeignKeyTo fk0), ForeignKeyFieldsMatch fk0 (ForeignKeyFromFields fk0) (ForeignKeyToFields fk0)), (~) * t5 (Entity (FromDb Live) (ForeignKeyFrom fk0)), (~) * t4 (m0 (Entity (FromDb Live) (ForeignKeyTo fk0))), (~) (* -> * -> *) t3 (Const *), (~) (* -> *) t2 ((->) (Entity (FromDb Live) (ForeignKeyFrom fk0))), (~) (* -> *) t1 ((->) (m0 (Entity (FromDb Live) (ForeignKeyTo fk0)) -> Const * (m0 (Entity (FromDb Live) (ForeignKeyTo fk0))) (m0 (Entity (FromDb Live) (ForeignKeyTo fk0))))), (~) (* -> *) t0 ((->) (proxy0 fk0))) => 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 #