Copyright | (c) Eitan Chatav 2017 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
This module defines a Migration
type to safely
change the schema of your database over time. Let's see an example!
First turn on some extensions.
>>>
:set -XDataKinds -XOverloadedLabels
>>>
:set -XOverloadedStrings -XFlexibleContexts -XTypeOperators
Next, let's define our TableType
s.
>>>
:{
type UsersTable = '[ "pk_users" ::: 'PrimaryKey '["id"] ] :=> '[ "id" ::: 'Def :=> 'NotNull 'PGint4 , "name" ::: 'NoDef :=> 'NotNull 'PGtext ] :}
>>>
:{
type EmailsTable = '[ "pk_emails" ::: 'PrimaryKey '["id"] , "fk_user_id" ::: 'ForeignKey '["user_id"] "users" '["id"] ] :=> '[ "id" ::: 'Def :=> 'NotNull 'PGint4 , "user_id" ::: 'NoDef :=> 'NotNull 'PGint4 , "email" ::: 'NoDef :=> 'Null 'PGtext ] :}
Now we can define some Migration
s to make our tables.
>>>
:{
let makeUsers :: Migration Definition (Public '[]) '["public" ::: '["users" ::: 'Table UsersTable]] makeUsers = Migration { name = "make users table" , up = createTable #users ( serial `as` #id :* notNullable text `as` #name ) ( primaryKey #id `as` #pk_users ) , down = dropTable #users } :}
>>>
:{
let makeEmails :: Migration Definition '["public" ::: '["users" ::: 'Table UsersTable]] '["public" ::: '["users" ::: 'Table UsersTable, "emails" ::: 'Table EmailsTable]] makeEmails = Migration { name = "make emails table" , up = createTable #emails ( serial `as` #id :* notNullable int `as` #user_id :* nullable text `as` #email ) ( primaryKey #id `as` #pk_emails :* foreignKey #user_id #users #id OnDeleteCascade OnUpdateCascade `as` #fk_user_id ) , down = dropTable #emails } :}
Now that we have a couple migrations we can chain them together into an AlignedList
.
>>>
let migrations = makeUsers :>> makeEmails :>> Done
Now run the migrations.
>>>
import Control.Monad.IO.Class
>>>
:{
withConnection "host=localhost port=5432 dbname=exampledb" $ manipulate (UnsafeManipulation "SET client_min_messages TO WARNING;") -- suppress notices & pqThen (liftIO (putStrLn "Migrate")) & pqThen (migrateUp migrations) & pqThen (liftIO (putStrLn "Rollback")) & pqThen (migrateDown migrations) :} Migrate Rollback
We can also create a simple executable using defaultMain
.
>>>
let main = defaultMain "host=localhost port=5432 dbname=exampledb" migrations
>>>
withArgs [] main
Invalid command: "". Use: migrate to run all available migrations rollback to rollback all available migrations status to display migrations run and migrations left to run
>>>
withArgs ["status"] main
Migrations already run: None Migrations left to run: - make users table - make emails table
>>>
withArgs ["migrate"] main
Migrations already run: - make users table - make emails table Migrations left to run: None
>>>
withArgs ["rollback"] main
Migrations already run: None Migrations left to run: - make users table - make emails table
In addition to enabling Migration
s using pure SQL Definition
s for
the up
and down
instructions, you can also perform impure IO
actions
by using a Migration
s over the Terminally
PQ
IO
category.
Synopsis
- data Migration p schemas0 schemas1 = Migration {}
- class Category p => Migratory p where
- migrateUp :: AlignedList (Migration p) schemas0 schemas1 -> PQ schemas0 schemas1 IO ()
- migrateDown :: AlignedList (Migration p) schemas0 schemas1 -> PQ schemas1 schemas0 IO ()
- newtype Terminally trans monad x0 x1 = Terminally {
- runTerminally :: trans x0 x1 monad ()
- terminally :: Functor (trans x0 x1 monad) => trans x0 x1 monad ignore -> Terminally trans monad x0 x1
- pureMigration :: Migration Definition schemas0 schemas1 -> Migration (Terminally PQ IO) schemas0 schemas1
- type MigrationsTable = '["migrations_unique_name" ::: Unique '["name"]] :=> '["name" ::: (NoDef :=> NotNull PGtext), "executed_at" ::: (Def :=> NotNull PGtimestamptz)]
- defaultMain :: Migratory p => ByteString -> AlignedList (Migration p) db0 db1 -> IO ()
Migration
data Migration p schemas0 schemas1 Source #
A Migration
is a named "isomorphism" over a given category.
It should contain an inverse pair of up
and down
instructions and a unique name
.
Instances
Generic (Migration p schemas0 schemas1) Source # | |
type Rep (Migration p schemas0 schemas1) Source # | |
Defined in Squeal.PostgreSQL.Migration type Rep (Migration p schemas0 schemas1) = D1 (MetaData "Migration" "Squeal.PostgreSQL.Migration" "squeal-postgresql-0.5.2.0-4fAomBtpMjd6mRwLthA4w2" False) (C1 (MetaCons "Migration" PrefixI True) (S1 (MetaSel (Just "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Just "up") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (p schemas0 schemas1)) :*: S1 (MetaSel (Just "down") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (p schemas1 schemas0))))) |
class Category p => Migratory p where Source #
A Migratory
p
is a Category
for which one can execute or rewind
an AlignedList
of Migration
s over p
. This includes the category of pure
SQL Definition
s and the category of impure Terminally
PQ
IO
actions.
migrateUp :: AlignedList (Migration p) schemas0 schemas1 -> PQ schemas0 schemas1 IO () Source #
Run an AlignedList
of Migration
s.
Create the MigrationsTable
as public.schema_migrations
if it does not already exist.
In one transaction, for each each Migration
query to see if the Migration
has been executed;
if not, up
the Migration
and insert its name
in the MigrationsTable
.
migrateDown :: AlignedList (Migration p) schemas0 schemas1 -> PQ schemas1 schemas0 IO () Source #
Rewind an AlignedList
of Migration
s.
Create the MigrationsTable
as public.schema_migrations
if it does not already exist.
In one transaction, for each each Migration
query to see if the Migration
has been executed;
if so, down
the Migration
and delete its name
in the MigrationsTable
.
Instances
Migratory Definition Source # | |
Defined in Squeal.PostgreSQL.Migration migrateUp :: AlignedList (Migration Definition) schemas0 schemas1 -> PQ schemas0 schemas1 IO () Source # migrateDown :: AlignedList (Migration Definition) schemas0 schemas1 -> PQ schemas1 schemas0 IO () Source # | |
Migratory (Terminally PQ IO) Source # | |
Defined in Squeal.PostgreSQL.Migration migrateUp :: AlignedList (Migration (Terminally PQ IO)) schemas0 schemas1 -> PQ schemas0 schemas1 IO () Source # migrateDown :: AlignedList (Migration (Terminally PQ IO)) schemas0 schemas1 -> PQ schemas1 schemas0 IO () Source # |
newtype Terminally trans monad x0 x1 Source #
Terminally
turns an indexed monad transformer and the monad it transforms
into a category by restricting the return type to ()
and permuting the type variables.
This is similar to how applying a monad to ()
yields a monoid.
Since a Terminally
action has a trivial return value, the only reason
to run one is for the side effects, in particular database and other IO effects.
Terminally | |
|
Instances
(IndexedMonadTransPQ trans, Monad monad, forall (x0 :: SchemasType) (x1 :: SchemasType). x0 ~ x1 => Monad (trans x0 x1 monad)) => Category (Terminally trans monad :: SchemasType -> SchemasType -> Type) Source # | |
Defined in Squeal.PostgreSQL.Migration id :: Terminally trans monad a a # (.) :: Terminally trans monad b c -> Terminally trans monad a b -> Terminally trans monad a c # | |
Migratory (Terminally PQ IO) Source # | |
Defined in Squeal.PostgreSQL.Migration migrateUp :: AlignedList (Migration (Terminally PQ IO)) schemas0 schemas1 -> PQ schemas0 schemas1 IO () Source # migrateDown :: AlignedList (Migration (Terminally PQ IO)) schemas0 schemas1 -> PQ schemas1 schemas0 IO () Source # | |
Generic (Terminally trans monad x0 x1) Source # | |
Defined in Squeal.PostgreSQL.Migration type Rep (Terminally trans monad x0 x1) :: Type -> Type # from :: Terminally trans monad x0 x1 -> Rep (Terminally trans monad x0 x1) x # to :: Rep (Terminally trans monad x0 x1) x -> Terminally trans monad x0 x1 # | |
type Rep (Terminally trans monad x0 x1) Source # | |
Defined in Squeal.PostgreSQL.Migration type Rep (Terminally trans monad x0 x1) = D1 (MetaData "Terminally" "Squeal.PostgreSQL.Migration" "squeal-postgresql-0.5.2.0-4fAomBtpMjd6mRwLthA4w2" True) (C1 (MetaCons "Terminally" PrefixI True) (S1 (MetaSel (Just "runTerminally") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (trans x0 x1 monad ())))) |
terminally :: Functor (trans x0 x1 monad) => trans x0 x1 monad ignore -> Terminally trans monad x0 x1 Source #
terminally
ignores the output of a computation, returning ()
and
wrapping it up into a Terminally
. You can lift an action in the base monad
by using terminally . lift
.
pureMigration :: Migration Definition schemas0 schemas1 -> Migration (Terminally PQ IO) schemas0 schemas1 Source #
A pureMigration
turns a Migration
involving only pure SQL
Definition
s into a Migration
that may be combined with arbitrary IO
.
type MigrationsTable = '["migrations_unique_name" ::: Unique '["name"]] :=> '["name" ::: (NoDef :=> NotNull PGtext), "executed_at" ::: (Def :=> NotNull PGtimestamptz)] Source #
The TableType
for a Squeal migration.
:: Migratory p | |
=> ByteString | connection string |
-> AlignedList (Migration p) db0 db1 | migrations |
-> IO () |
defaultMain
creates a simple executable
from a connection string and a list of Migration
s.