beam-migrate-0.2.0.0: SQL DDL support and migrations support library for Beam

Safe HaskellNone
LanguageHaskell2010

Database.Beam.Migrate.SQL.Tables

Contents

Synopsis

Table manipulation

Creation and deletion

createTable :: (Beamable table, Table table, IsSql92DdlCommandSyntax syntax) => Text -> TableSchema (Sql92CreateTableColumnSchemaSyntax (Sql92DdlCommandCreateTableSyntax syntax)) table -> Migration syntax (CheckedDatabaseEntity be db (TableEntity table)) Source #

Add a CREATE TABLE statement to this migration

The first argument is the name of the table.

The second argument is a table containing a FieldSchema for each field. See documentation on the Field command for more information.

dropTable :: IsSql92DdlCommandSyntax syntax => CheckedDatabaseEntity be db (TableEntity table) -> Migration syntax () Source #

Add a DROP TABLE statement to this migration.

preserve :: CheckedDatabaseEntity be db e -> Migration syntax (CheckedDatabaseEntity be db' e) Source #

Copy a table schema from one database to another

ALTER TABLE

newtype TableMigration syntax a Source #

Monad representing a series of ALTER TABLE statements

data ColumnMigration a Source #

A column in the process of being altered

alterTable :: forall be db db' table table' syntax. (Table table', IsSql92DdlCommandSyntax syntax) => CheckedDatabaseEntity be db (TableEntity table) -> (table ColumnMigration -> TableMigration syntax (table' ColumnMigration)) -> Migration syntax (CheckedDatabaseEntity be db' (TableEntity table')) Source #

Compose a series of ALTER TABLE commands

Example usage

