beam-automigrate-0.1.2.0: DB migration library for beam, targeting Postgres.

Safe HaskellNone
LanguageHaskell2010

Database.Beam.AutoMigrate.Generic

Synopsis

Documentation

class GSchema be db (anns :: [Annotation]) (x :: * -> *) where Source #

Methods

gSchema :: AnnotatedDatabaseSettings be db -> Proxy anns -> x p -> Schema Source #

Instances
(Constructor f, GTables be db anns x, GEnums be db x) => GSchema be db anns (C1 f x) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gSchema :: AnnotatedDatabaseSettings be db -> Proxy anns -> C1 f x p -> Schema Source #

GSchema be db anns x => GSchema be db anns (D1 f x) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gSchema :: AnnotatedDatabaseSettings be db -> Proxy anns -> D1 f x p -> Schema Source #

class GTables be db (anns :: [Annotation]) (x :: * -> *) where Source #

Methods

gTables :: AnnotatedDatabaseSettings be db -> Proxy anns -> x p -> (Tables, Sequences) Source #

Instances
(GTables be db anns a, GTables be db anns b) => GTables be db anns (a :*: b) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTables :: AnnotatedDatabaseSettings be db -> Proxy anns -> (a :*: b) p -> (Tables, Sequences) Source #

GTableEntry be db anns False (S1 f x) => GTables be db anns (S1 f x) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTables :: AnnotatedDatabaseSettings be db -> Proxy anns -> S1 f x p -> (Tables, Sequences) Source #

class GTableEntry (be :: *) (db :: DatabaseKind) (anns :: [Annotation]) (tableFound :: Bool) (x :: * -> *) where Source #

Methods

gTableEntries :: AnnotatedDatabaseSettings be db -> Proxy anns -> Proxy tableFound -> x p -> ([(TableName, Table)], Sequences) Source #

Instances
(GTableEntry be outerDB xs found a, GTableEntry be outerDB xs found b) => GTableEntry be outerDB xs found (a :*: b) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableEntries :: AnnotatedDatabaseSettings be outerDB -> Proxy xs -> Proxy found -> (a :*: b) p -> ([(TableName, Table)], Sequences) Source #

GTableEntry be outerDB xs found x => GTableEntry be outerDB xs found (C1 f x) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableEntries :: AnnotatedDatabaseSettings be outerDB -> Proxy xs -> Proxy found -> C1 f x p -> ([(TableName, Table)], Sequences) Source #

GTableEntry be outerDB xs found x => GTableEntry be outerDB xs found (D1 f x) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableEntries :: AnnotatedDatabaseSettings be outerDB -> Proxy xs -> Proxy found -> D1 f x p -> ([(TableName, Table)], Sequences) Source #

