| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Database.Beam.AutoMigrate
Description
This module provides the high-level API to migrate a database.
Synopsis
- defaultAnnotatedDbSettings :: forall be db. ToAnnotated be db DatabaseEntity AnnotatedDatabaseEntity => DatabaseSettings be db -> AnnotatedDatabaseSettings be db
- fromAnnotatedDbSettings :: (FromAnnotated be db DatabaseEntity AnnotatedDatabaseEntity, GSchema be db anns (Rep (AnnotatedDatabaseSettings be db))) => AnnotatedDatabaseSettings be db -> Proxy (anns :: [Annotation]) -> Schema
- deAnnotateDatabase :: forall be db. FromAnnotated be db DatabaseEntity AnnotatedDatabaseEntity => AnnotatedDatabaseSettings be db -> DatabaseSettings be db
- type Migration m = ExceptT MigrationError (StateT [WithPriority Edit] m) ()
- migrate :: MonadIO m => Connection -> Schema -> Migration m
- runMigrationUnsafe :: MonadBeam Postgres Pg => Connection -> Migration Pg -> IO ()
- runMigrationWithEditUpdate :: MonadBeam Postgres Pg => ([WithPriority Edit] -> [WithPriority Edit]) -> Connection -> Schema -> IO ()
- tryRunMigrationsWithEditUpdate :: (Generic (db (DatabaseEntity be db)), Generic (db (AnnotatedDatabaseEntity be db)), Database be db, GZipDatabase be (AnnotatedDatabaseEntity be db) (AnnotatedDatabaseEntity be db) (DatabaseEntity be db) (Rep (db (AnnotatedDatabaseEntity be db))) (Rep (db (AnnotatedDatabaseEntity be db))) (Rep (db (DatabaseEntity be db))), GSchema be db '[] (Rep (db (AnnotatedDatabaseEntity be db)))) => AnnotatedDatabaseSettings be db -> Connection -> IO ()
- calcMigrationSteps :: (Generic (db (DatabaseEntity be db)), Generic (db (AnnotatedDatabaseEntity be db)), Database be db, GZipDatabase be (AnnotatedDatabaseEntity be db) (AnnotatedDatabaseEntity be db) (DatabaseEntity be db) (Rep (db (AnnotatedDatabaseEntity be db))) (Rep (db (AnnotatedDatabaseEntity be db))) (Rep (db (DatabaseEntity be db))), GSchema be db '[] (Rep (db (AnnotatedDatabaseEntity be db)))) => AnnotatedDatabaseSettings be db -> Connection -> IO Diff
- createMigration :: Monad m => Diff -> Migration m
- splitEditsOnSafety :: [WithPriority Edit] -> ([WithPriority Edit], [WithPriority Edit])
- fastApproximateRowCountFor :: TableName -> Pg (Maybe Int64)
- prettyEditActionDescription :: EditAction -> Text
- prettyEditSQL :: Edit -> Text
- showMigration :: MonadIO m => Migration m -> m String
- printMigration :: MonadIO m => Migration m -> m ()
- printMigrationIO :: Migration Pg -> IO ()
- unsafeRunMigration :: (MonadBeam Postgres m, MonadIO m) => Migration m -> m ()
- module Database.Beam.AutoMigrate.Validity
- module Database.Beam.AutoMigrate.Types
- module Database.Beam.AutoMigrate.Generic
- module Database.Beam.AutoMigrate.Diff
- module Database.Beam.AutoMigrate.Compat
- module Database.Beam.AutoMigrate.Annotated
- type FromAnnotated (be :: *) (db :: DatabaseKind) e1 e2 = (Generic (db (e1 be db)), Generic (db (e2 be db)), Database be db, GZipDatabase be (e2 be db) (e2 be db) (e1 be db) (Rep (db (e2 be db))) (Rep (db (e2 be db))) (Rep (db (e1 be db))))
- type ToAnnotated (be :: *) (db :: DatabaseKind) e1 e2 = (Generic (db (e1 be db)), Generic (db (e2 be db)), Database be db, GZipDatabase be (e1 be db) (e2 be db) (e2 be db) (Rep (db (e1 be db))) (Rep (db (e2 be db))) (Rep (db (e2 be db))))
- sqlSingleQuoted :: Text -> Text
- sqlEscaped :: Text -> Text
- editToSqlCommand :: Edit -> PgCommandSyntax
Annotating a database
The first thing to do in order to be able to use this library is to convert a Beam's DatabaseSettings
into an AnnotatedDatabaseSettings. You typically have two options in order to do that:
- If you don't have an existing
DatabaseSettingsfrom a previous application, you can simply calldefaultAnnotatedDbSettingswithdefaultDbSettings, as indefaultAnnotatedDbSettings defaultDbSettings; - If you are starting from an existing
DatabaseSettings, then simply calldefaultAnnotatedDbSettingspassing your existingDatabaseSettings.
defaultAnnotatedDbSettings :: forall be db. ToAnnotated be db DatabaseEntity AnnotatedDatabaseEntity => DatabaseSettings be db -> AnnotatedDatabaseSettings be db Source #
Turns a Beam's DatabaseSettings into an AnnotatedDatabaseSettings.
Generating a Schema
Once you have an AnnotatedDatabaseSettings, you can produce a Schema simply by calling
fromAnnotatedDbSettings. The second parameter can be used to selectively turn off automatic FK-discovery
for one or more tables. For more information about specifying your own table constraints, refer to the
Annotated module.
fromAnnotatedDbSettings :: (FromAnnotated be db DatabaseEntity AnnotatedDatabaseEntity, GSchema be db anns (Rep (AnnotatedDatabaseSettings be db))) => AnnotatedDatabaseSettings be db -> Proxy (anns :: [Annotation]) -> Schema Source #
Turns an AnnotatedDatabaseSettings into a Schema. Under the hood, this function will do the
following:
- It will turn each
TableEntityof your database into aTable; - It will turn each
PgEnumenumeration type into anEnumeration, which will map to anENUMtype in the DB; - It will run what we call the automatic FK-discovery algorithm. What this means practically speaking
is that if a reference to an external
PrimaryKeyis found, and suchPrimaryKeyuniquely identifies anotherTableEntityin your database, the automatic FK-discovery algorithm will turn into into aForeignKeyTableConstraint, without any user intervention. In case there is ambiguity instead, the library will fail with a static error until the user won't disable the relevant tables (via the providedProxytype) and annotate them to do the "right thing".
Downcasting an AnnotatedDatabaseSettings into a simple DatabaseSettings
deAnnotateDatabase :: forall be db. FromAnnotated be db DatabaseEntity AnnotatedDatabaseEntity => AnnotatedDatabaseSettings be db -> DatabaseSettings be db Source #
Downcast an AnnotatedDatabaseSettings into Beam's standard DatabaseSettings.
Generating and running migrations
type Migration m = ExceptT MigrationError (StateT [WithPriority Edit] m) () Source #
A database Migration.
migrate :: MonadIO m => Connection -> Schema -> Migration m Source #
Given a Connection to a database and a Schema (which can be generated using fromAnnotatedDbSettings)
it returns a Migration, which can then be executed via runMigration.
runMigrationUnsafe :: MonadBeam Postgres Pg => Connection -> Migration Pg -> IO () Source #
Runs the input Migration in a concrete Postgres backend.
runMigrationWithEditUpdate :: MonadBeam Postgres Pg => ([WithPriority Edit] -> [WithPriority Edit]) -> Connection -> Schema -> IO () Source #
Run the steps of the migration in priority order, providing a hook to allow the user
to take action for Unsafe edits. The given function is only called for unsafe edits.
This allows you to perform some checks for when the edit safe in some circumstances.
- Deleting an empty table/column
- Making an empty column non-nullable
tryRunMigrationsWithEditUpdate :: (Generic (db (DatabaseEntity be db)), Generic (db (AnnotatedDatabaseEntity be db)), Database be db, GZipDatabase be (AnnotatedDatabaseEntity be db) (AnnotatedDatabaseEntity be db) (DatabaseEntity be db) (Rep (db (AnnotatedDatabaseEntity be db))) (Rep (db (AnnotatedDatabaseEntity be db))) (Rep (db (DatabaseEntity be db))), GSchema be db '[] (Rep (db (AnnotatedDatabaseEntity be db)))) => AnnotatedDatabaseSettings be db -> Connection -> IO () Source #
Compare the existing schema in the database with the expected schema in Haskell and try to edit the existing schema as necessary
calcMigrationSteps :: (Generic (db (DatabaseEntity be db)), Generic (db (AnnotatedDatabaseEntity be db)), Database be db, GZipDatabase be (AnnotatedDatabaseEntity be db) (AnnotatedDatabaseEntity be db) (DatabaseEntity be db) (Rep (db (AnnotatedDatabaseEntity be db))) (Rep (db (AnnotatedDatabaseEntity be db))) (Rep (db (DatabaseEntity be db))), GSchema be db '[] (Rep (db (AnnotatedDatabaseEntity be db)))) => AnnotatedDatabaseSettings be db -> Connection -> IO Diff Source #
Compute the Diff consisting of the steps that would be taken to migrate from the current actual
database schema to the given one, without actually performing the migration.
Creating a migration from a Diff
Migration utility functions
splitEditsOnSafety :: [WithPriority Edit] -> ([WithPriority Edit], [WithPriority Edit]) Source #
Split the given list of Edits based on their EditSafety setting.
fastApproximateRowCountFor :: TableName -> Pg (Maybe Int64) Source #
Helper query to retrieve the approximate row count from the pg_class table.
Number of live rows in the table. This is only an estimate used by the planner. It is updated by VACUUM, ANALYZE, and a few DDL commands such as CREATE INDEX.
This can be used as a check to see if an otherwise Unsafe EditAction is safe to execute.
See: * PostgreSQL Wiki Count Estimate and * PostgreSQL Manual for @pg_class@ for more information.
Printing migrations for debugging purposes
prettyEditSQL :: Edit -> Text Source #
showMigration :: MonadIO m => Migration m -> m String Source #
Pretty-prints the migration. Useful for debugging and diagnostic.
printMigration :: MonadIO m => Migration m -> m () Source #
Prints the migration to stdout. Useful for debugging and diagnostic.
Unsafe functions
unsafeRunMigration :: (MonadBeam Postgres m, MonadIO m) => Migration m -> m () Source #
Runs the input Migration in a concrete Postgres backend.
IMPORTANT: This function does not run inside a SQL transaction, hence the unsafe prefix.
Handy re-exports
Internals
type FromAnnotated (be :: *) (db :: DatabaseKind) e1 e2 = (Generic (db (e1 be db)), Generic (db (e2 be db)), Database be db, GZipDatabase be (e2 be db) (e2 be db) (e1 be db) (Rep (db (e2 be db))) (Rep (db (e2 be db))) (Rep (db (e1 be db)))) Source #
Simple class to make the signatures for defaultAnnotatedDbSettings and fromAnnotatedDbSettings
less scary. From a user's standpoint, there is nothing you have to implement.
type ToAnnotated (be :: *) (db :: DatabaseKind) e1 e2 = (Generic (db (e1 be db)), Generic (db (e2 be db)), Database be db, GZipDatabase be (e1 be db) (e2 be db) (e2 be db) (Rep (db (e1 be db))) (Rep (db (e2 be db))) (Rep (db (e2 be db)))) Source #
Simple synonym to make the signatures for defaultAnnotatedDbSettings and fromAnnotatedDbSettings
less scary. From a user's standpoint, there is nothing you have to implement.
sqlSingleQuoted :: Text -> Text Source #
sqlEscaped :: Text -> Text Source #
Escape a sql identifier according to the rules defined in the postgres manual