beam-migrate
Safe HaskellNone
LanguageHaskell2010

Database.Beam.Migrate.SQL.Tables

Synopsis

Table manipulation

Creation and deletion

createTable :: forall table be (db :: (Type -> Type) -> Type). (Beamable table, Table table, BeamMigrateSqlBackend be) => Text -> TableSchema be table -> Migration be (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.

To create a table in a specific schema, see createTableWithSchema.

createTableWithSchema Source #

Arguments

:: forall table be (db :: (Type -> Type) -> Type). (Beamable table, Table table, BeamMigrateSqlBackend be) 
=> Maybe DatabaseSchema

Schema name, if any

-> Text

Table name

-> TableSchema be table 
-> Migration be (CheckedDatabaseEntity be db (TableEntity table)) 

Add a CREATE TABLE statement to this migration, with an explicit schema

The first argument is the name of the schema, while the second 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.

Note that the database schema is expected to exist; see createDatabaseSchema to create a database schema.

dropTable :: forall be (db :: (Type -> Type) -> Type) (table :: (Type -> Type) -> Type). BeamMigrateSqlBackend be => CheckedDatabaseEntity be db (TableEntity table) -> Migration be () Source #

Add a DROP TABLE statement to this migration.

preserve :: forall be (db :: (Type -> Type) -> Type) e (db' :: (Type -> Type) -> Type). CheckedDatabaseEntity be db e -> Migration be (CheckedDatabaseEntity be db' e) Source #

Copy a table schema from one database to another

ALTER TABLE

newtype TableMigration be a Source #

Monad representing a series of ALTER TABLE statements

Constructors

TableMigration (WriterT [BeamSqlBackendAlterTableSyntax be] (State (TableName, [TableCheck])) a) 

Instances

Instances details
Applicative (TableMigration be) Source # 
Instance details

Defined in Database.Beam.Migrate.SQL.Tables

Methods

pure :: a -> TableMigration be a #

(<*>) :: TableMigration be (a -> b) -> TableMigration be a -> TableMigration be b #

liftA2 :: (a -> b -> c) -> TableMigration be a -> TableMigration be b -> TableMigration be c #

(*>) :: TableMigration be a -> TableMigration be b -> TableMigration be b #

(<*) :: TableMigration be a -> TableMigration be b -> TableMigration be a #

Functor (TableMigration be) Source # 
Instance details

Defined in Database.Beam.Migrate.SQL.Tables

Methods

fmap :: (a -> b) -> TableMigration be a -> TableMigration be b #

(<$) :: a -> TableMigration be b -> TableMigration be a #

Monad (TableMigration be) Source # 
Instance details

Defined in Database.Beam.Migrate.SQL.Tables

Methods

(>>=) :: TableMigration be a -> (a -> TableMigration be b) -> TableMigration be b #

(>>) :: TableMigration be a -> TableMigration be b -> TableMigration be b #

return :: a -> TableMigration be a #

data ColumnMigration a Source #

A column in the process of being altered

alterTable :: forall be (db :: (Type -> Type) -> Type) (db' :: (Type -> Type) -> Type) table table'. (Table table', BeamMigrateSqlBackend be) => CheckedDatabaseEntity be db (TableEntity table) -> (table ColumnMigration -> TableMigration be (table' ColumnMigration)) -> Migration be (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 :: BeamMigrateSqlBackend be => Text -> table ColumnMigration -> TableMigration be (table ColumnMigration) Source #

ALTER TABLE ... RENAME TO command

renameColumnTo :: BeamMigrateSqlBackend be => Text -> ColumnMigration a -> TableMigration be (ColumnMigration a) Source #

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

addColumn :: BeamMigrateSqlBackend be => TableFieldSchema be a -> TableMigration be (ColumnMigration a) Source #

ALTER TABLE ... ADD COLUMN ... command

dropColumn :: BeamMigrateSqlBackend be => ColumnMigration a -> TableMigration be () Source #

ALTER TABLE ... DROP COLUMN ... command

Schema manipulation

data DatabaseSchema Source #

Represents a database schema. To create one, see createDatabaseSchema; to materialize one, see existingDatabaseSchema.

createDatabaseSchema :: BeamMigrateSchemaSqlBackend be => Text -> Migration be DatabaseSchema Source #

Add a CREATE SCHEMA statement to this migration

To create a table in a specific schema, see createTableWithSchema. To drop a schema, see dropDatabaseSchema. To materialize an existing schema for use in a migration, see existingDatabaseSchema.

dropDatabaseSchema :: BeamMigrateSchemaSqlBackend be => DatabaseSchema -> Migration be () Source #

Add a DROP SCHEMA statement to this migration.

Depending on the backend, this may fail if the schema is not empty.

To create a schema, see createDatabaseSchema. To materialize a DatabaseSchema, see 'existingDatabaseSchema

existingDatabaseSchema :: Text -> Migration be DatabaseSchema Source #

Materialize a schema for use during a migration.

Example usage, where NewDB has one more table than OldDB in the my_schema schema:

migrationStep :: CheckedDatabaseSettings be OldDB
              -> Migration be (CheckedDatabaseSettings be NewDB)
migrationStep (OldDB oldtable)= do
  schema <- existingDatabaseSchema "my_schema"
  pure $ NewDB <$> pure oldtable
               <*> createTableWithSchema (Just schema) "my_table"

Field specification

data DefaultValue be a Source #

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

Instances

Instances details
FieldReturnType 'True collationGiven be resTy a => FieldReturnType 'False collationGiven be resTy (DefaultValue be resTy -> a) Source # 
Instance details

Defined in Database.Beam.Migrate.SQL.Tables

Methods

field' :: Proxy 'False -> Proxy collationGiven -> Text -> BeamMigrateSqlBackendDataTypeSyntax be -> Maybe (BeamSqlBackendExpressionSyntax be) -> Maybe Text -> [BeamSqlBackendColumnConstraintDefinitionSyntax be] -> DefaultValue be resTy -> a Source #

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

Defined in Database.Beam.Migrate.SQL.Tables

Methods

field' :: Proxy 'True -> Proxy collationGiven -> Text -> BeamMigrateSqlBackendDataTypeSyntax be -> Maybe (BeamSqlBackendExpressionSyntax be) -> Maybe Text -> [BeamSqlBackendColumnConstraintDefinitionSyntax be] -> DefaultValue be resTy -> a Source #

newtype Constraint be Source #

Represents a constraint in the given column schema syntax

Instances

Instances details
FieldReturnType defaultGiven collationGiven be resTy a => FieldReturnType defaultGiven collationGiven be resTy (Constraint be -> a) Source # 
Instance details

Defined in Database.Beam.Migrate.SQL.Tables

Methods

field' :: Proxy defaultGiven -> Proxy collationGiven -> Text -> BeamMigrateSqlBackendDataTypeSyntax be -> Maybe (BeamSqlBackendExpressionSyntax be) -> Maybe Text -> [BeamSqlBackendColumnConstraintDefinitionSyntax be] -> Constraint be -> a Source #

data NotNullConstraint be Source #

Instances

Instances details
(FieldReturnType defaultGiven collationGiven be resTy (Constraint be -> a), IsNotNull resTy) => FieldReturnType defaultGiven collationGiven be resTy (NotNullConstraint be -> a) Source # 
Instance details

Defined in Database.Beam.Migrate.SQL.Tables

Methods

field' :: Proxy defaultGiven -> Proxy collationGiven -> Text -> BeamMigrateSqlBackendDataTypeSyntax be -> Maybe (BeamSqlBackendExpressionSyntax be) -> Maybe Text -> [BeamSqlBackendColumnConstraintDefinitionSyntax be] -> NotNullConstraint be -> a Source #

field :: (BeamMigrateSqlBackend be, FieldReturnType 'False 'False be resTy a) => Text -> DataType be 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_ :: BeamMigrateSqlBackend be => (forall s. QExpr be s a) -> DefaultValue be a Source #

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

notNull :: BeamMigrateSqlBackend be => NotNullConstraint be Source #

The SQL92 NOT NULL constraint

unique :: BeamMigrateSqlBackend be => Constraint be Source #

SQL UNIQUE constraint

Internal classes

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

Methods

field' :: Proxy defaultGiven -> Proxy collationGiven -> Text -> BeamMigrateSqlBackendDataTypeSyntax be -> Maybe (BeamSqlBackendExpressionSyntax be) -> Maybe Text -> [BeamSqlBackendColumnConstraintDefinitionSyntax be] -> a Source #

Instances

Instances details
FieldReturnType 'True collationGiven be resTy a => FieldReturnType 'False collationGiven be resTy (DefaultValue be resTy -> a) Source # 
Instance details

Defined in Database.Beam.Migrate.SQL.Tables

Methods

field' :: Proxy 'False -> Proxy collationGiven -> Text -> BeamMigrateSqlBackendDataTypeSyntax be -> Maybe (BeamSqlBackendExpressionSyntax be) -> Maybe Text -> [BeamSqlBackendColumnConstraintDefinitionSyntax be] -> DefaultValue be resTy -> a Source #

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

Defined in Database.Beam.Migrate.SQL.Tables

Methods

field' :: Proxy 'True -> Proxy collationGiven -> Text -> BeamMigrateSqlBackendDataTypeSyntax be -> Maybe (BeamSqlBackendExpressionSyntax be) -> Maybe Text -> [BeamSqlBackendColumnConstraintDefinitionSyntax be] -> DefaultValue be resTy -> a Source #

(BeamMigrateSqlBackend be, HasDataTypeCreatedCheck (BeamMigrateSqlBackendDataTypeSyntax be)) => FieldReturnType defaultGiven collationGiven be resTy (TableFieldSchema be resTy) Source # 
Instance details

Defined in Database.Beam.Migrate.SQL.Tables

Methods

field' :: Proxy defaultGiven -> Proxy collationGiven -> Text -> BeamMigrateSqlBackendDataTypeSyntax be -> Maybe (BeamSqlBackendExpressionSyntax be) -> Maybe Text -> [BeamSqlBackendColumnConstraintDefinitionSyntax be] -> TableFieldSchema be resTy Source #

(FieldReturnType defaultGiven collationGiven be resTy a, TypeError ('Text "Only one type declaration allowed per 'field' invocation") :: Constraint) => FieldReturnType defaultGiven collationGiven be resTy (DataType be' x -> a) Source # 
Instance details

Defined in Database.Beam.Migrate.SQL.Tables

Methods

field' :: Proxy defaultGiven -> Proxy collationGiven -> Text -> BeamMigrateSqlBackendDataTypeSyntax be -> Maybe (BeamSqlBackendExpressionSyntax be) -> Maybe Text -> [BeamSqlBackendColumnConstraintDefinitionSyntax be] -> DataType be' x -> a Source #

FieldReturnType defaultGiven collationGiven be resTy a => FieldReturnType defaultGiven collationGiven be resTy (Constraint be -> a) Source # 
Instance details

Defined in Database.Beam.Migrate.SQL.Tables

Methods

field' :: Proxy defaultGiven -> Proxy collationGiven -> Text -> BeamMigrateSqlBackendDataTypeSyntax be -> Maybe (BeamSqlBackendExpressionSyntax be) -> Maybe Text -> [BeamSqlBackendColumnConstraintDefinitionSyntax be] -> Constraint be -> a Source #

(FieldReturnType defaultGiven collationGiven be resTy (Constraint be -> a), IsNotNull resTy) => FieldReturnType defaultGiven collationGiven be resTy (NotNullConstraint be -> a) Source # 
Instance details

Defined in Database.Beam.Migrate.SQL.Tables

Methods

field' :: Proxy defaultGiven -> Proxy collationGiven -> Text -> BeamMigrateSqlBackendDataTypeSyntax be -> Maybe (BeamSqlBackendExpressionSyntax be) -> Maybe Text -> [BeamSqlBackendColumnConstraintDefinitionSyntax be] -> NotNullConstraint be -> a Source #

type family IsNotNull x where ... Source #

Equations

IsNotNull (Maybe x) = TypeError (('Text "You used Database.Beam.Migrate.notNull on a column with type" ':$$: 'ShowType (Maybe x)) ':$$: 'Text "Either remove 'notNull' from your migration or 'Maybe' from your table") :: Constraint 
IsNotNull x = ()