Safe Haskell | None |
---|---|
Language | Haskell2010 |
Utilities for validating and inspecting Selda tables.
Synopsis
- data TableDiff
- = TableOK
- | TableMissing
- | UniqueMissing [[ColName]]
- | UniquePresent [[ColName]]
- | PkMissing [ColName]
- | PkPresent [ColName]
- | InconsistentColumns [(ColName, [ColumnDiff])]
- data ColumnDiff
- data TableName
- data ColName
- data ColumnInfo
- data SqlTypeRep
- tableInfo :: Table a -> TableInfo
- showTableDiff :: TableDiff -> Text
- showColumnDiff :: ColumnDiff -> Text
- describeTable :: MonadSelda m => TableName -> m TableInfo
- diffTable :: MonadSelda m => Table a -> m TableDiff
- diffTables :: Table a -> Table b -> TableDiff
- validateTable :: (MonadSelda m, MonadThrow m) => Table a -> m ()
- validateSchema :: MonadThrow m => Table a -> m ()
Documentation
A description of the difference between a schema and its corresponding database table.
TableOK | |
TableMissing | |
UniqueMissing [[ColName]] | |
UniquePresent [[ColName]] | |
PkMissing [ColName] | |
PkPresent [ColName] | |
InconsistentColumns [(ColName, [ColumnDiff])] |
data ColumnDiff Source #
A description of the difference between a column in a Selda table and its corresponding database column.
Instances
Eq ColumnDiff Source # | |
Defined in Database.Selda.Validation (==) :: ColumnDiff -> ColumnDiff -> Bool # (/=) :: ColumnDiff -> ColumnDiff -> Bool # | |
Show ColumnDiff Source # | |
Defined in Database.Selda.Validation showsPrec :: Int -> ColumnDiff -> ShowS # show :: ColumnDiff -> String # showList :: [ColumnDiff] -> ShowS # |
Name of a database table.
Name of a database column.
data ColumnInfo Source #
Comprehensive information about a column.
Instances
Eq ColumnInfo Source # | |
Defined in Database.Selda.Backend.Internal (==) :: ColumnInfo -> ColumnInfo -> Bool # (/=) :: ColumnInfo -> ColumnInfo -> Bool # | |
Show ColumnInfo Source # | |
Defined in Database.Selda.Backend.Internal showsPrec :: Int -> ColumnInfo -> ShowS # show :: ColumnInfo -> String # showList :: [ColumnInfo] -> ShowS # |
data SqlTypeRep Source #
Representation of an SQL type.
Instances
Eq SqlTypeRep Source # | |
Defined in Database.Selda.SqlType (==) :: SqlTypeRep -> SqlTypeRep -> Bool # (/=) :: SqlTypeRep -> SqlTypeRep -> Bool # | |
Ord SqlTypeRep Source # | |
Defined in Database.Selda.SqlType compare :: SqlTypeRep -> SqlTypeRep -> Ordering # (<) :: SqlTypeRep -> SqlTypeRep -> Bool # (<=) :: SqlTypeRep -> SqlTypeRep -> Bool # (>) :: SqlTypeRep -> SqlTypeRep -> Bool # (>=) :: SqlTypeRep -> SqlTypeRep -> Bool # max :: SqlTypeRep -> SqlTypeRep -> SqlTypeRep # min :: SqlTypeRep -> SqlTypeRep -> SqlTypeRep # | |
Show SqlTypeRep Source # | |
Defined in Database.Selda.SqlType showsPrec :: Int -> SqlTypeRep -> ShowS # show :: SqlTypeRep -> String # showList :: [SqlTypeRep] -> ShowS # |
tableInfo :: Table a -> TableInfo Source #
Get the column information for each column in the given table.
showTableDiff :: TableDiff -> Text Source #
Pretty-print a table diff.
showColumnDiff :: ColumnDiff -> Text Source #
Pretty-print a column diff.
describeTable :: MonadSelda m => TableName -> m TableInfo Source #
Get a description of the table by the given name currently in the database.
diffTable :: MonadSelda m => Table a -> m TableDiff Source #
Check the given table for consistency with the current database, returning a description of all inconsistencies found. The table schema itself is not validated beforehand.
diffTables :: Table a -> Table b -> TableDiff Source #
Compute the difference between the two given tables. The first table is considered to be the schema, and the second the database.
validateTable :: (MonadSelda m, MonadThrow m) => Table a -> m () Source #
Validate a table schema, and check it for consistency against the current
database.
Throws a ValidationError
if the schema does not validate, or if
inconsistencies were found.
validateSchema :: MonadThrow m => Table a -> m () Source #
Ensure that the schema of the given table is valid. Does not ensure consistency with the current database.