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

Safe HaskellNone
LanguageHaskell2010

Database.Beam.Migrate.Types

Contents

Synopsis

Checked database entities

type CheckedDatabaseSettings be db = db (CheckedDatabaseEntity be db) Source #

The type of a checked database descriptor. Conceptually, this is just a DatabaseSettings with a set of predicates. Use unCheckDatabase to get the regular DatabaseSettings object and collectChecks to access the predicates.

class IsDatabaseEntity be entity => IsCheckedDatabaseEntity be entity where Source #

Like IsDatabaseEntity in beam-core, but for entities against which we can generate DatabasePredicates. Conceptually, this is the same as IsDatabaseEntity, but with one extra function to generate DatabasePredicates from the description.

Associated Types

data CheckedDatabaseEntityDescriptor be entity :: * Source #

The type of the descriptor for this checked entity. Usually this wraps the corresponding DatabaseEntityDescriptor from IsDatabaseEntity, along with some mechanism for generating DatabasePredicates.

type CheckedDatabaseEntityDefaultRequirements be entity :: Constraint Source #

Like DatabaseEntityDefaultRequirements but for checked entities

Methods

unCheck :: CheckedDatabaseEntityDescriptor be entity -> DatabaseEntityDescriptor be entity Source #

Produce the corresponding DatabaseEntityDescriptor

unChecked :: Lens' (CheckedDatabaseEntityDescriptor be entity) (DatabaseEntityDescriptor be entity) Source #

A lens to access the internal unchecked descriptor

collectEntityChecks :: CheckedDatabaseEntityDescriptor be entity -> [SomeDatabasePredicate] Source #

Produce the set of DatabasePredicates that apply to this entity

checkedDbEntityAuto :: CheckedDatabaseEntityDefaultRequirements be entity => Text -> CheckedDatabaseEntityDescriptor be entity Source #

Like dbEntityAuto but for checked databases. Most often, this wraps dbEntityAuto and provides some means to generate DatabasePredicates

Instances
Beamable tbl => IsCheckedDatabaseEntity be (TableEntity tbl) Source # 
Instance details

Defined in Database.Beam.Migrate.Types.CheckedEntities

IsCheckedDatabaseEntity be (DomainTypeEntity ty) Source # 
Instance details

Defined in Database.Beam.Migrate.Types.CheckedEntities

data CheckedDatabaseEntity be (db :: (* -> *) -> *) entityType where Source #

Like DatabaseEntity but for checked databases

unCheckDatabase :: forall be db. Database be db => CheckedDatabaseSettings be db -> DatabaseSettings be db Source #

Convert a CheckedDatabaseSettings to a regular DatabaseSettings. The return value is suitable for use in any regular beam query or DML statement.

collectChecks :: forall be db. Database be db => CheckedDatabaseSettings be db -> [SomeDatabasePredicate] Source #

A beam-migrate database schema is defined completely by the set of predicates that apply to it. This function allows you to access this definition for a CheckedDatabaseSettings object.

Modifyinging checked entities

data CheckedFieldModification tbl a Source #

Purposefully opaque type describing how to modify a table field. Used to parameterize the second argument to modifyCheckedTable. For now, the only way to construct a value is the IsString instance, which allows you to rename the field.

modifyCheckedTable :: (Text -> Text) -> tbl (CheckedFieldModification tbl) -> EntityModification (CheckedDatabaseEntity be db) be (TableEntity tbl) Source #

Modify a checked table.

The first argument is a function that takes the original table name as input and produces a new table name.

The second argument gives instructions on how to rename each field in the table. Use checkedTableModification to create a value of this type which does no renaming. Each field in the table supplied here has the type CheckedFieldModification. Most commonly, the programmer will use the OverloadedStrings instance to provide a new name.

Examples

Rename a table, without renaming any of its fields:

modifyCheckedTable (_ -> NewTblNm) checkedTableModification

Modify a table, renaming the field called _field1 in Haskell to FirstName. Note that below, FirstName represents a CheckedFieldModification object.

modifyCheckedTable id (checkedTableModification { _field1 = FirstName })

checkedTableModification :: forall tbl. Beamable tbl => tbl (CheckedFieldModification tbl) Source #

Produce a table field modification that does nothing

Most commonly supplied as the second argument to modifyCheckedTable when you just want to rename the table, not the fields.

Predicates

class (Typeable p, Hashable p, Eq p) => DatabasePredicate p where Source #

