beam-migrate-0.5.2.0: SQL DDL support and migrations support library for Beam
Safe HaskellSafe-Inferred
LanguageHaskell2010

Database.Beam.Migrate.Checks

Description

Defines common DatabasePredicates that are shared among backends

Synopsis

Table checks

data TableExistsPredicate Source #

Asserts that a table with the given name exists in a database

Constructors

TableExistsPredicate QualifiedName

Table name

Instances

Instances details
Generic TableExistsPredicate Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

Associated Types

type Rep TableExistsPredicate :: Type -> Type #

Show TableExistsPredicate Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

DatabasePredicate TableExistsPredicate Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

Eq TableExistsPredicate Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

Ord TableExistsPredicate Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

Hashable TableExistsPredicate Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

type Rep TableExistsPredicate Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

type Rep TableExistsPredicate = D1 ('MetaData "TableExistsPredicate" "Database.Beam.Migrate.Checks" "beam-migrate-0.5.2.0-inplace" 'False) (C1 ('MetaCons "TableExistsPredicate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QualifiedName)))

class HasDataTypeCreatedCheck dataType where Source #

A class that can check whether a particular data type is present in a set of preconditions.

Methods

dataTypeHasBeenCreated :: dataType -> (forall preCondition. Typeable preCondition => [preCondition]) -> Bool Source #

Instances

Instances details
HasDataTypeCreatedCheck HsDataType Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Methods

dataTypeHasBeenCreated :: HsDataType -> (forall preCondition. Typeable preCondition => [preCondition]) -> Bool Source #

data TableHasColumn be where Source #

Asserts that the table specified has a column with the given data type. The type paramater syntax should be an instance of IsSql92ColumnSchemaSyntax.

data TableColumnHasConstraint be Source #

Asserts that a particular column of a table has a given constraint. The syntax type parameter should be an instance of IsSql92ColumnSchemaSyntax

Instances

Instances details
Generic (TableColumnHasConstraint be) Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

Associated Types

type Rep (TableColumnHasConstraint be) :: Type -> Type #

(Typeable be, BeamMigrateOnlySqlBackend be, Hashable (BeamSqlBackendColumnConstraintDefinitionSyntax be)) => DatabasePredicate (TableColumnHasConstraint be) Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

Eq (BeamSqlBackendColumnConstraintDefinitionSyntax be) => Eq (TableColumnHasConstraint be) Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

Hashable (BeamSqlBackendColumnConstraintDefinitionSyntax be) => Hashable (TableColumnHasConstraint be) Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

type Rep (TableColumnHasConstraint be) Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

type Rep (TableColumnHasConstraint be) = D1 ('MetaData "TableColumnHasConstraint" "Database.Beam.Migrate.Checks" "beam-migrate-0.5.2.0-inplace" 'False) (C1 ('MetaCons "TableColumnHasConstraint" 'PrefixI 'True) (S1 ('MetaSel ('Just "hasConstraint_table") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QualifiedName) :*: (S1 ('MetaSel ('Just "hasConstraint_column") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "hasConstraint_defn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (BeamSqlBackendColumnConstraintDefinitionSyntax be)))))

data TableHasPrimaryKey Source #

Asserts that the given table has a primary key made of the given columns. The order of the columns is significant.

Constructors

TableHasPrimaryKey 

Fields

Instances

Instances details
Generic TableHasPrimaryKey Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

Associated Types

type Rep TableHasPrimaryKey :: Type -> Type #

Show TableHasPrimaryKey Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

DatabasePredicate TableHasPrimaryKey Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

Eq TableHasPrimaryKey Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

Hashable TableHasPrimaryKey Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

type Rep TableHasPrimaryKey Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

type Rep TableHasPrimaryKey = D1 ('MetaData "TableHasPrimaryKey" "Database.Beam.Migrate.Checks" "beam-migrate-0.5.2.0-inplace" 'False) (C1 ('MetaCons "TableHasPrimaryKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "hasPrimaryKey_table") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QualifiedName) :*: S1 ('MetaSel ('Just "hasPrimaryKey_cols") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])))

Deserialization