(Generic (innerDB (AnnotatedDatabaseEntity be outerDB)), Database be innerDB, GTableEntry be outerDB xs found (Rep (innerDB (AnnotatedDatabaseEntity be outerDB)))) => GTableEntry be outerDB xs found (K1 R (innerDB (AnnotatedDatabaseEntity be outerDB)) :: Type -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableEntries :: AnnotatedDatabaseSettings be outerDB -> Proxy xs -> Proxy found -> K1 R (innerDB (AnnotatedDatabaseEntity be outerDB)) p -> ([(TableName, Table)], Sequences) Source #

GTableEntry be db anns tableFound x => GTableEntry be db anns tableFound (S1 f x) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableEntries :: AnnotatedDatabaseSettings be db -> Proxy anns -> Proxy tableFound -> S1 f x p -> ([(TableName, Table)], Sequences) Source #

(IsAnnotatedDatabaseEntity be (TableEntity tbl), GColumns GenSequences (Rep (TableSchema tbl)), Generic (TableSchema tbl), Table tbl, GTableConstraintColumns be db (Rep (TableSchema tbl))) => GTableEntry be db ([] :: [Annotation]) False (K1 R (AnnotatedDatabaseEntity be db (TableEntity tbl)) :: Type -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

(IsAnnotatedDatabaseEntity be (TableEntity tbl), GColumns GenSequences (Rep (TableSchema tbl)), Generic (TableSchema tbl), Table tbl) => GTableEntry be db ([] :: [Annotation]) True (K1 R (AnnotatedDatabaseEntity be db (TableEntity tbl)) :: Type -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

(GColumns GenSequences (Rep (TableSchema tbl)), Generic (TableSchema tbl), Table tbl) => GTableEntry be db (UserDefinedFk tbl' ': xs) True (K1 R (AnnotatedDatabaseEntity be db (TableEntity tbl)) :: Type -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

(GColumns GenSequences (Rep (TableSchema tbl)), Generic (TableSchema tbl), Table tbl, GTableEntry be db xs (TestTableEqual tbl tbl') (K1 R (AnnotatedDatabaseEntity be db (TableEntity tbl)) :: Type -> Type)) => GTableEntry be db (UserDefinedFk tbl' ': xs) False (K1 R (AnnotatedDatabaseEntity be db (TableEntity tbl)) :: Type -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

class GTable be db (x :: * -> *) where Source #

Methods

gTable :: AnnotatedDatabaseSettings be db -> x p -> Table Source #

class GEnums be db x where Source #

Instances
GEnums be db (S1 f (K1 R (PrimaryKey tbl1 (g (TableFieldSchema tbl2))) :: k -> Type) :: k -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gEnums :: AnnotatedDatabaseSettings be db -> S1 f (K1 R (PrimaryKey tbl1 (g (TableFieldSchema tbl2)))) p -> Enumerations Source #

GEnums be db (S1 f (K1 R (PrimaryKey tbl1 (TableFieldSchema tbl2)) :: k -> Type) :: k -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

HasColumnType ty => GEnums be db (S1 f (K1 R (TableFieldSchema tbl ty) :: k -> Type) :: k -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

(GEnums be db (Rep (sub f)), Generic (sub f)) => GEnums be db (S1 m (K1 R (sub f) :: k1 -> Type) :: k1 -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gEnums :: AnnotatedDatabaseSettings be db -> S1 m (K1 R (sub f)) p -> Enumerations Source #

(IsAnnotatedDatabaseEntity be (TableEntity tbl), Table tbl, GEnums be db (Rep (TableSchema tbl)), Generic (TableSchema tbl)) => GEnums be db (S1 f (K1 R (AnnotatedDatabaseEntity be db (TableEntity tbl)) :: k -> Type) :: k -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

(GEnums be db a, GEnums be db b) => GEnums be db (a :*: b :: k -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

GEnums be db x => GEnums be db (C1 f x :: k -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

GEnums be db x => GEnums be db (D1 f x :: k -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

data GenSequencesForSerial Source #

Type-level witness of whether or not we have to generate an extra "SEQUENCE" in case the table field is a SqlSerial.

class GColumns (genSeqs :: GenSequencesForSerial) (x :: * -> *) where Source #

Methods

gColumns :: Proxy genSeqs -> TableName -> x p -> (Columns, Sequences) Source #

Instances
(GColumns NoGenSequences (Rep (PrimaryKey tbl f)), Generic (PrimaryKey tbl f), Beamable (PrimaryKey tbl)) => GColumns x (S1 m (K1 R (PrimaryKey tbl f) :: Type -> Type)) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gColumns :: Proxy x -> TableName -> S1 m (K1 R (PrimaryKey tbl f)) p -> (Columns, Sequences) Source #

(GColumns p (Rep (sub f)), Generic (sub f)) => GColumns p (S1 m (K1 R (sub f) :: Type -> Type)) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gColumns :: Proxy p -> TableName -> S1 m (K1 R (sub f)) p0 -> (Columns, Sequences) Source #

(GColumns p a, GColumns p b) => GColumns p (a :*: b) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gColumns :: Proxy p -> TableName -> (a :*: b) p0 -> (Columns, Sequences) Source #

GColumns gseq x => GColumns gseq (C1 f x) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gColumns :: Proxy gseq -> TableName -> C1 f x p -> (Columns, Sequences) Source #

GColumns gseq x => GColumns gseq (D1 f x) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gColumns :: Proxy gseq -> TableName -> D1 f x p -> (Columns, Sequences) Source #

HasCompanionSequence ty => GColumns GenSequences (S1 m (K1 R (TableFieldSchema tbl ty) :: Type -> Type)) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

GColumns NoGenSequences (S1 m (K1 R (TableFieldSchema tbl ty) :: Type -> Type)) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

class GTableConstraintColumns be db x where Source #

Instances
(Generic (AnnotatedDatabaseSettings be db), Generic (sub f), GColumns GenSequences (Rep (sub f)), GTableConstraintColumns be db (Rep (sub f))) => GTableConstraintColumns be db (S1 m (K1 R (sub f) :: k1 -> Type) :: k1 -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

GTableConstraintColumns be db (S1 m (K1 R (TableFieldSchema tbl ty) :: k -> Type) :: k -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

(GTableConstraintColumns be db a, GTableConstraintColumns be db b) => GTableConstraintColumns be db (a :*: b :: k -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

GTableConstraintColumns be db x => GTableConstraintColumns be db (C1 f x :: k -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

GTableConstraintColumns be db x => GTableConstraintColumns be db (D1 f x :: k -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

(Generic (AnnotatedDatabaseSettings be db), Generic (PrimaryKey tbl f), GColumns NoGenSequences (Rep (PrimaryKey tbl f)), GTableLookupSettings sel tbl (Rep (AnnotatedDatabaseSettings be db)), m ~ MetaSel sel su ss ds) => GTableConstraintColumns be db (S1 m (K1 R (PrimaryKey tbl f) :: k -> Type) :: k -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

class GTableLookupSettings (sel :: Maybe Symbol) (tbl :: TableKind) x where Source #

Lookup a table by type in the given DB settings.

The selector name is only provided for error messages.

Only returns if the table type is unique. Returns the table name and the column names of its primary key.

Methods

gTableLookupSettings :: Proxy sel -> Proxy tbl -> x p -> (TableName, [ColumnName]) Source #

Instances
GTableLookupTables sel tbl x (U1 :: Type -> Type) => GTableLookupSettings sel tbl (C1 f x :: Type -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableLookupSettings :: Proxy sel -> Proxy tbl -> C1 f x p -> (TableName, [ColumnName]) Source #

GTableLookupSettings sel tbl x => GTableLookupSettings sel tbl (D1 f x :: k -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableLookupSettings :: Proxy sel -> Proxy tbl -> D1 f x p -> (TableName, [ColumnName]) Source #

class GTableLookupTables (sel :: Maybe Symbol) (tbl :: TableKind) (x :: Type -> Type) (k :: Type -> Type) where Source #

Helper class that takes an additional continuation parameter k.

We treat k as a type-level stack with U1 being the empty stack and :*: used right-associatively to place items onto the stack.

The reason we do not use a type-level list here is that we also need a term-level representation of the continuation, and we already have suitable inhabitants for U1 and :*:.

Methods

gTableLookupTables :: Proxy sel -> Proxy tbl -> x p -> k p -> (TableName, [ColumnName]) Source #

Instances
GTableLookupTables sel tbl x k => GTableLookupTables sel tbl (C1 f x) k Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableLookupTables :: Proxy sel -> Proxy tbl -> C1 f x p -> k p -> (TableName, [ColumnName]) Source #

GTableLookupTables sel tbl x k => GTableLookupTables sel tbl (D1 f x) k Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableLookupTables :: Proxy sel -> Proxy tbl -> D1 f x p -> k p -> (TableName, [ColumnName]) Source #

(GTableLookupTables sel tbl (Rep (innerDB (AnnotatedDatabaseEntity be outerDB))) k, Database be innerDB, Generic (innerDB (AnnotatedDatabaseEntity be outerDB))) => GTableLookupTables sel tbl (K1 R (innerDB (AnnotatedDatabaseEntity be outerDB)) :: Type -> Type) k Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableLookupTables :: Proxy sel -> Proxy tbl -> K1 R (innerDB (AnnotatedDatabaseEntity be outerDB)) p -> k p -> (TableName, [ColumnName]) Source #

(GTableLookupTable (TestTableEqual tbl tbl') sel tbl k, Beamable tbl', Table tbl') => GTableLookupTables sel tbl (K1 R (AnnotatedDatabaseEntity be db (TableEntity tbl')) :: Type -> Type) k Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableLookupTables :: Proxy sel -> Proxy tbl -> K1 R (AnnotatedDatabaseEntity be db (TableEntity tbl')) p -> k p -> (TableName, [ColumnName]) Source #

GTableLookupTables sel tbl a (b :*: k) => GTableLookupTables sel tbl (a :*: b) k Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableLookupTables :: Proxy sel -> Proxy tbl -> (a :*: b) p -> k p -> (TableName, [ColumnName]) Source #

GTableLookupTables sel tbl x k => GTableLookupTables sel tbl (S1 f x) k Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableLookupTables :: Proxy sel -> Proxy tbl -> S1 f x p -> k p -> (TableName, [ColumnName]) Source #

class GTableLookupTablesExpectFail (sel :: Maybe Symbol) (tbl :: TableKind) (x :: Type -> Type) (k :: Type -> Type) where Source #

We use this function to continue searching once we've already found a match, and to abort if we find a second match.

Methods

gTableLookupTablesExpectFail :: Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> x p -> k p -> (TableName, [ColumnName]) Source #

Instances
GTableLookupTablesExpectFail sel tbl x k => GTableLookupTablesExpectFail sel tbl (C1 f x) k Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableLookupTablesExpectFail :: Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> C1 f x p -> k p -> (TableName, [ColumnName]) Source #

GTableLookupTablesExpectFail sel tbl x k => GTableLookupTablesExpectFail sel tbl (D1 f x) k Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableLookupTablesExpectFail :: Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> D1 f x p -> k p -> (TableName, [ColumnName]) Source #

(GTableLookupTablesExpectFail sel tbl (Rep (innerDb (AnnotatedDatabaseEntity be outerDb))) k, Generic (innerDb (AnnotatedDatabaseEntity be outerDb)), Database be innerDb) => GTableLookupTablesExpectFail sel tbl (K1 R (innerDb (AnnotatedDatabaseEntity be outerDb)) :: Type -> Type) k Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableLookupTablesExpectFail :: Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> K1 R (innerDb (AnnotatedDatabaseEntity be outerDb)) p -> k p -> (TableName, [ColumnName]) Source #

(GTableLookupTableExpectFail (TestTableEqual tbl tbl') sel tbl k, Beamable tbl') => GTableLookupTablesExpectFail sel tbl (K1 R (AnnotatedDatabaseEntity be db (TableEntity tbl')) :: Type -> Type) k Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

GTableLookupTablesExpectFail sel tbl a (b :*: k) => GTableLookupTablesExpectFail sel tbl (a :*: b) k Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableLookupTablesExpectFail :: Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> (a :*: b) p -> k p -> (TableName, [ColumnName]) Source #

GTableLookupTablesExpectFail sel tbl x k => GTableLookupTablesExpectFail sel tbl (S1 f x) k Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableLookupTablesExpectFail :: Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> S1 f x p -> k p -> (TableName, [ColumnName]) Source #

type family TestTableEqual (tbl1 :: TableKind) (tbl2 :: TableKind) :: Bool where ... Source #

Equations

TestTableEqual tbl tbl = True 
TestTableEqual _ _ = False 

class GTableLookupTable (b :: Bool) (sel :: Maybe Symbol) (tbl :: TableKind) (k :: Type -> Type) where Source #

Methods

gTableLookupTable :: Proxy b -> Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> k p -> (TableName, [ColumnName]) Source #

Instances
(TypeError (LookupFailed sel tbl) :: Constraint) => GTableLookupTable False sel tbl (U1 :: Type -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableLookupTable :: Proxy False -> Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> U1 p -> (TableName, [ColumnName]) Source #

GTableLookupTable True sel tbl (U1 :: Type -> Type) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableLookupTable :: Proxy True -> Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> U1 p -> (TableName, [ColumnName]) Source #

GTableLookupTables sel tbl k ks => GTableLookupTable False sel tbl (k :*: ks) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableLookupTable :: Proxy False -> Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> (k :*: ks) p -> (TableName, [ColumnName]) Source #

GTableLookupTablesExpectFail sel tbl k ks => GTableLookupTable True sel tbl (k :*: ks) Source # 
Instance details

Defined in Database.Beam.AutoMigrate.Generic

Methods

gTableLookupTable :: Proxy True -> Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> (k :*: ks) p -> (TableName, [ColumnName]) Source #

class GTableLookupTableExpectFail (b :: Bool) (sel :: Maybe Symbol) (tbl :: TableKind) (k :: Type -> Type) where Source #

Methods

gTableLookupTableExpectFail :: Proxy b -> Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> k p -> (TableName, [ColumnName]) Source #

type LookupAmbiguous (sel :: Maybe Symbol) (tbl :: TableKind) = ((((((((((Text "Could not derive foreign key constraint for " :<>: ShowField sel) :<>: Text ",") :$$: ((Text "because there are several tables of type `" :<>: ShowType tbl) :<>: Text "' in the schema.")) :$$: Text "In this scenario you have to manually disable the FK-discovery algorithm for all the tables ") :$$: Text "hit by such ambiguity, for example by creating your Schema via: ") :$$: Text "") :$$: Text "fromAnnotatedDbSettings annotatedDB (Proxy @'[ 'UserDefinedFk TBL1, 'UserDefinedFk TBL2, .. ])") :$$: Text "") :$$: ((Text "Where `TBL1..n` are types referencing " :<>: ShowType tbl) :<>: Text " in the schema.")) :$$: Text "Once done that, you can explicitly provide manual FKs for the tables by using `foreignKeyOnPk` ") :$$: Text "when annotating your `DatabaseSettings`." Source #

type LookupFailed (sel :: Maybe Symbol) (tbl :: TableKind) = ((((((Text "Could not derive foreign key constraint for " :<>: ShowField sel) :<>: Text ",") :$$: ((Text "because there are no tables of type `" :<>: ShowType tbl) :<>: Text "' in the schema.")) :$$: ((Text "This might be because this particular " :<>: ShowField sel) :<>: Text " doesn't appear anywhere ")) :$$: Text "in your database, so the FK-discovery mechanism doesn't know how to reach it. Please note that ") :$$: Text "in presence of nested databases there might be more than one field with the same name referencing ") :$$: Text "different things. You might want to check you are adding or targeting the correct one." Source #

type family ShowField (sel :: Maybe Symbol) :: ErrorMessage where ... Source #

Equations

ShowField Nothing = Text "unnamed field" 
ShowField (Just sel) = (Text "field `" :<>: Text sel) :<>: Text "'"