Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides an AnnotatedDatabaseSettings
type to be used as a drop-in replacement for the
standard DatabaseSettings
. Is it possible to "downcast" an AnnotatedDatabaseSettings
to a standard
DatabaseSettings
simply by calling deAnnotateDatabase
.
Synopsis
- data Annotation where
- UserDefinedFk :: TableKind -> Annotation
- type AnnotatedDatabaseSettings be db = db (AnnotatedDatabaseEntity be db)
- data AnnotatedDatabaseEntity be (db :: (* -> *) -> *) entityType where
- AnnotatedDatabaseEntity :: (IsAnnotatedDatabaseEntity be entityType, IsDatabaseEntity be entityType) => AnnotatedDatabaseEntityDescriptor be entityType -> DatabaseEntity be db entityType -> AnnotatedDatabaseEntity be db entityType
- class IsDatabaseEntity be entityType => IsAnnotatedDatabaseEntity be entityType where
- data AnnotatedDatabaseEntityDescriptor be entityType :: *
- type AnnotatedDatabaseEntityDefaultRequirements be entityType :: Constraint
- type AnnotatedDatabaseEntityRegularRequirements be entityType :: Constraint
- dbAnnotatedEntityAuto :: AnnotatedDatabaseEntityRegularRequirements be entityType => DatabaseEntityDescriptor be entityType -> AnnotatedDatabaseEntityDescriptor be entityType
- type TableSchema tbl = tbl (TableFieldSchema tbl)
- data TableFieldSchema (tbl :: (* -> *) -> *) ty where
- TableFieldSchema :: {..} -> TableFieldSchema tbl ty
- data FieldSchema ty where
- FieldSchema :: ColumnType -> Set ColumnConstraint -> FieldSchema ty
- annotatedDescriptor :: SimpleGetter (AnnotatedDatabaseEntity be db entityType) (AnnotatedDatabaseEntityDescriptor be entityType)
- defaultTableSchema :: forall tbl. (GDefaultTableSchema (Rep (TableSchema tbl) ()) (Rep (TableSettings tbl) ()), Generic (TableSchema tbl), Generic (TableSettings tbl)) => TableSettings tbl -> TableSchema tbl
- lowerEntityDescriptor :: SimpleGetter (AnnotatedDatabaseEntity be db entityType) (DatabaseEntityDescriptor be entityType)
- deannotate :: SimpleGetter (AnnotatedDatabaseEntity be db entityType) (DatabaseEntity be db entityType)
- annotateTableFields :: tbl (FieldModification (TableFieldSchema tbl)) -> EntityModification (AnnotatedDatabaseEntity be db) be (TableEntity tbl)
- defaultsTo :: (HasColumnType ty, HasSqlValueSyntax PgValueSyntax ty) => (forall ctx s. QGenExpr ctx Postgres s ty) -> FieldModification (TableFieldSchema tbl) ty
- data UniqueConstraint (tbl :: (* -> *) -> *) where
- U :: HasColumnNames entity tbl => (tbl (TableField tbl) -> entity) -> UniqueConstraint tbl
- uniqueConstraintOn :: [UniqueConstraint tbl] -> EntityModification (AnnotatedDatabaseEntity be db) be (TableEntity tbl)
- data ForeignKeyConstraint (tbl :: (* -> *) -> *) (tbl' :: (* -> *) -> *) where
- References :: Beamable (PrimaryKey tbl') => (tbl (TableField tbl) -> PrimaryKey tbl' (TableField tbl)) -> (tbl' (TableField tbl') -> Columnar Identity (TableField tbl' ty)) -> ForeignKeyConstraint tbl tbl'
- foreignKeyOnPk :: (Beamable (PrimaryKey tbl'), Beamable tbl', Table tbl', PrimaryKey tbl' f ~ PrimaryKey tbl' g) => DatabaseEntity be db (TableEntity tbl') -> (tbl (TableField tbl) -> PrimaryKey tbl' (TableField tbl)) -> ReferenceAction -> ReferenceAction -> EntityModification (AnnotatedDatabaseEntity be db) be (TableEntity tbl)
- foreignKeyOn :: Beamable tbl' => DatabaseEntity be db (TableEntity tbl') -> [ForeignKeyConstraint tbl tbl'] -> ReferenceAction -> ReferenceAction -> EntityModification (AnnotatedDatabaseEntity be db) be (TableEntity tbl)
- type TableKind = (Type -> Type) -> Type
- type DatabaseKind = (Type -> Type) -> Type
- zipTables :: (Generic (db f), Generic (db g), Generic (db h), Monad m, GZipDatabase be f g h (Rep (db f)) (Rep (db g)) (Rep (db h))) => Proxy be -> (forall tbl. (IsAnnotatedDatabaseEntity be tbl, AnnotatedDatabaseEntityRegularRequirements be tbl) => f tbl -> g tbl -> m (h tbl)) -> db f -> db g -> m (db h)
- class GZipDatabase be f g h x y z
- pgDefaultConstraint :: forall ty. (HasColumnType ty, HasSqlValueSyntax PgValueSyntax ty) => (forall ctx s. QGenExpr ctx Postgres s ty) -> ColumnConstraint
User annotations
data Annotation where Source #
A user-defined annotation. Currently the only possible annotation is the ability to specify for which tables the FK-discovery algorithm is "turned" off.
UserDefinedFk :: TableKind -> Annotation | Specifies that the given Caveat emptor: Due to what we said earlier (namely that we cannot enforce that tables are not
repeated multiple times within a DB) there might be situations where also the specified |
Instances
Annotating a DatabaseSettings
type AnnotatedDatabaseSettings be db = db (AnnotatedDatabaseEntity be db) Source #
An AnnotatedDatabaseSettings
is similar in spirit to a beam-core
DatabaseSettings
, but it
embellish the latter with extra metadata this library can use to derive more information about the input
DB, like table and column constraints.
data AnnotatedDatabaseEntity be (db :: (* -> *) -> *) entityType where Source #
An AnnotatedDatabaseEntity
wraps the underlying DatabaseEntity
together with an annotated
description called AnnotatedDatabaseEntityDescriptor
, which is once again similar to the standard
DatabaseEntityDescriptor
from Beam.
An AnnotatedDatabaseEntityDescriptor
is not a concrete type, but rather a data family provided by the
IsAnnotatedDatabaseEntity
.
AnnotatedDatabaseEntity :: (IsAnnotatedDatabaseEntity be entityType, IsDatabaseEntity be entityType) => AnnotatedDatabaseEntityDescriptor be entityType -> DatabaseEntity be db entityType -> AnnotatedDatabaseEntity be db entityType |
Instances
class IsDatabaseEntity be entityType => IsAnnotatedDatabaseEntity be entityType where Source #
data AnnotatedDatabaseEntityDescriptor be entityType :: * Source #
type AnnotatedDatabaseEntityDefaultRequirements be entityType :: Constraint Source #
type AnnotatedDatabaseEntityRegularRequirements be entityType :: Constraint Source #
dbAnnotatedEntityAuto :: AnnotatedDatabaseEntityRegularRequirements be entityType => DatabaseEntityDescriptor be entityType -> AnnotatedDatabaseEntityDescriptor be entityType Source #
Instances
IsDatabaseEntity be (TableEntity tbl) => IsAnnotatedDatabaseEntity be (TableEntity tbl) Source # | |
Defined in Database.Beam.AutoMigrate.Annotated data AnnotatedDatabaseEntityDescriptor be (TableEntity tbl) :: Type Source # type AnnotatedDatabaseEntityDefaultRequirements be (TableEntity tbl) :: Constraint Source # type AnnotatedDatabaseEntityRegularRequirements be (TableEntity tbl) :: Constraint Source # dbAnnotatedEntityAuto :: DatabaseEntityDescriptor be (TableEntity tbl) -> AnnotatedDatabaseEntityDescriptor be (TableEntity tbl) Source # |
type TableSchema tbl = tbl (TableFieldSchema tbl) Source #
A table schema.
data TableFieldSchema (tbl :: (* -> *) -> *) ty where Source #
A schema for a field within a given table
TableFieldSchema | |
|
Instances
data FieldSchema ty where Source #
FieldSchema :: ColumnType -> Set ColumnConstraint -> FieldSchema ty |
Instances
Show (FieldSchema ty) Source # | |
Defined in Database.Beam.AutoMigrate.Annotated showsPrec :: Int -> FieldSchema ty -> ShowS # show :: FieldSchema ty -> String # showList :: [FieldSchema ty] -> ShowS # |
annotatedDescriptor :: SimpleGetter (AnnotatedDatabaseEntity be db entityType) (AnnotatedDatabaseEntityDescriptor be entityType) Source #
defaultTableSchema :: forall tbl. (GDefaultTableSchema (Rep (TableSchema tbl) ()) (Rep (TableSettings tbl) ()), Generic (TableSchema tbl), Generic (TableSettings tbl)) => TableSettings tbl -> TableSchema tbl Source #
Downcasting annotated types
lowerEntityDescriptor :: SimpleGetter (AnnotatedDatabaseEntity be db entityType) (DatabaseEntityDescriptor be entityType) Source #
A SimpleGetter
to get a plain DatabaseEntityDescriptor
from an AnnotatedDatabaseEntity
.
deannotate :: SimpleGetter (AnnotatedDatabaseEntity be db entityType) (DatabaseEntity be db entityType) Source #
Specifying constraints
Once an AnnotatedDatabaseSettings
has been acquired, the user is able to customise the default
medatata associated with it. In order to do so, one can reuse the existing machinery from Beam, in
particular the withDbModification
. For example:
annotatedDB :: AnnotatedDatabaseSettings Postgres FlowerDB annotatedDB = defaultAnnotatedDbSettings flowerDB `withDbModification` dbModification { dbFlowers = annotateTableFields tableModification { flowerDiscounted = defaultsTo (val_ $ Just True) , flowerPrice = defaultsTo (val_ $ Just 10.0) } <> uniqueFields [U (addressPostalCode . addressRegion . flowerAddress)] , dbLineItems = annotateTableFields tableModification { lineItemDiscount = defaultsTo (val_ $ Just False) } <> uniqueFields [U lineItemFlowerID, U lineItemOrderID, U lineItemQuantity] , dbOrders = annotateTableFields tableModification { orderTime = defaultsTo (cast_ currentTimestamp_ utctime) } <> foreignKeyOnPk (dbFlowers flowerDB) orderFlowerIdRef Cascade Restrict <> uniqueFields [U (addressPostalCode . addressRegion . orderAddress)] }
Refer to the rest of the documentation for this module for more information about annotateTableFields
,
uniqueFields
and foreignKeyOnPk
.
annotateTableFields :: tbl (FieldModification (TableFieldSchema tbl)) -> EntityModification (AnnotatedDatabaseEntity be db) be (TableEntity tbl) Source #
Annotate the table fields for a given AnnotatedDatabaseEntity
. Refer to the $specifyingConstraints
section for an example.
Specifying Column constraints
Due to the fact most column constraints can span multiple columns (think about UNIQUE
or
FOREIGN KEY
) the only constraint associated to a TableFieldSchema
we allow to customise at the
"single-column-granularity" is DEFAULT
.
defaultsTo :: (HasColumnType ty, HasSqlValueSyntax PgValueSyntax ty) => (forall ctx s. QGenExpr ctx Postgres s ty) -> FieldModification (TableFieldSchema tbl) ty Source #
Specify a default value for an entity. The relevant migration will generate an associated SQL
DEFAULT
. This function accepts any Beam's expression that also the standard field
machinery would
accept, for example:
defaultsTo (val_ $ Just 10)
Specifying Table constraints
Is it possible to annotate an AnnotatedDatabaseEntity
with UNIQUE
and FOREIGN KEY
constraints.
data UniqueConstraint (tbl :: (* -> *) -> *) where Source #
U :: HasColumnNames entity tbl => (tbl (TableField tbl) -> entity) -> UniqueConstraint tbl | Use this to "tag" a standard Beam |
Unique constraint
uniqueConstraintOn :: [UniqueConstraint tbl] -> EntityModification (AnnotatedDatabaseEntity be db) be (TableEntity tbl) Source #
Given a list of TableField
selectors wrapped in a UniqueConstraint
type constructor, it adds
to the relevant AnnotatedDatabaseEntity
a new UNIQUE
TableConstraint
composed by all the
fields specified. To put it differently, every call to uniqueConstraintOn
generates a separate
UNIQUE
constraint composed by the listed fields.
If a TableConstraint
is passed as input, it will desugar under the hood into as many columns as
the primary key refers to.
Foreign key constraint
data ForeignKeyConstraint (tbl :: (* -> *) -> *) (tbl' :: (* -> *) -> *) where Source #
References :: Beamable (PrimaryKey tbl') => (tbl (TableField tbl) -> PrimaryKey tbl' (TableField tbl)) -> (tbl' (TableField tbl') -> Columnar Identity (TableField tbl' ty)) -> ForeignKeyConstraint tbl tbl' |
:: (Beamable (PrimaryKey tbl'), Beamable tbl', Table tbl', PrimaryKey tbl' f ~ PrimaryKey tbl' g) | |
=> DatabaseEntity be db (TableEntity tbl') | The |
-> (tbl (TableField tbl) -> PrimaryKey tbl' (TableField tbl)) | A function yielding a |
-> ReferenceAction | What do to "on delete" |
-> ReferenceAction | What do to "on update" |
-> EntityModification (AnnotatedDatabaseEntity be db) be (TableEntity tbl) |
Special-case combinator to use when defining FK constraints referencing the primary key of the target table.
:: Beamable tbl' | |
=> DatabaseEntity be db (TableEntity tbl') | |
-> [ForeignKeyConstraint tbl tbl'] | |
-> ReferenceAction | On Delete |
-> ReferenceAction | On Update |
-> EntityModification (AnnotatedDatabaseEntity be db) be (TableEntity tbl) |
Other types and functions
Ports from Beam
zipTables :: (Generic (db f), Generic (db g), Generic (db h), Monad m, GZipDatabase be f g h (Rep (db f)) (Rep (db g)) (Rep (db h))) => Proxy be -> (forall tbl. (IsAnnotatedDatabaseEntity be tbl, AnnotatedDatabaseEntityRegularRequirements be tbl) => f tbl -> g tbl -> m (h tbl)) -> db f -> db g -> m (db h) Source #
Zip tables together. Unfortunately we cannot reuse the stock zipTables
from 'beam-core', because it
works by supplying a rank-2 function with IsDatabaseEntity
and DatabaseEntityRegularRequirements
as
witnesses, we we need the annotated counterparts instead.
This function can be written without the need of a typeclass, but alas it requires the unexported
GZipDatabase
from 'beam-core', so we had to re-implement this ourselves for now.
class GZipDatabase be f g h x y z Source #
See above on why this class has been re-implemented.
gZipDatabase
Instances
(Database be db, Generic (db f), Generic (db g), Generic (db h), GZipDatabase be f g h (Rep (db f)) (Rep (db g)) (Rep (db h))) => GZipDatabase be f g h (K1 R (db f) :: Type -> Type) (K1 R (db g) :: Type -> Type) (K1 R (db h) :: Type -> Type) Source # | |
Defined in Database.Beam.AutoMigrate.Annotated gZipDatabase :: Monad m => (Proxy f, Proxy g, Proxy h, Proxy be) -> (forall tbl. (IsAnnotatedDatabaseEntity be tbl, AnnotatedDatabaseEntityRegularRequirements be tbl) => f tbl -> g tbl -> m (h tbl)) -> K1 R (db f) () -> K1 R (db g) () -> m (K1 R (db h) ()) | |
(IsAnnotatedDatabaseEntity be tbl, AnnotatedDatabaseEntityRegularRequirements be tbl) => GZipDatabase be f g h (K1 R (f tbl) :: Type -> Type) (K1 R (g tbl) :: Type -> Type) (K1 R (h tbl) :: Type -> Type) Source # | |
Defined in Database.Beam.AutoMigrate.Annotated gZipDatabase :: Monad m => (Proxy f, Proxy g, Proxy h, Proxy be) -> (forall tbl0. (IsAnnotatedDatabaseEntity be tbl0, AnnotatedDatabaseEntityRegularRequirements be tbl0) => f tbl0 -> g tbl0 -> m (h tbl0)) -> K1 R (f tbl) () -> K1 R (g tbl) () -> m (K1 R (h tbl) ()) | |
(GZipDatabase be f g h ax ay az, GZipDatabase be f g h bx by bz) => GZipDatabase be f g h (ax :*: bx) (ay :*: by) (az :*: bz) Source # | |
Defined in Database.Beam.AutoMigrate.Annotated gZipDatabase :: Monad m => (Proxy f, Proxy g, Proxy h, Proxy be) -> (forall tbl. (IsAnnotatedDatabaseEntity be tbl, AnnotatedDatabaseEntityRegularRequirements be tbl) => f tbl -> g tbl -> m (h tbl)) -> (ax :*: bx) () -> (ay :*: by) () -> m ((az :*: bz) ()) | |
GZipDatabase be f g h x y z => GZipDatabase be f g h (M1 a b x) (M1 a b y) (M1 a b z) Source # | |
Defined in Database.Beam.AutoMigrate.Annotated gZipDatabase :: Monad m => (Proxy f, Proxy g, Proxy h, Proxy be) -> (forall tbl. (IsAnnotatedDatabaseEntity be tbl, AnnotatedDatabaseEntityRegularRequirements be tbl) => f tbl -> g tbl -> m (h tbl)) -> M1 a b x () -> M1 a b y () -> m (M1 a b z ()) |
Internals
pgDefaultConstraint :: forall ty. (HasColumnType ty, HasSqlValueSyntax PgValueSyntax ty) => (forall ctx s. QGenExpr ctx Postgres s ty) -> ColumnConstraint Source #
Postgres-specific function to convert any QGenExpr
into a meaningful PgExpressionSyntax
, so
that it can be rendered inside a Default
column constraint.