Copyright | (c) Eitan Chatav 2019 |
---|---|
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"] "public" "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.
Migration
s are parameterized giving the option of a
- pure one-way
Migration
Definition
- impure one-way
Migration
(
Indexed
PQ
IO
)
- pure reversible
Migration
(
IsoQ
Definition
)
- impure reversible
Migration
(
IsoQ
(
Indexed
PQ
IO
)
)
For this example, we'll use pure reversible Migration
s.
>>>
:{
let makeUsers :: Migration (IsoQ Definition) '["public" ::: '[]] '["public" ::: '["users" ::: 'Table UsersTable]] makeUsers = Migration "make users table" IsoQ { up = createTable #users ( serial `as` #id :* notNullable text `as` #name ) ( primaryKey #id `as` #pk_users ) , down = dropTable #users } :}
>>>
:{
let makeEmails :: Migration (IsoQ Definition) '["public" ::: '["users" ::: 'Table UsersTable]] '["public" ::: '["users" ::: 'Table UsersTable, "emails" ::: 'Table EmailsTable]] makeEmails = Migration "make emails table" IsoQ { 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 (OnDelete Cascade) (OnUpdate Cascade) `as` #fk_user_id ) , down = dropTable #emails } :}
Now that we have a couple migrations we can chain them together into a Path
.
>>>
let migrations = makeUsers :>> makeEmails :>> Done
Now run the migrations.
>>>
import Control.Monad.IO.Class
>>>
:{
withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $ 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 mainMigrateIso
.
>>>
let main = mainMigrateIso "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" 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
migrations, you can also perform impure IO
actions
by using a Migration
s over the Indexed
PQ
IO
category.
Synopsis
- data Migration def db0 db1 = Migration {
- migrationName :: Text
- migrationDef :: def db0 db1
- class (Category def, Category run) => Migratory def run | def -> run where
- runMigrations :: Path (Migration def) db0 db1 -> run db0 db1
- migrate :: Migratory def (Indexed PQ IO ()) => Path (Migration def) db0 db1 -> PQ db0 db1 IO ()
- migrateUp :: Migratory def (IsoQ (Indexed PQ IO ())) => Path (Migration def) db0 db1 -> PQ db0 db1 IO ()
- migrateDown :: Migratory def (IsoQ (Indexed PQ IO ())) => Path (Migration def) db0 db1 -> PQ db1 db0 IO ()
- type MigrationsTable = '["migrations_unique_name" ::: 'Unique '["name"]] :=> '["name" ::: ('NoDef :=> 'NotNull 'PGtext), "executed_at" ::: ('Def :=> 'NotNull 'PGtimestamptz)]
- mainMigrate :: Migratory p (Indexed PQ IO ()) => ByteString -> Path (Migration p) db0 db1 -> IO ()
- mainMigrateIso :: Migratory (IsoQ def) (IsoQ (Indexed PQ IO ())) => ByteString -> Path (Migration (IsoQ def)) db0 db1 -> IO ()
- data IsoQ (c :: k -> k -> Type) (x :: k) (y :: k) = IsoQ {}
Migration
data Migration def db0 db1 Source #
A Migration
consists of a name and a migration definition.
Migration | |
|
Instances
QFunctor (Migration :: (k2 -> k3 -> Type) -> k2 -> k3 -> Type) Source # | |
Defined in Squeal.PostgreSQL.Session.Migration | |
Generic (Migration def db0 db1) Source # | |
type Rep (Migration def db0 db1) Source # | |
Defined in Squeal.PostgreSQL.Session.Migration type Rep (Migration def db0 db1) = D1 ('MetaData "Migration" "Squeal.PostgreSQL.Session.Migration" "squeal-postgresql-0.9.0.0-D17NIjlcsGRAwJTaCTXyvM" 'False) (C1 ('MetaCons "Migration" 'PrefixI 'True) (S1 ('MetaSel ('Just "migrationName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "migrationDef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (def db0 db1)))) |
class (Category def, Category run) => Migratory def run | def -> run where Source #
Instances
Migratory Definition (Indexed PQ IO ()) Source # | pure migrations |
Defined in Squeal.PostgreSQL.Session.Migration runMigrations :: forall (db0 :: k) (db1 :: k). Path (Migration Definition) db0 db1 -> Indexed PQ IO () db0 db1 Source # | |
Migratory (IsoQ Definition) (IsoQ (Indexed PQ IO ())) Source # | pure rewindable migrations |
Defined in Squeal.PostgreSQL.Session.Migration | |
Migratory (IsoQ (Indexed PQ IO ())) (IsoQ (Indexed PQ IO ())) Source # | impure rewindable migrations |
Migratory (OpQ Definition) (OpQ (Indexed PQ IO ())) Source # | pure rewinds |
Defined in Squeal.PostgreSQL.Session.Migration | |
Migratory (OpQ (Indexed PQ IO ())) (OpQ (Indexed PQ IO ())) Source # | impure rewinds |
Migratory (Indexed PQ IO ()) (Indexed PQ IO ()) Source # | impure migrations |
migrate :: Migratory def (Indexed PQ IO ()) => Path (Migration def) db0 db1 -> PQ db0 db1 IO () Source #
Run migrations.
migrateUp :: Migratory def (IsoQ (Indexed PQ IO ())) => Path (Migration def) db0 db1 -> PQ db0 db1 IO () Source #
Run rewindable migrations.
migrateDown :: Migratory def (IsoQ (Indexed PQ IO ())) => Path (Migration def) db0 db1 -> PQ db1 db0 IO () Source #
Rewind migrations.
type MigrationsTable = '["migrations_unique_name" ::: 'Unique '["name"]] :=> '["name" ::: ('NoDef :=> 'NotNull 'PGtext), "executed_at" ::: ('Def :=> 'NotNull 'PGtimestamptz)] Source #
The TableType
for a Squeal migration.
Executable
:: Migratory p (Indexed PQ IO ()) | |
=> ByteString | connection string |
-> Path (Migration p) db0 db1 | migrations |
-> IO () |
mainMigrate
creates a simple executable
from a connection string and a Path
of Migration
s.
:: Migratory (IsoQ def) (IsoQ (Indexed PQ IO ())) | |
=> ByteString | connection string |
-> Path (Migration (IsoQ def)) db0 db1 | migrations |
-> IO () |
mainMigrateIso
creates a simple executable
from a connection string and a Path
of Migration
IsoQ
s.
Re-export
data IsoQ (c :: k -> k -> Type) (x :: k) (y :: k) #
Arrows of IsoQ
are bidirectional edges.
Instances
QFunctor (IsoQ :: (k -> k -> Type) -> k -> k -> Type) | |
Defined in Data.Quiver.Functor | |
Category c => Category (IsoQ c :: k -> k -> Type) | |
Migratory (IsoQ Definition) (IsoQ (Indexed PQ IO ())) Source # | pure rewindable migrations |
Defined in Squeal.PostgreSQL.Session.Migration | |
Migratory (IsoQ (Indexed PQ IO ())) (IsoQ (Indexed PQ IO ())) Source # | impure rewindable migrations |
(Eq (c x y), Eq (c y x)) => Eq (IsoQ c x y) | |
(Ord (c x y), Ord (c y x)) => Ord (IsoQ c x y) | |
(Show (c x y), Show (c y x)) => Show (IsoQ c x y) | |
(Category c, x ~ y) => Semigroup (IsoQ c x y) | |
(Category c, x ~ y) => Monoid (IsoQ c x y) | |