Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- createTable :: (Beamable table, Table table, BeamMigrateSqlBackend be) => Text -> TableSchema be table -> Migration be (CheckedDatabaseEntity be db (TableEntity table))
- dropTable :: BeamMigrateSqlBackend be => CheckedDatabaseEntity be db (TableEntity table) -> Migration be ()
- preserve :: CheckedDatabaseEntity be db e -> Migration be (CheckedDatabaseEntity be db' e)
- newtype TableMigration be a = TableMigration (WriterT [BeamSqlBackendAlterTableSyntax be] (State (TableName, [TableCheck])) a)
- data ColumnMigration a = ColumnMigration {}
- alterTable :: forall be db db' table table'. (Table table', BeamMigrateSqlBackend be) => CheckedDatabaseEntity be db (TableEntity table) -> (table ColumnMigration -> TableMigration be (table' ColumnMigration)) -> Migration be (CheckedDatabaseEntity be db' (TableEntity table'))
- renameTableTo :: BeamMigrateSqlBackend be => Text -> table ColumnMigration -> TableMigration be (table ColumnMigration)
- renameColumnTo :: BeamMigrateSqlBackend be => Text -> ColumnMigration a -> TableMigration be (ColumnMigration a)
- addColumn :: BeamMigrateSqlBackend be => TableFieldSchema be a -> TableMigration be (ColumnMigration a)
- dropColumn :: BeamMigrateSqlBackend be => ColumnMigration a -> TableMigration be ()
- data DefaultValue be a
- newtype Constraint be = Constraint (BeamSqlBackendConstraintSyntax be)
- data NotNullConstraint be
- field :: (BeamMigrateSqlBackend be, FieldReturnType False False be resTy a) => Text -> DataType be resTy -> a
- defaultTo_ :: BeamMigrateSqlBackend be => (forall s. QExpr be s a) -> DefaultValue be a
- notNull :: BeamMigrateSqlBackend be => NotNullConstraint be
- unique :: BeamMigrateSqlBackend be => Constraint be
- class FieldReturnType (defaultGiven :: Bool) (collationGiven :: Bool) be resTy a | a -> be resTy where
- field' :: BeamMigrateSqlBackend be => Proxy defaultGiven -> Proxy collationGiven -> Text -> BeamMigrateSqlBackendDataTypeSyntax be -> Maybe (BeamSqlBackendExpressionSyntax be) -> Maybe Text -> [BeamSqlBackendColumnConstraintDefinitionSyntax be] -> a
Table manipulation
Creation and deletion
createTable :: (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.c
dropTable :: BeamMigrateSqlBackend be => CheckedDatabaseEntity be db (TableEntity table) -> Migration be () Source #
Add a DROP TABLE
statement to this migration.
preserve :: 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
TableMigration (WriterT [BeamSqlBackendAlterTableSyntax be] (State (TableName, [TableCheck])) a) |
Instances
Monad (TableMigration be) Source # | |
Defined in Database.Beam.Migrate.SQL.Tables (>>=) :: TableMigration be a -> (a -> TableMigration be b) -> TableMigration be b # (>>) :: TableMigration be a -> TableMigration be b -> TableMigration be b # return :: a -> TableMigration be a # fail :: String -> TableMigration be a # | |
Functor (TableMigration be) Source # | |
Defined in Database.Beam.Migrate.SQL.Tables fmap :: (a -> b) -> TableMigration be a -> TableMigration be b # (<$) :: a -> TableMigration be b -> TableMigration be a # | |
Applicative (TableMigration be) Source # | |
Defined in Database.Beam.Migrate.SQL.Tables 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 # |
data ColumnMigration a Source #
A column in the process of being altered
alterTable :: forall be db db' 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
Field specification
data DefaultValue be a Source #
Represents the default value of a field with a given column schema syntax and type
Instances
FieldReturnType True collationGiven be resTy a => FieldReturnType False collationGiven be resTy (DefaultValue be resTy -> a) Source # | |
Defined in Database.Beam.Migrate.SQL.Tables 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 # | |
Defined in Database.Beam.Migrate.SQL.Tables 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
FieldReturnType defaultGiven collationGiven be resTy a => FieldReturnType defaultGiven collationGiven be resTy (Constraint be -> a) Source # | |
Defined in Database.Beam.Migrate.SQL.Tables field' :: Proxy defaultGiven -> Proxy collationGiven -> Text -> BeamMigrateSqlBackendDataTypeSyntax be -> Maybe (BeamSqlBackendExpressionSyntax be) -> Maybe Text -> [BeamSqlBackendColumnConstraintDefinitionSyntax be] -> Constraint be -> a Source # |
data NotNullConstraint be Source #
Instances
(FieldReturnType defaultGiven collationGiven be resTy (Constraint be -> a), IsNotNull resTy) => FieldReturnType defaultGiven collationGiven be resTy (NotNullConstraint be -> a) Source # | |
Defined in Database.Beam.Migrate.SQL.Tables 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 #
field' :: BeamMigrateSqlBackend be => Proxy defaultGiven -> Proxy collationGiven -> Text -> BeamMigrateSqlBackendDataTypeSyntax be -> Maybe (BeamSqlBackendExpressionSyntax be) -> Maybe Text -> [BeamSqlBackendColumnConstraintDefinitionSyntax be] -> a Source #