Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class GSchema be db (anns :: [Annotation]) (x :: * -> *) where
- gSchema :: AnnotatedDatabaseSettings be db -> Proxy anns -> x p -> Schema
- class GTables be db (anns :: [Annotation]) (x :: * -> *) where
- gTables :: AnnotatedDatabaseSettings be db -> Proxy anns -> x p -> (Tables, Sequences)
- class GTableEntry (be :: *) (db :: DatabaseKind) (anns :: [Annotation]) (tableFound :: Bool) (x :: * -> *) where
- gTableEntries :: AnnotatedDatabaseSettings be db -> Proxy anns -> Proxy tableFound -> x p -> ([(TableName, Table)], Sequences)
- class GTable be db (x :: * -> *) where
- gTable :: AnnotatedDatabaseSettings be db -> x p -> Table
- class GEnums be db x where
- gEnums :: AnnotatedDatabaseSettings be db -> x p -> Enumerations
- data GenSequencesForSerial
- class GColumns (genSeqs :: GenSequencesForSerial) (x :: * -> *) where
- class GTableConstraintColumns be db x where
- gTableConstraintsColumns :: AnnotatedDatabaseSettings be db -> TableName -> x p -> Set TableConstraint
- mkTableEntryNoFkDiscovery :: (GColumns GenSequences (Rep (TableSchema tbl)), Generic (TableSchema tbl), Table tbl) => AnnotatedDatabaseEntity be db (TableEntity tbl) -> ((TableName, Table), Sequences)
- mkTableEntryFkDiscovery :: (GColumns GenSequences (Rep (TableSchema tbl)), Generic (TableSchema tbl), Table tbl, GTableConstraintColumns be db (Rep (TableSchema tbl))) => AnnotatedDatabaseSettings be db -> AnnotatedDatabaseEntity be db (TableEntity tbl) -> ((TableName, Table), Sequences)
- gColumnsPK :: TableName -> S1 m (K1 R (TableFieldSchema tbl ty)) p -> (Columns, Sequences)
- class GTableLookupSettings (sel :: Maybe Symbol) (tbl :: TableKind) x where
- gTableLookupSettings :: Proxy sel -> Proxy tbl -> x p -> (TableName, [ColumnName])
- class GTableLookupTables (sel :: Maybe Symbol) (tbl :: TableKind) (x :: Type -> Type) (k :: Type -> Type) where
- gTableLookupTables :: Proxy sel -> Proxy tbl -> x p -> k p -> (TableName, [ColumnName])
- class GTableLookupTablesExpectFail (sel :: Maybe Symbol) (tbl :: TableKind) (x :: Type -> Type) (k :: Type -> Type) where
- gTableLookupTablesExpectFail :: Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> x p -> k p -> (TableName, [ColumnName])
- type family TestTableEqual (tbl1 :: TableKind) (tbl2 :: TableKind) :: Bool where ...
- class GTableLookupTable (b :: Bool) (sel :: Maybe Symbol) (tbl :: TableKind) (k :: Type -> Type) where
- gTableLookupTable :: Proxy b -> Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> k p -> (TableName, [ColumnName])
- class GTableLookupTableExpectFail (b :: Bool) (sel :: Maybe Symbol) (tbl :: TableKind) (k :: Type -> Type) where
- gTableLookupTableExpectFail :: Proxy b -> Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> k p -> (TableName, [ColumnName])
- 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`."
- 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."
- type family ShowField (sel :: Maybe Symbol) :: ErrorMessage where ...
Documentation
class GSchema be db (anns :: [Annotation]) (x :: * -> *) where Source #
Instances
(Constructor f, GTables be db anns x, GEnums be db x) => GSchema be db anns (C1 f x) Source # | |
Defined in Database.Beam.AutoMigrate.Generic | |
GSchema be db anns x => GSchema be db anns (D1 f x) Source # | |
Defined in Database.Beam.AutoMigrate.Generic |
class GTables be db (anns :: [Annotation]) (x :: * -> *) where Source #
Instances
(GTables be db anns a, GTables be db anns b) => GTables be db anns (a :*: b) Source # | |
Defined in Database.Beam.AutoMigrate.Generic | |
GTableEntry be db anns False (S1 f x) => GTables be db anns (S1 f x) Source # | |
Defined in Database.Beam.AutoMigrate.Generic |
class GTableEntry (be :: *) (db :: DatabaseKind) (anns :: [Annotation]) (tableFound :: Bool) (x :: * -> *) where Source #
gTableEntries :: AnnotatedDatabaseSettings be db -> Proxy anns -> Proxy tableFound -> x p -> ([(TableName, Table)], Sequences) Source #
Instances
class GTable be db (x :: * -> *) where Source #
gTable :: AnnotatedDatabaseSettings be db -> x p -> Table Source #
class GEnums be db x where Source #
gEnums :: AnnotatedDatabaseSettings be db -> x p -> Enumerations Source #
Instances
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 #
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 # | |
(GColumns p (Rep (sub f)), Generic (sub f)) => GColumns p (S1 m (K1 R (sub f) :: Type -> Type)) Source # | |
(GColumns p a, GColumns p b) => GColumns p (a :*: b) Source # | |
GColumns gseq x => GColumns gseq (C1 f x) Source # | |
GColumns gseq x => GColumns gseq (D1 f x) Source # | |
HasCompanionSequence ty => GColumns GenSequences (S1 m (K1 R (TableFieldSchema tbl ty) :: Type -> Type)) Source # | |
Defined in Database.Beam.AutoMigrate.Generic | |
GColumns NoGenSequences (S1 m (K1 R (TableFieldSchema tbl ty) :: Type -> Type)) Source # | |
Defined in Database.Beam.AutoMigrate.Generic |
class GTableConstraintColumns be db x where Source #
gTableConstraintsColumns :: AnnotatedDatabaseSettings be db -> TableName -> x p -> Set TableConstraint Source #
Instances
mkTableEntryNoFkDiscovery :: (GColumns GenSequences (Rep (TableSchema tbl)), Generic (TableSchema tbl), Table tbl) => AnnotatedDatabaseEntity be db (TableEntity tbl) -> ((TableName, Table), Sequences) Source #
mkTableEntryFkDiscovery :: (GColumns GenSequences (Rep (TableSchema tbl)), Generic (TableSchema tbl), Table tbl, GTableConstraintColumns be db (Rep (TableSchema tbl))) => AnnotatedDatabaseSettings be db -> AnnotatedDatabaseEntity be db (TableEntity tbl) -> ((TableName, Table), Sequences) Source #
gColumnsPK :: TableName -> S1 m (K1 R (TableFieldSchema tbl ty)) p -> (Columns, Sequences) Source #
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.
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 # | |
Defined in Database.Beam.AutoMigrate.Generic 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 # | |
Defined in Database.Beam.AutoMigrate.Generic 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 :*:
.
gTableLookupTables :: Proxy sel -> Proxy tbl -> x p -> k p -> (TableName, [ColumnName]) Source #
Instances
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.
gTableLookupTablesExpectFail :: Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> x p -> k p -> (TableName, [ColumnName]) Source #
Instances
type family TestTableEqual (tbl1 :: TableKind) (tbl2 :: TableKind) :: Bool where ... Source #
TestTableEqual tbl tbl = True | |
TestTableEqual _ _ = False |
class GTableLookupTable (b :: Bool) (sel :: Maybe Symbol) (tbl :: TableKind) (k :: Type -> Type) where Source #
gTableLookupTable :: Proxy b -> Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> k p -> (TableName, [ColumnName]) Source #
Instances
class GTableLookupTableExpectFail (b :: Bool) (sel :: Maybe Symbol) (tbl :: TableKind) (k :: Type -> Type) where Source #
gTableLookupTableExpectFail :: Proxy b -> Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> k p -> (TableName, [ColumnName]) Source #
Instances
(TypeError (LookupAmbiguous sel tbl) :: Constraint) => GTableLookupTableExpectFail True sel tbl k Source # | |
Defined in Database.Beam.AutoMigrate.Generic gTableLookupTableExpectFail :: Proxy True -> Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> k p -> (TableName, [ColumnName]) Source # | |
GTableLookupTableExpectFail False sel tbl (U1 :: Type -> Type) Source # | |
Defined in Database.Beam.AutoMigrate.Generic gTableLookupTableExpectFail :: Proxy False -> Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> U1 p -> (TableName, [ColumnName]) Source # | |
GTableLookupTablesExpectFail sel tbl k ks => GTableLookupTableExpectFail False sel tbl (k :*: ks) Source # | |
Defined in Database.Beam.AutoMigrate.Generic gTableLookupTableExpectFail :: Proxy False -> Proxy sel -> Proxy tbl -> (TableName, [ColumnName]) -> (k :*: ks) 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 #