migrate (OldDb oldTbl) = do
  alterTable oldTbl $ oldTbl' ->
    field2 <- renameColumnTo NewNameForField2 (_field2 oldTbl')
    dropColumn (_field3 oldTbl')
    renameTableTo NewTableName
    field4 <- addColumn (field ANewColumn smallint notNull (defaultTo_ (val_ 0)))
    return (NewTable (_field1 oldTbl') field2 field4)

The above would result in commands like:

ALTER TABLE oldtable RENAME COLUMN field2 TO NewNameForField2;
ALTER TABLE oldtable DROP COLUMN field3;
ALTER TABLE oldtable RENAME TO NewTableName;
ALTER TABLE NewTableName ADD COLUMN ANewColumn SMALLINT NOT NULL DEFAULT 0;

renameTableTo :: Sql92SaneDdlCommandSyntax syntax => Text -> table ColumnMigration -> TableMigration syntax (table ColumnMigration) Source #

ALTER TABLE ... RENAME TO command

renameColumnTo :: Sql92SaneDdlCommandSyntax syntax => Text -> ColumnMigration a -> TableMigration syntax (ColumnMigration a) Source #

ALTER TABLE ... RENAME COLUMN ... TO ... command

addColumn :: Sql92SaneDdlCommandSyntax syntax => TableFieldSchema (Sql92DdlCommandColumnSchemaSyntax syntax) a -> TableMigration syntax (ColumnMigration a) Source #

ALTER TABLE ... ADD COLUMN ... command

dropColumn :: Sql92SaneDdlCommandSyntax syntax => ColumnMigration a -> TableMigration syntax () Source #

ALTER TABLE ... DROP COLUMN ... command

Field specification

data DefaultValue syntax a Source #

Represents the default value of a field with a given column schema syntax and type

Instances

FieldReturnType True collationGiven syntax resTy a => FieldReturnType False collationGiven syntax resTy (DefaultValue syntax resTy -> a) Source # 
(FieldReturnType True collationGiven syntax resTy a, TypeError Constraint (Text "Only one DEFAULT clause can be given per 'field' invocation")) => FieldReturnType True collationGiven syntax resTy (DefaultValue syntax resTy -> a) Source # 

newtype Constraint syntax Source #

Represents a constraint in the given column schema syntax

Instances

FieldReturnType defaultGiven collationGiven syntax resTy a => FieldReturnType defaultGiven collationGiven syntax resTy (Constraint syntax -> a) Source # 

field :: IsSql92ColumnSchemaSyntax syntax => FieldReturnType False False syntax resTy a => Text -> DataType (Sql92ColumnSchemaColumnTypeSyntax syntax) resTy -> a Source #

Build a schema for a field. This function takes the name and type of the field and a variable number of modifiers, such as constraints and default values. GHC will complain at you if the modifiers do not make sense. For example, you cannot apply the notNull constraint to a column with a Maybe type.

Example of creating a table named Employee with three columns: FirstName, LastName, and HireDate

data Employee f =
  Employee { _firstName :: C f Text
           , _lastName  :: C f Text
           , _hireDate  :: C f (Maybe LocalTime)
           } deriving Generic
instance Beamable Employee

instance Table Employee where
   data PrimaryKey Employee f = EmployeeKey (C f Text) (C f Text) deriving Generic
   primaryKey = EmployeeKey $ _firstName * _lastName

instance Beamable PrimaryKey Employee f

data EmployeeDb entity
    = EmployeeDb { _employees :: entity (TableEntity Employee) }
    deriving Generic
instance Database EmployeeDb

migration :: IsSql92DdlCommandSyntax syntax => Migration syntax () EmployeeDb
migration = do
  employees <- createTable EmployeesTable
                 (Employee (field FirstNameField (varchar (Just 15)) notNull)
                           (field "last_name" (varchar Nothing) notNull (defaultTo_ (val_ Smith)))
                           (field "hiredDate" (maybeType timestamp)))
  return (EmployeeDb employees)

defaultTo_ :: IsSql92ExpressionSyntax (Sql92ColumnSchemaExpressionSyntax syntax) => (forall s. QExpr (Sql92ColumnSchemaExpressionSyntax syntax) s a) -> DefaultValue syntax a Source #

Build a DefaultValue from a QExpr. GHC will complain if you supply more than one default value.

notNull :: IsSql92ColumnSchemaSyntax syntax => Constraint syntax Source #

The SQL92 NOT NULL constraint

int :: (IsSql92DataTypeSyntax syntax, Integral a) => DataType syntax a Source #

SQL92 INTEGER data type

smallint :: (IsSql92DataTypeSyntax syntax, Integral a) => DataType syntax a Source #

SQL92 SMALLINT data type

bigint :: (IsSql2008BigIntDataTypeSyntax syntax, Integral a) => DataType syntax a Source #

SQL2008 Optional BIGINT data type

char :: IsSql92DataTypeSyntax syntax => Maybe Word -> DataType syntax Text Source #

SQL92 CHAR data type

varchar :: IsSql92DataTypeSyntax syntax => Maybe Word -> DataType syntax Text Source #

SQL92 VARCHAR data type

double :: IsSql92DataTypeSyntax syntax => DataType syntax Double Source #

SQL92 DOUBLE data type

characterLargeObject :: IsSql99DataTypeSyntax syntax => DataType syntax Text Source #

SQL99 CLOB data type

binaryLargeObject :: IsSql99DataTypeSyntax syntax => DataType syntax ByteString Source #

SQL99 BLOB data type

array :: (Typeable a, IsSql99DataTypeSyntax syntax) => DataType syntax a -> Int -> DataType syntax (Vector a) Source #

SQL99 array data types

boolean :: IsSql99DataTypeSyntax syntax => DataType syntax Bool Source #

SQL99 BOOLEAN data type

numeric :: IsSql92DataTypeSyntax syntax => Maybe (Word, Maybe Word) -> DataType syntax Scientific Source #

SQL92 NUMERIC data type

date :: IsSql92DataTypeSyntax syntax => DataType syntax LocalTime Source #

SQL92 DATE data type

time :: IsSql92DataTypeSyntax syntax => Maybe Word -> DataType syntax TimeOfDay Source #

SQL92 TIME data type

timestamp :: IsSql92DataTypeSyntax syntax => DataType syntax LocalTime Source #

SQL92 TIMESTAMP WITHOUT TIME ZONE data type

timestamptz :: IsSql92DataTypeSyntax syntax => DataType syntax LocalTime Source #

SQL92 TIMESTAMP WITH TIME ZONE data type

binary :: IsSql2003BinaryAndVarBinaryDataTypeSyntax syntax => Maybe Word -> DataType syntax Integer Source #

SQL2003 Optional BINARY data type

varbinary :: IsSql2003BinaryAndVarBinaryDataTypeSyntax syntax => Maybe Word -> DataType syntax Integer Source #

SQL2003 Optional VARBINARY data type

maybeType :: DataType syntax a -> DataType syntax (Maybe a) Source #

Haskell requires DataTypes to match exactly. Use this function to convert a DataType that expects a concrete value to one expecting a Maybe

autoType :: DataType syntax a -> DataType syntax (Auto a) Source #

Wrap a DataType in Auto

Internal classes

class FieldReturnType (defaultGiven :: Bool) (collationGiven :: Bool) syntax resTy a | a -> syntax resTy where Source #

Minimal complete definition

field'

Instances

FieldReturnType True collationGiven syntax resTy a => FieldReturnType False collationGiven syntax resTy (DefaultValue syntax resTy -> a) Source # 
(FieldReturnType True collationGiven syntax resTy a, TypeError Constraint (Text "Only one DEFAULT clause can be given per 'field' invocation")) => FieldReturnType True collationGiven syntax resTy (DefaultValue syntax resTy -> a) Source # 
(Typeable * syntax, Typeable * (Sql92ColumnSchemaColumnTypeSyntax syntax), Sql92DisplaySyntax (Sql92ColumnSchemaColumnTypeSyntax syntax), Eq (Sql92ColumnSchemaColumnTypeSyntax syntax), Sql92DisplaySyntax (Sql92ColumnSchemaColumnConstraintDefinitionSyntax syntax), Eq (Sql92ColumnSchemaColumnConstraintDefinitionSyntax syntax), IsSql92ColumnSchemaSyntax syntax, Sql92SerializableConstraintDefinitionSyntax (Sql92ColumnSchemaColumnConstraintDefinitionSyntax syntax), Sql92SerializableDataTypeSyntax (Sql92ColumnSchemaColumnTypeSyntax syntax)) => FieldReturnType defaultGiven collationGiven syntax resTy (TableFieldSchema syntax resTy) Source # 
(FieldReturnType defaultGiven collationGiven syntax resTy a, TypeError Constraint (Text "Only one type declaration allowed per 'field' invocation")) => FieldReturnType defaultGiven collationGiven syntax resTy (DataType syntax' x -> a) Source # 
FieldReturnType defaultGiven collationGiven syntax resTy a => FieldReturnType defaultGiven collationGiven syntax resTy (Constraint syntax -> a) Source #