Safe Haskell | None |
---|---|
Language | Haskell2010 |
Utility functions for common use cases
Synopsis
- autoMigrate :: Database be db => BeamMigrationBackend be m -> CheckedDatabaseSettings be db -> m ()
- simpleSchema :: Database be db => ActionProvider be -> CheckedDatabaseSettings be db -> Maybe [BeamSqlBackendSyntax be]
- simpleMigration :: (MonadBeam be m, Database be db) => (forall a. handle -> m a -> IO a) -> BeamMigrationBackend be m -> handle -> CheckedDatabaseSettings be db -> IO (Maybe [BeamSqlBackendSyntax be])
- runSimpleMigration :: MonadBeam be m => (forall a. hdl -> m a -> IO a) -> hdl -> [BeamSqlBackendSyntax be] -> IO ()
- backendMigrationScript :: BeamSqlBackend be => (BeamSqlBackendSyntax be -> String) -> Migration be a -> String
- data VerificationResult
- verifySchema :: (Database be db, MonadBeam be m) => BeamMigrationBackend be m -> CheckedDatabaseSettings be db -> m VerificationResult
- createSchema :: Database be db => BeamMigrationBackend be m -> CheckedDatabaseSettings be db -> m ()
- data BringUpToDateHooks m = BringUpToDateHooks {
- runIrreversibleHook :: m Bool
- startStepHook :: Int -> Text -> m ()
- endStepHook :: Int -> Text -> m ()
- runCommandHook :: Int -> String -> m ()
- queryFailedHook :: m ()
- discontinuousMigrationsHook :: Int -> m ()
- logMismatchHook :: Int -> Text -> Text -> m ()
- databaseAheadHook :: Int -> m ()
- defaultUpToDateHooks :: Monad m => BringUpToDateHooks m
- bringUpToDate :: (Database be db, HasDataTypeCreatedCheck (BeamMigrateSqlBackendDataTypeSyntax be)) => BeamMigrationBackend be m -> MigrationSteps be () (CheckedDatabaseSettings be db) -> m (Maybe (CheckedDatabaseSettings be db))
- bringUpToDateWithHooks :: forall db be m. (Database be db, HasDataTypeCreatedCheck (BeamMigrateSqlBackendDataTypeSyntax be)) => BringUpToDateHooks m -> BeamMigrationBackend be m -> MigrationSteps be () (CheckedDatabaseSettings be db) -> m (Maybe (CheckedDatabaseSettings be db))
- haskellSchema :: MonadBeam be m => BeamMigrationBackend be m -> m String
- module Database.Beam.Migrate.Actions
- module Database.Beam.Migrate.Types
Documentation
autoMigrate :: Database be db => BeamMigrationBackend be m -> CheckedDatabaseSettings be db -> m () Source #
Given a BeamMigrationBackend
, attempt to automatically bring the current
database up-to-date with the given CheckedDatabaseSettings
. Fails (via
fail
) if this involves an irreversible migration (one that may result in
data loss).
simpleSchema :: Database be db => ActionProvider be -> CheckedDatabaseSettings be db -> Maybe [BeamSqlBackendSyntax be] Source #
Attempt to find a SQL schema given an ActionProvider
and a checked
database. Returns Nothing
if no schema could be found, which usually means
you have chosen the wrong ActionProvider
, or the backend you're using is
buggy.
simpleMigration :: (MonadBeam be m, Database be db) => (forall a. handle -> m a -> IO a) -> BeamMigrationBackend be m -> handle -> CheckedDatabaseSettings be db -> IO (Maybe [BeamSqlBackendSyntax be]) Source #
Given a migration backend, a handle to a database, and a checked database,
attempt to find a schema. This should always return Just
, unless the
backend has incomplete migrations support.
BeamMigrationBackend
s can usually be found in a module named
Database.Beam.Backend.Migrate
with the namemigrationBackend
runSimpleMigration :: MonadBeam be m => (forall a. hdl -> m a -> IO a) -> hdl -> [BeamSqlBackendSyntax be] -> IO () Source #
Run a sequence of commands on a database
backendMigrationScript :: BeamSqlBackend be => (BeamSqlBackendSyntax be -> String) -> Migration be a -> String Source #
Given a function to convert a command to a String
, produce a script that
will execute the given migration. Usually, the function you provide
eventually calls displaySyntax
to rendere the command.
data VerificationResult Source #
Result type for verifySchema
Instances
Show VerificationResult Source # | |
Defined in Database.Beam.Migrate.Simple showsPrec :: Int -> VerificationResult -> ShowS # show :: VerificationResult -> String # showList :: [VerificationResult] -> ShowS # |
verifySchema :: (Database be db, MonadBeam be m) => BeamMigrationBackend be m -> CheckedDatabaseSettings be db -> m VerificationResult Source #
Verify that the given, beam database matches the actual
schema. On success, returns VerificationSucceeded
, on failure,
returns VerificationFailed
and a list of missing predicates.
createSchema :: Database be db => BeamMigrationBackend be m -> CheckedDatabaseSettings be db -> m () Source #
Given a CheckedDatabaseSettings
and a BeamMigrationBackend
,
attempt to create the schema from scratch in the current database.
May fail
if we cannot find a schema
data BringUpToDateHooks m Source #
BringUpToDateHooks | |
|
defaultUpToDateHooks :: Monad m => BringUpToDateHooks m Source #
Default set of BringUpToDateHooks
. Refuses to run irreversible
migrations, and fails in case of error, using fail
.
bringUpToDate :: (Database be db, HasDataTypeCreatedCheck (BeamMigrateSqlBackendDataTypeSyntax be)) => BeamMigrationBackend be m -> MigrationSteps be () (CheckedDatabaseSettings be db) -> m (Maybe (CheckedDatabaseSettings be db)) Source #
Equivalent to calling bringUpToDateWithHooks
with defaultUpToDateHooks
.
Tries to bring the database up to date, using the database log and the given
MigrationSteps
. Fails if the migration is irreversible, or an error occurs.
bringUpToDateWithHooks :: forall db be m. (Database be db, HasDataTypeCreatedCheck (BeamMigrateSqlBackendDataTypeSyntax be)) => BringUpToDateHooks m -> BeamMigrationBackend be m -> MigrationSteps be () (CheckedDatabaseSettings be db) -> m (Maybe (CheckedDatabaseSettings be db)) Source #
Check for the beam-migrate log. If it exists, use it and the supplied migrations to bring the database up-to-date. Otherwise, create the log and run all migrations.
Accepts a set of hooks that can be used to customize behavior. See the
documentation for BringUpToDateHooks
for more information. Calling this
with defaultUpToDateHooks
is the same as using bringUpToDate
.
haskellSchema :: MonadBeam be m => BeamMigrationBackend be m -> m String Source #
Given a BeamMigrationBackend
, get a string representing a Haskell module
that would be a good starting point for further development.
For example, for a postgres database named chinook
import Database.Beam.Migrate.Simple import Database.Beam.Postgres (runBeamPostgres) import Database.Beam.Postgres.Migrate (migrationBackend) import Database.PostgreSQL.Simple getSchema :: IO String getSchema = do pg <- connectPostgreSQL runBeamPostgres pg (haskellSchema migrationBackend)
Backends that have a migration backend typically export it under the module
name Database.Beam.Backend.Migrate
.
module Database.Beam.Migrate.Types