A predicate is a type that describes some condition that the database schema must meet. Beam represents database schemas as the set of all predicates that apply to a database schema. The Hashable and Eq instances allow us to build HashSets of predicates to represent schemas in this way.

Methods

englishDescription :: p -> String Source #

An english language description of this predicate. For example, "There is a table named TableName"

predicateSpecificity :: proxy p -> PredicateSpecificity Source #

Whether or not this predicate applies to all backends or only one backend. This is used when attempting to translate schemas between backends. If you are unsure, provide PredicateSpecificityOnlyBackend along with an identifier unique to your backend.

serializePredicate :: p -> Value Source #

Serialize a predicate to a JSON Value.

predicateCascadesDropOn :: DatabasePredicate p' => p -> p' -> Bool Source #

Some predicates require other predicates to be true. For example, in order for a table to have a column, that table must exist. This function takes in the current predicate and another arbitrary database predicate. It should return True if this predicate needs the other predicate to be true in order to exist.

By default, this simply returns False, which makes sense for many predicates.

Instances
DatabasePredicate TableHasPrimaryKey Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

DatabasePredicate TableExistsPredicate Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

(Typeable be, BeamMigrateOnlySqlBackend be, Hashable (BeamSqlBackendColumnConstraintDefinitionSyntax be)) => DatabasePredicate (TableColumnHasConstraint be) Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

(Typeable be, BeamMigrateOnlySqlBackend be, Hashable (BeamMigrateSqlBackendDataTypeSyntax be)) => DatabasePredicate (TableHasColumn be) Source # 
Instance details

Defined in Database.Beam.Migrate.Checks

data SomeDatabasePredicate where Source #

A Database predicate is a value of any type which satisfies DatabasePredicate. We often want to store these in lists and sets, so we need a monomorphic container that can store these polymorphic values.

data PredicateSpecificity Source #

Some predicates make sense in any backend. Others only make sense in one. This denotes the difference.

Instances
Eq PredicateSpecificity Source # 
Instance details

Defined in Database.Beam.Migrate.Types.Predicates

Show PredicateSpecificity Source # 
Instance details

Defined in Database.Beam.Migrate.Types.Predicates

Generic PredicateSpecificity Source # 
Instance details

Defined in Database.Beam.Migrate.Types.Predicates

Associated Types

type Rep PredicateSpecificity :: Type -> Type #

Hashable PredicateSpecificity Source # 
Instance details

Defined in Database.Beam.Migrate.Types.Predicates

ToJSON PredicateSpecificity Source # 
Instance details

Defined in Database.Beam.Migrate.Types.Predicates

FromJSON PredicateSpecificity Source # 
Instance details

Defined in Database.Beam.Migrate.Types.Predicates

type Rep PredicateSpecificity Source # 
Instance details

Defined in Database.Beam.Migrate.Types.Predicates

type Rep PredicateSpecificity = D1 (MetaData "PredicateSpecificity" "Database.Beam.Migrate.Types.Predicates" "beam-migrate-0.4.0.1-LFWMnC8rnYz3hNNRXqkW0o" False) (C1 (MetaCons "PredicateSpecificityOnlyBackend" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "PredicateSpecificityAllBackends" PrefixI False) (U1 :: Type -> Type))

data QualifiedName Source #

A name in a schema

Constructors

QualifiedName (Maybe Text) Text 
Instances
Eq QualifiedName Source # 
Instance details

Defined in Database.Beam.Migrate.Types.Predicates

Ord QualifiedName Source # 
Instance details

Defined in Database.Beam.Migrate.Types.Predicates

Show QualifiedName Source # 
Instance details

Defined in Database.Beam.Migrate.Types.Predicates

Hashable QualifiedName Source # 
Instance details

Defined in Database.Beam.Migrate.Types.Predicates

ToJSON QualifiedName Source # 
Instance details

Defined in Database.Beam.Migrate.Types.Predicates

FromJSON QualifiedName Source # 
Instance details

Defined in Database.Beam.Migrate.Types.Predicates

Entity checks

newtype TableCheck Source #

A predicate that depends on the name of a table as well as its fields

Constructors

TableCheck (forall tbl. Table tbl => QualifiedName -> tbl (TableField tbl) -> SomeDatabasePredicate) 

newtype DomainCheck Source #

A predicate that depends on the name of a domain type

newtype FieldCheck Source #

