squeal-postgresql-0.6.0.0: Squeal PostgreSQL Library

Copyright(c) Eitan Chatav 2019
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Squeal.PostgreSQL.Session.Migration

Contents

Description

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 TableTypes.

>>> :{
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 Migrations to make our tables.

Migrations are parameterized giving the option of a

For this example, we'll use pure reversible Migrations.

>>> :{
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
              OnDeleteCascade OnUpdateCascade `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" $
  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" 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 Migrations using pure SQL Definitions for the up and down migrations, you can also perform impure IO actions by using a Migrations over the Indexed PQ IO category.

Synopsis

Migration

data Migration def db0 db1 Source #

A Migration consists of a name and a migration definition.

Constructors

Migration 

Fields

Instances
QFunctor (Migration :: (k2 -> k3 -> Type) -> k2 -> k3 -> Type) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Migration

Methods

qmap :: (forall (x1 :: k) (y1 :: k1). p x1 y1 -> q x1 y1) -> Migration p x y -> Migration q x y #

Generic (Migration def db0 db1) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Migration

Associated Types

type Rep (Migration def db0 db1) :: Type -> Type #

Methods

from :: Migration def db0 db1 -> Rep (Migration def db0 db1) x #

to :: Rep (Migration def db0 db1) x -> Migration def db0 db1 #

type Rep (Migration def db0 db1) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Migration

type Rep (Migration def db0 db1) = D1 (MetaData "Migration" "Squeal.PostgreSQL.Session.Migration" "squeal-postgresql-0.6.0.0-56EGnKmL3FAInHQPvmCKa1" False) (C1 (MetaCons "Migration" PrefixI True) (S1 (MetaSel (Just "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "migration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (def db0 db1))))

class (Category def, Category run) => Migratory def run | def -> run where Source #

A Migratory Category can run or possibly rewind a Path of Migrations.

Methods

runMigrations :: Path (Migration def) db0 db1 -> run db0 db1 Source #

Run a Path of Migrations.

Instances
Migratory Definition (Indexed PQ IO ()) Source #

pure migrations

Instance details

Defined in Squeal.PostgreSQL.Session.Migration

Methods

runMigrations :: Path (Migration Definition) db0 db1 -> Indexed PQ IO () db0 db1 Source #

Migratory (IsoQ Definition) (IsoQ (Indexed PQ IO ())) Source #

pure rewindable migrations

Instance details

Defined in Squeal.PostgreSQL.Session.Migration

Methods

runMigrations :: Path (Migration (IsoQ Definition)) db0 db1 -> IsoQ (Indexed PQ IO ()) db0 db1 Source #

Migratory (IsoQ (Indexed PQ IO ())) (IsoQ (Indexed PQ IO ())) Source #

impure rewindable migrations

Instance details

Defined in Squeal.PostgreSQL.Session.Migration

Methods

runMigrations :: Path (Migration (IsoQ (Indexed PQ IO ()))) db0 db1 -> IsoQ (Indexed PQ IO ()) db0 db1 Source #

Migratory (OpQ Definition) (OpQ (Indexed PQ IO ())) Source #

pure rewinds

Instance details

Defined in Squeal.PostgreSQL.Session.Migration

Methods

runMigrations :: Path (Migration (OpQ Definition)) db0 db1 -> OpQ (Indexed PQ IO ()) db0 db1 Source #

Migratory (OpQ (Indexed PQ IO ())) (OpQ (Indexed PQ IO ())) Source #

impure rewinds

Instance details

Defined in Squeal.PostgreSQL.Session.Migration

Methods

runMigrations :: Path (Migration (OpQ (Indexed PQ IO ()))) db0 db1 -> OpQ (Indexed PQ IO ()) db0 db1 Source #

Migratory (Indexed PQ IO ()) (Indexed PQ IO ()) Source #

impure migrations

Instance details

Defined in Squeal.PostgreSQL.Session.Migration

Methods

runMigrations :: Path (Migration (Indexed PQ IO ())) db0 db1 -> Indexed PQ IO () db0 db1 Source #

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

mainMigrate Source #

Arguments

:: 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 Migrations.

mainMigrateIso Source #

Arguments

:: 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 IsoQs.

Re-export

data IsoQ (c :: k -> k -> Type) (x :: k) (y :: k) :: forall k. (k -> k -> Type) -> k -> k -> Type #

Arrows of IsoQ are bidirectional edges.

Constructors

IsoQ 

Fields

Instances
QFunctor (IsoQ :: (k -> k -> Type) -> k -> k -> Type) 
Instance details

Defined in Data.Quiver.Functor

Methods

qmap :: (forall (x1 :: k0) (y1 :: k1). p x1 y1 -> q x1 y1) -> IsoQ p x y -> IsoQ q x y #

Category c => Category (IsoQ c :: k -> k -> Type) 
Instance details

Defined in Data.Quiver

Methods

id :: IsoQ c a a #

(.) :: IsoQ c b c0 -> IsoQ c a b -> IsoQ c a c0 #

Migratory (IsoQ Definition) (IsoQ (Indexed PQ IO ())) Source #

pure rewindable migrations

Instance details

Defined in Squeal.PostgreSQL.Session.Migration

Methods

runMigrations :: Path (Migration (IsoQ Definition)) db0 db1 -> IsoQ (Indexed PQ IO ()) db0 db1 Source #

Migratory (IsoQ (Indexed PQ IO ())) (IsoQ (Indexed PQ IO ())) Source #

impure rewindable migrations

Instance details

Defined in Squeal.PostgreSQL.Session.Migration

Methods

runMigrations :: Path (Migration (IsoQ (Indexed PQ IO ()))) db0 db1 -> IsoQ (Indexed PQ IO ()) db0 db1 Source #

(Eq (c x y), Eq (c y x)) => Eq (IsoQ c x y) 
Instance details

Defined in Data.Quiver

Methods

(==) :: IsoQ c x y -> IsoQ c x y -> Bool #

(/=) :: IsoQ c x y -> IsoQ c x y -> Bool #

(Ord (c x y), Ord (c y x)) => Ord (IsoQ c x y) 
Instance details

Defined in Data.Quiver

Methods

compare :: IsoQ c x y -> IsoQ c x y -> Ordering #

(<) :: IsoQ c x y -> IsoQ c x y -> Bool #

(<=) :: IsoQ c x y -> IsoQ c x y -> Bool #

(>) :: IsoQ c x y -> IsoQ c x y -> Bool #

(>=) :: IsoQ c x y -> IsoQ c x y -> Bool #

max :: IsoQ c x y -> IsoQ c x y -> IsoQ c x y #

min :: IsoQ c x y -> IsoQ c x y -> IsoQ c x y #

(Show (c x y), Show (c y x)) => Show (IsoQ c x y) 
Instance details

Defined in Data.Quiver

Methods

showsPrec :: Int -> IsoQ c x y -> ShowS #

show :: IsoQ c x y -> String #

showList :: [IsoQ c x y] -> ShowS #

(Category c, x ~ y) => Semigroup (IsoQ c x y) 
Instance details

Defined in Data.Quiver

Methods

(<>) :: IsoQ c x y -> IsoQ c x y -> IsoQ c x y #

sconcat :: NonEmpty (IsoQ c x y) -> IsoQ c x y #

stimes :: Integral b => b -> IsoQ c x y -> IsoQ c x y #

(Category c, x ~ y) => Monoid (IsoQ c x y) 
Instance details

Defined in Data.Quiver

Methods

mempty :: IsoQ c x y #

mappend :: IsoQ c x y -> IsoQ c x y -> IsoQ c x y #

mconcat :: [IsoQ c x y] -> IsoQ c x y #