persistent-migration-0.0.1: Manual migrations for the persistent library

MaintainerBrandon Chinn <brandonchinn178@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Database.Persist.Migration.Internal

Description

Defines a migration framework for the persistent library.

Synopsis

Documentation

type Version = Int Source #

The version of a database. An operation migrates from the given version to another version.

The version must be increasing, such that the lowest version is the first version and the highest version is the most up-to-date version.

type OperationPath = (Version, Version) Source #

The path that an operation takes.

(~>) :: Int -> Int -> OperationPath Source #

An infix constructor for OperationPath.

data Operation Source #

An operation that can be migrated.

Constructors

Migrateable op => Operation 

Fields

type Migration = [Operation] Source #

A migration is simply a list of operations.

data MigrateBackend Source #

The backend to migrate with.

Constructors

MigrateBackend 

Fields

getCurrVersion :: MonadIO m => MigrateBackend -> SqlPersistT m (Maybe Version) Source #

Get the current version of the database, or Nothing if none exists.

getMigratePlan :: Migration -> Maybe Version -> Either (Version, Version) Migration Source #

Get the migration plan given the current state of the database.

getFirstVersion :: Migration -> Version Source #

Get the first version in the given migration.

getLatestVersion :: Migration -> Version Source #

Get the most up-to-date version in the given migration.

newtype MigrateSettings Source #

Settings to customize migration steps.

Constructors

MigrateSettings 

Fields

defaultSettings :: MigrateSettings Source #

Default migration settings.

validateMigration :: Migration -> Either String () Source #

Validate the given migration.

runMigration :: MonadIO m => MigrateBackend -> MigrateSettings -> Migration -> SqlPersistT m () Source #

Run the given migration. After successful completion, saves the migration to the database.

getMigration :: MonadIO m => MigrateBackend -> MigrateSettings -> Migration -> SqlPersistT m [Text] Source #

Get the SQL queries for the given migration.

rawExecute' :: MonadIO m => [Text] -> SqlPersistT m () Source #

Execute the given SQL strings.

data CreateTable Source #

An operation to create a table according to the specified schema.

Constructors

CreateTable 

data AddColumn Source #

An operation to add the given column to an existing table.

Constructors

AddColumn 

Fields

newtype DropColumn Source #

An operation to drop the given column to an existing table.

Constructors

DropColumn 

data RawOperation Source #

A custom operation that can be defined manually.

RawOperations should primarily use rawSql and rawExecute from the persistent library. If the operation depends on the backend being run, query connRDBMS from the SqlBackend:

asks connRDBMS >>= case
  "sqlite" -> ...
  _ -> return ()

Constructors

RawOperation 

Fields

data NoOp Source #

A noop operation.

Constructors

NoOp 

type ColumnIdentifier = (Text, Text) Source #

A column identifier, table.column

dotted :: ColumnIdentifier -> Text Source #

Make a ColumnIdentifier displayable.

data Column Source #

The definition for a Column in a SQL database.

Constructors

Column 

Instances

validateColumn :: Column -> Either String () Source #

Validate a Column.

data ColumnProp Source #

A property for a Column.

Constructors

NotNull

Makes a column non-nullable (defaults to nullable)

References ColumnIdentifier

Mark this column as a foreign key to the given column

AutoIncrement

Makes a column auto-incrementing

Instances

Eq ColumnProp Source # 
Data ColumnProp Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ColumnProp -> c ColumnProp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ColumnProp #

toConstr :: ColumnProp -> Constr #

dataTypeOf :: ColumnProp -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ColumnProp) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColumnProp) #

gmapT :: (forall b. Data b => b -> b) -> ColumnProp -> ColumnProp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColumnProp -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColumnProp -> r #

gmapQ :: (forall d. Data d => d -> u) -> ColumnProp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ColumnProp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ColumnProp -> m ColumnProp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ColumnProp -> m ColumnProp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ColumnProp -> m ColumnProp #

Show ColumnProp Source # 

data TableConstraint Source #

Table constraints in a CREATE query.

Constructors

PrimaryKey [Text]

PRIMARY KEY (col1, col2, ...)

Unique Text [Text]

CONSTRAINT name UNIQUE (col1, col2, ...)

Instances

Data TableConstraint Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableConstraint -> c TableConstraint #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableConstraint #

toConstr :: TableConstraint -> Constr #

dataTypeOf :: TableConstraint -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TableConstraint) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableConstraint) #

gmapT :: (forall b. Data b => b -> b) -> TableConstraint -> TableConstraint #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableConstraint -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableConstraint -> r #

gmapQ :: (forall d. Data d => d -> u) -> TableConstraint -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TableConstraint -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TableConstraint -> m TableConstraint #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TableConstraint -> m TableConstraint #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TableConstraint -> m TableConstraint #

Show TableConstraint Source # 

getConstraintColumns :: TableConstraint -> [Text] Source #

Get the columns defined in the given TableConstraint.