A predicate that depends on the name of a table and one of its fields

Migrations

data MigrationStep be next where Source #

Represents a particular step in a migration

Constructors

MigrationStep :: Text -> Migration be a -> (a -> next) -> MigrationStep be next 
Instances
Functor (MigrationStep be) Source # 
Instance details

Defined in Database.Beam.Migrate.Types

Methods

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

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

newtype MigrationSteps be from to Source #

A series of MigrationSteps that take a database from the schema in from to the one in to. Use the migrationStep function and the arrow interface to sequence MigrationSteps.

Constructors

MigrationSteps (Kleisli (F (MigrationStep be)) from to) 
Instances
Arrow (MigrationSteps be) Source # 
Instance details

Defined in Database.Beam.Migrate.Types

Methods

arr :: (b -> c) -> MigrationSteps be b c #

first :: MigrationSteps be b c -> MigrationSteps be (b, d) (c, d) #

second :: MigrationSteps be b c -> MigrationSteps be (d, b) (d, c) #

(***) :: MigrationSteps be b c -> MigrationSteps be b' c' -> MigrationSteps be (b, b') (c, c') #

(&&&) :: MigrationSteps be b c -> MigrationSteps be b c' -> MigrationSteps be b (c, c') #

Category (MigrationSteps be :: Type -> Type -> Type) Source # 
Instance details

Defined in Database.Beam.Migrate.Types

Methods

id :: MigrationSteps be a a #

(.) :: MigrationSteps be b c -> MigrationSteps be a b -> MigrationSteps be a c #

type Migration be = F (MigrationF be) Source #

A sequence of potentially reversible schema update commands

data MigrationF be next where Source #

Free monadic function for Migrations

Constructors

MigrationRunCommand 

Fields

Instances
Functor (MigrationF be) Source # 
Instance details

Defined in Database.Beam.Migrate.Types

Methods

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

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

data MigrationCommand be Source #

A migration command along with metadata on whether the command can lose data

Constructors

MigrationCommand 

Fields

data MigrationDataLoss Source #

Information on whether a MigrationCommand loses data. You can monoidally combine these to get the potential data loss for a sequence of commands.

Constructors

MigrationLosesData

The command loses data

MigrationKeepsData

The command keeps all data

runMigrationSteps Source #

Arguments

:: Monad m 
=> Int

Zero-based index of the first step to run

-> Maybe Int

Index of the last step to run, or Nothing to run every step

-> MigrationSteps be () a

The set of steps to run

-> (forall a'. Int -> Text -> Migration be a' -> m a')

Callback for each step. Called with the step index, the step description and the migration.

-> m a 

Run the migration steps between the given indices, using a custom execution function.

runMigrationSilenced :: Migration be a -> a Source #

Get the result of a migration, without running any steps

executeMigration :: Applicative m => (BeamSqlBackendSyntax be -> m ()) -> Migration be a -> m a Source #

Execute a given migration, provided a command to execute arbitrary syntax. You usually use this with runNoReturn.

eraseMigrationType :: a -> MigrationSteps be a a' -> MigrationSteps be () () Source #

Remove the explicit source and destination schemas from a MigrationSteps object

migrationStep :: Text -> (a -> Migration be a') -> MigrationSteps be a a' Source #

Create a MigrationSteps from the given description and migration function.

upDown :: BeamSqlBackendSyntax be -> Maybe (BeamSqlBackendSyntax be) -> Migration be () Source #

Given a command in the forward direction, and an optional one in the reverse direction, construct a Migration that performs the given command. Multiple commands can be sequenced monadically.

migrationDataLoss :: Migration be a -> MigrationDataLoss Source #

Given a migration, get the potential data loss, if it's run top-down

migrateScript Source #

Arguments

:: (Monoid m, Semigroup m, BeamSqlBackend be) 
=> (Text -> m)

Called at the beginning of each MigrationStep with the step description

-> (BeamSqlBackendSyntax be -> m)

Called for each command in the migration step

-> MigrationSteps be () a

The set of steps to run

-> m 

Given functions to render a migration step description and the underlying syntax, create a script for the given MigrationSteps.

evaluateDatabase :: forall be a. MigrationSteps be () a -> a Source #

Run a MigrationSteps without executing any of the commands against a database.

stepNames :: forall be a. MigrationSteps be () a -> [Text] Source #

Collect the names of all steps in hte given MigrationSteps