moto-0.0.4: General purpose migrations library

Safe HaskellNone
LanguageHaskell2010

Moto

Contents

Description

moto is a library for describing and running migrations.

A migration is any code that changes the environment somehow. The stereotypical example of a migration is code that modifies the schema of a database, but really anything that changes the environment somehow can be seen as a migration. For example, moving a file to a different directory or host, installing a package, deploying infrastructure, etc.

Essentially, a migration is a glorified bash script to which we hold dear because of how devastating it can be for our project if we get it wrong. moto understands this, so it is very careful about how, when, where and why it runs these migrations, paying special attention to what happens when something goes wrong. Of course, this being Haskell, we are encouraged to use domain specific tools that can prevent us from accidentally writing the wrong migration code (e.g., deleting a database rather than modifying it).

In moto we can specify migrations in such a way that any data that is going modified or deleted by a migration can be backed up for us in one or more storages of our choice. If anything goes wrong, or if we latter decide to undo these changes, then this backup will be automatically made available to us.

moto is excellent for teams, where multiple collaborators can add new migrations to the project at the same time, establishing dependencies between them by saying “this migration needs to run before that other one” as a graph. At compile time, moto will ensure whether there is at least one way to execute these migrations graph sequentially, or fail to compile otherwise. And at runtime, it will execute this graph in any way that's compatible with the environment where the migrations are being run. We don't need to worry about serializing the release and deployment of migrations anymore, nor about making sure that everybody runs migrations in the same order. We can delegate that responsibility to moto.

Also, moto is an excellent interface to interacting with our migrations and environment. The final product we obtain as a user of moto is a ready-made command line interface program that we can deploy and use to run all or some migrations, undo them, render the dependency graph, compare it with the current registry of migrations that have been run so far, obtain an execution plan as well as very detailed logs in human and computer readable formats, etc.

moto relies on a registry of migrations to understand what has been run so far and what hasn't. We can decide whether to keep this state locally or in a remote database.

Last, but not least, moto encourages us to remove old migrations after some time, once these migrations are so old that maintaining them in the project is an unnecessary burden to us. To this end, moto offers us enough vocabulary to mark said migrations as gone.

This module is inteded to be imported qualified:

import qualified Moto
Synopsis

Example

The main interface to running migrations is the command line. As a user of moto, we are expected to create an executable that calls cli. This executable can then be deployed and used to run migrations.

Usually, the code in this executable will look like this:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PartialTypeSignatures #-}


-- Our project will be an executable, so we name our module Main as it is
-- customary.
module Main (main) where


-- Moto is designed to be imported qualified, as well as Di, a module that
-- provides the logging support required by Moto.
import qualified Di
import qualified Moto

-- Moreover, in this example we will use a migrations registry from the
-- Moto.File module as an example.
import qualified Moto.File


-- Here are some migrations, each of them with a identifier and a set of
-- identifiers for other migrations expected to be executed before them when
-- going Forwards.
--
-- Optional: It is actually recommended to put each migration in its own module.
-- It is not necessary, but GHC takes a longer time and more resources to
-- compile big modules. And considering the list of migrations in our project
-- will always be growing, it's better to organize things that way from the
-- start, as this can quickly become a source of slow compilation times.  For
-- example, instead of Main.mig_black and Main.mig_blue, we can have
-- MyProject.Migs.Black.mig and MyProject.Migs.Blue.mig that we import as
-- necessary.
mig_red :: Moto.Mig "red" '["blue"]
mig_red = Moto.Mig ... -- Please see the documentation for Mig.

mig_yellow :: Moto.Mig "yellow" '["black","red"]
mig_yellow = Moto.Mig ... -- Please see the documentation for Mig.

mig_green :: Moto.Mig "green" '["red"]
mig_green = Moto.Mig ... -- Please see the documentation for Mig.

mig_black :: Moto.Mig "black" '["blue"]
mig_black = Moto.Mig ... -- Please see the documentation for Mig.

mig_blue :: Moto.Mig "blue" '[]
mig_blue = Moto.Mig ... -- Please see the documentation for Mig.


-- All of the Migs that we might want to run need to be put in directed
-- acyclic graph where each migration is a node and each edge is a dependency
-- between migrations. In Moto, we use migs and the infix *
-- function to safely construct the graph of migrations.  The way we define our
-- Migs is a bit strange. Let's understand why.
--
-- The Moto.* infix function says that the migrations that appear syntactically
-- to its right can only mention as their dependencies migrations that appear
-- to its syntactic left. This prevents us from mentioning our migrations in
-- any order, but on the other hand it ensures at construction that there are no
-- cycles nor dangling references in our dependency graph. If we get the order
-- wrong, we will get a type-checker error. Moreover, migration identifiers are
-- forced to be unique within this graph. The Moto.migs value itself is a dummy
-- starting point we use as the leftmost argument to our chain of Moto.* calls.
--
-- Observation: Note we avoid giving an explicit type to myMigs. Instead, we
-- used the PartialTypeSignatures GHC extension to put an underscore there and
-- allow GHC to use the inferred type. This is a desirable thing to do so as to
-- prevent type-inference from accidentally inferring an undesired identifier
-- for our migrations. This approach forces all of our Moto.Mig values to have
-- their identifiers and dependencies fully specified at their definition site.
-- We could have accomplished the same by not giving an type signature to our
-- top level myMigs, or by simply inlining our definition of myMigs at its use
-- site later on.
myMigs :: Moto.Migs _
myMigs = Moto.migs
  Moto.* mig_blue
  Moto.* mig_red
  Moto.* mig_black
  Moto.* mig_green
  Moto.* mig_yellow


-- Finally, we have our main entry point. This program can be run from the
-- command line and allows us to run and inspect migrations.
main :: IO ()
main = do

   -- Using getOpts we parse the command-line arguments and obtain the
   -- instructions necessary to call run afterwards.  We specify as
   -- arguments a RegistryConf that describes the migrations
   -- registry where we keep track of the migrations that have run so far, as
   -- well as any extra command-line parsing needs we may have. In our case, we
   -- use a file in the filesystem as our registry, and we don't do any extra
   -- command-line argument parsing. Please see the documentation of
   -- getOpts for more details.
   (myOpts, ()) <- Moto.getOpts Moto.File.registryConf (pure ())

   -- moto uses Di for its own logging, so we first
   -- need to obtain a Di Level Path Message value (also
   -- known by its Df1 synonym). We can do this using new.
   Di.new $ \di -> do

      -- Finally, we run moto as instructed by myOpts, passing in the
      -- Df1 we just obtained, as well as the migrations graph
      Moto.run di myMigs myOpts

Frequently Asked Questions

Here are some answers to questions you'll frequently ask yourselves when using moto.

Where should we maintain the migrations code for our project?
Ideally, if you keep your whole project in a single code repository, you should keep the migrations in that same repository, so that they are always in sync with the code they cater for. You should create a standalone executable program for running your migrations.
Should my migrations program depend on the code I am migrating?
Definitely not. That code will change or disappear over time, and it will affect your migrations code whenever it changes. Your migrations code should stand alone and have a holistic view of the history of the many environments where your project runs, without depending on it.
Can I use moto to migrate projects not written in Haskell?
Yes, moto doesn't care about the language your project is written in. However, the migrations code itself will have to be written Haskell.
How do I deploy this?
The same way you deploy other executables. We recommend packaging the program as a Nix derivation containing a statically linked executable. Moreover, you can package the migrations execution as a NixOS module that runs automatically whenever a new version is deployed. Future versions of moto will provide a web interface for making migration execution a bit more interactive.
How do I make sure my migrations work before deploying them?
Generally speaking, as much as possible, you should use domain-specific type-safe DSLs to describe your changes. But still, eventually, try the real thing locally. Don't try to “mock” scenarios, that doesn't help. moto makes it quite easy to run migrations backwards afterwards. Moreover, in order to try recovery scenarios, you try and throw exceptions from the different parts of your migrations and see what happens.
I don't see anything about SQL nor versioned data-types here
Whether you are modifying an SQL database or moving any other kind of bits around, moto doesn't care about those details. You can write all the SQL you want inside your migration, using the SQL-supporting library of your choice, or version your datatypes as well.
Is this ready for production?
Migrations are a tricky business, and this is a very early release of moto, so use at your own risk.
Is the API stable?
No, and it will never be. We will always break the API as necessary if it allows us offer better safety and experience. However, we understand the subtle nature of the projects relying on moto an we will take the necessary steps to ensure a positive and maintainable experience over time. Please see the changelog to understand differences between versions and learn about any necessary changes you'll need to make. In a moto version x.y.z, we will always increase one of x or y whenever a new version introduces backwards incompatible changes.
I have more questions!
We have more answers. Just ask.

Running

run Source #

Arguments

:: Df1

Root logger. If you don't have a Df1 for your program yet, you can obtain one using Di.new from the di library.

-> Migs graph

Avaliable migrations graph.

-> Opts

Instructions on how to interact with our migrations. Obtain with getOpts.

-> IO () 

Run moto on the given migrations graph Migs, according to the instructions in Opts.

data Opts Source #

This is the input required by run, obtained from the command line arguments by using getOpts.

getOpts Source #

Arguments

:: RegistryConf

Configuration for the Registry to use.

Among other things, this will dictate how we interpret the --registry command-line option.

Examples: Moto.PostgreSQL.registryConf from the moto-postgresql library or Moto.File.registryConf from this library.

-> Parser a

This extra parser can be used to read some extra configuration values from the command-line arguments, besides moto's own.

For example, we can obtain things such as the name of a configuration file or a database connection string we might want to use in our migrations.

If no such extra data is required, then pure () can be used.

Notice that moto's own command-line argument's parser has precedence over this parser. Yet, in the command-line, the argument's for the parser for a should come before moto's own subcommand arguments, otherwise the command line program will complain about a malformed command-line.

-> IO (Opts, a) 

Run the command-line arguments parser, obtaining the Opts necessary for calling run afterwards.

Notice that we can run the executable that calls getOpts with a --help command line switch for extensive documentation on how to interact with moto.

Describing individual migrations

data Mig (id :: Symbol) (deps :: [Symbol]) where Source #

A single side-effecting migration uniquely identfied by id and depending on all of the migrations listed in deps.

These migration identifiers that appear as type-level Symbol here, will be of type MigId when represented at the type level.

Constructors

Mig

Description of the different phashes that make up this migration identified by id, depending on others identified by deps.

Fields

  • :: Store x

    How to save and load data obtained during the Backup phase when necessary.

    Please note that you can reuse this same Store across different migrations.

    Any stored data will remain in the Store until it is not necessary anymore (but it can be manually deleted if desired, at your own risk).

    Please refer to Store for further documentation.

  • -> Backup x

    Backup phase of this migration

    This phase is executed only once when trying to run the migration Forwards for the first time.

    Please refer to Backup for further documentation.

  • -> Change x

    Change phase of this migration.

    This phase is executed both when going Forwards and Backwards. Here we alter the environment somehow while having access to the x data obtained in the Backup phase.

    Please refer to Change for further documentation.

  • -> Mig id deps
     
Gone :: Mig id deps

This constructor conveys the idea that code for a particular migration is gone, while still communicating the dependencies that this migration used to have so that we don't change the past dependency graph over time, which would make it impossible for moto to operate reliably.

data Store (x :: *) Source #

A Store describes how to save, load and delete the x data obtained by a Backup.

This x data is used later by the Change phase.

A single Store might be used by different Migs.

Hint: store from the Moto.File module is a Store you can use that's distributed with the main moto library.

Constructors

Store 

Fields

  • store_save :: Df1 -> MigId -> x -> IO ()

    Saves the x data originating from a Backup step for a migration identified by MigId, overwriting previous data if any.

    If it's not possible to save the x data, then this function must fail with some exception.

    The passed in Df1 can be used for logging if necessary (see Di and Di.Df1), but please don't log exceptions nor messages telling whether this function succeeds or fails, since this library already does that for you.

  • store_load :: forall r. Df1 -> MigId -> (x -> IO r) -> IO r

    Load the data previously saved by store_save, for a migration identified by the given MigId.

    Notice that x is returned in a continuation-passing style so that we can do proper resource deallocation after x has been consumed. Using x outside of this intended scope is undefined.

    If it's was not possible to load the x data, then this function must fail with some exception.

    The passed in Df1 can be used for logging if necessary (see Di and Di.Df1), but please don't log exceptions nor messages telling whether this function succeeds or fails, since this library already does that for you.

  • store_delete :: Df1 -> MigId -> IO ()

    Delete the data previously saved by store_save, if any. for a migration identified by the given MigId.

    If it's there was no data to delete, then this function should return (). On the other hand, if its acceptable to throw exceptions when it's not possible to access the underlying storage.

    The passed in Df1 can be used for logging if necessary (see Di and Di.Df1), but please don't log exceptions nor messages telling whether this function succeeds or fails, since this library already does that for you.

mapStore Source #

Arguments

:: (b -> a)

Isomorphism from b to a.

-> (a -> b)

Isomorphism from a to b.

-> Store a 
-> Store b 

Given isomorpisms between a and b, obtain an function from Store a and Store b.

A Store x is both covariant and contravariant with x.

This function respects the functor laws.

dummyStore :: Store () Source #

A Store that does nothing and always succeeds.

data Backup (x :: *) Source #

The backup phase of a migration, collecting some data x for backup in a Store.

Here we interact with the environment in a read-only manner, collecting all data that may be destroyed by a subsequent Change phase for backup in some Store.

This data will be crucial for automatic recovery in case the Change phase of the Mig that uses this Backup fails, or in case we manually decide to undo said Mig at a later time. Thus, when deciding what data to return as x, please consider those scenarios.

The actual storing of the backup data is performed by the Store that is used as part of the same Mig. That is, we don't physically store the data within this Backup, all we do is return it as x.

Please keep in mind that depending on your environment, x could be really large, so in those situations it best for x to be some kind of stream (e.g., a Producer).

Notice that x is returned in a continuation-passing style so that we can do proper resource deallocation after x has been consumed. Using x outside of this intended scope is undefined.

Constructors

Backup (forall r. Df1 -> (x -> IO r) -> IO r) 
Instances
Functor Backup Source #

Backup is covariant with x.

Instance details

Defined in Moto.Internal

Methods

fmap :: (a -> b) -> Backup a -> Backup b #

(<$) :: a -> Backup b -> Backup a #

dummyBackup :: Backup () Source #

A Backup that does nothing and always succeeds.

newtype Change x Source #

A Change describes how a Mig changes the environment.

The given function will be called when running the migration both in Forwards or Backwards direction.

In both cases, we have access to the original Backup data while running the migration, which implies that even “irrecoverable” migrations that delete things when going Forwards can be undone by relying on data from the Backup.

The given Mode specifies why and how this Change is being run. Particularly, it describes the assumptions you can make about the environment, which is very important if something goes wrong. Please refer to the documentation for Mode for a better understanding.

The passed in Df1 can be used for logging if necessary (see Di and Di.Df1), but please don't log exceptions nor messages telling whether this function as a whole succeeds or fails, since this library already does that for you. However, for debugging purposes in case something goes wrong, it is very important that you log what your Change is doing, particularly if the changes themselves are not atomic. Please see the documentation for Recovery to understand what can be helpful.

After a successful Backwards execution of this Change, any recovery data associated with the Mig previously obtained during the Backup phase can be deleted from its Store, since it is not necessary anymore. This will happen automatically if you request so when instructing moto to run your migrations.

Constructors

Change (Df1 -> Direction -> Mode -> x -> IO ()) 

data Direction Source #

Direction in which a migration runs.

Running it Forwards conveys the idea of “advancing” or “improving” your state over time somehow, while running it Backwards conveys the idea of undoing all the changes that the migration does when going Forwards.

Constructors

Backwards 
Forwards 

direction :: a -> a -> Direction -> a Source #

Case analysis for Direction. Evaluate to the first a in case it is Backwards, otherwise to the second a.

data Mode Source #

Execution mode of a migration, describing why and how a Change migration is being run.

Constructors

Normal

The migration is being run as requested by the user, in the requested Direction. Every previous step until now has run successfully. You can assume a clean starting point.

If running the migration in Normal mode fails, the same migration will be run again in Recovery mode in the opposite Direction as a way to undo any partial changes and go back to having a clean state. This recovery mechanism survives through different program executions, so even if a failure when running a migration in Normal mode causes the whole program to crash, the corresponding Recovery mode can still be run from the command line program. In fact, moto will refuse making any other changes until this matter is sorted. For this reason, if let a Change being executed in Normal mode fails, it is always preferrable to let that exception propagate, and instead focus on writing any mitigating code as part of the Recovery mode.

Recovery

An attempt to run the migration in the Direction requested by the user has failed, so as a recovery meassure we are running the same migration in the opposite direction now. You can't make assumptions about the starting point, because running the migration in the desired Direction failed somewhere in the middle of process. Please rely on the Backup data you obtained before to decide how to correct the situation.

Ultimately, running a migration in Recovery mode in a particular Direction needs to accomplish the same outcome as running it in Normal mode in that same Direction.

If running a migration in Recovery mode fails, then the program will exit and the migrations registry will be left in a dirty state, from which you can manually attempt to initiate a recovery again. At this point, reading the output logs and understanding what when wrong will be very useful: Maybe the migration failed because of a temporary phenomenon such as a network connectivity issue, in which simply retrying later will solve it, or maybe it failed because of a bug in the migration implementation, in which case logs will be crucial to understand how to change the migrations code in order to fix it.

Instances
ToValue Mode Source # 
Instance details

Defined in Moto.Internal

Methods

value :: Mode -> Value #

newtype MigId Source #

A term-level identifier for a Mig.

Constructors

MigId 

Fields

Instances
Eq MigId Source # 
Instance details

Defined in Moto.Internal

Methods

(==) :: MigId -> MigId -> Bool #

(/=) :: MigId -> MigId -> Bool #

Ord MigId Source # 
Instance details

Defined in Moto.Internal

Methods

compare :: MigId -> MigId -> Ordering #

(<) :: MigId -> MigId -> Bool #

(<=) :: MigId -> MigId -> Bool #

(>) :: MigId -> MigId -> Bool #

(>=) :: MigId -> MigId -> Bool #

max :: MigId -> MigId -> MigId #

min :: MigId -> MigId -> MigId #

Read MigId Source # 
Instance details

Defined in Moto.Internal

Show MigId Source # 
Instance details

Defined in Moto.Internal

Methods

showsPrec :: Int -> MigId -> ShowS #

show :: MigId -> String #

showList :: [MigId] -> ShowS #

IsString MigId Source # 
Instance details

Defined in Moto.Internal

Methods

fromString :: String -> MigId #

ToValue MigId Source # 
Instance details

Defined in Moto.Internal

Methods

value :: MigId -> Value #

Describing migrations graph

data Migs (graph :: [(Symbol, [Symbol])]) Source #

The directed acyclic graph of migrations available for execution.

Construct using migs and *. For example:

migs * someMig * anotherMig * ...

migs :: Migs '[] Source #

An empty, yet valid, graph of migrations.

You can use migs as a starting point for constructing bigger migrations graphs. For example:

migs * someMig * anotherMig * ...

(*) infixl 7 Source #

Arguments

:: DAG id deps graph 
=> Migs graph 
-> Mig id deps

id must not be present in graph.

All of deps must be present in graph.

-> Migs ('(id, deps) ': graph) 

Add a new migration with an unique identifier id depending on each of deps to a graph of migrations graph.

The DAG constraint guarantees that the result is a directed acyclic graph.

To create a Migs from scratch, use * in combination with migs. For example:

migs * someMig * anotherMig * ...

type DAG id deps graph = DAG_ id deps graph Source #

This Constraint is automatically satisfied by an id that is absent from graph, and deps listing identifiers present in the given graph.

In other words, DAG effectively forces * to always build Directed Acyclic Graphs (hence the name).

DAG id deps graph :: Constraint

Command line help

This is the full description of the command line options supported by getOpts, using Moto.File.fileRegistry as the registry.

Main program (here called moto-example):

Usage: moto-example COMMAND
  Command line interface to migrations.

Available options:
  -h,--help                Show this help text

Available commands:
  run                      Run migrations.
  show-migrations          Show available migrations.
  check-migrations         Exit immediately with status 0 if the available
                           migrations are compatible with the registry.
                           Otherwise, exit with status 1.
  show-registry            Show migrations registry.
  clean-registry           Clean a dirty migrations registry.
  delete-recovery-data     Delete contents from the migrations data store.

Subcommand run:

Usage: moto-example run --registry URI [--backwards] [--mig ID] [--no-dry-run]
  Run migrations.

Available options:
  --registry URI           File where registry file is stored. E.g.,
                           file:///var/db/migrations
  --mig ID                 If specified, only consider running the migration
                           identified by this ID. Use multiple times for
                           multiple migrations.
  --no-dry-run             Don't just show the execution plan, run it!
  -h,--help                Show this help text

Subcommand show-migrations:

Usage: moto-example show-migrations [--dot]
  Show available migrations.

Available options:
  --dot                    Render graph in DOT (Graphviz) format.
  -h,--help                Show this help text

Subcommand check-migrations:

Usage: moto-example check-migrations --registry URI
  Exit immediately with status 0 if the available migrations are compatible with
  the registry. Otherwise, exit with status 1.

Available options:
  --registry URI           File where registry file is stored. E.g.,
                           file:///var/db/migrations
  -h,--help                Show this help text

Subcommand show-registry:

Usage: moto-example show-registry --registry URI
  Show migrations registry.

Available options:
  --registry URI           File where registry file is stored. E.g.,
                           file:///var/db/migrations
  -h,--help                Show this help text

Subcommand clean-registry:

Usage: moto-example clean-registry --registry URI [--dry-run] ([--unsafe-abort]
                                   | [--unsafe-commit])
  Clean a dirty migrations registry.

Available options:
  --registry URI           File where registry file is stored. E.g.,
                           file:///var/db/migrations
  --dry-run                Don't clean registry, just show whether it is clean
                           and exit immediately with status 0 if so, otherwise
                           exit with status 1.
  --unsafe-abort           If the registry is dirty, unsafely abort the pending
                           migration without performing any actual clean-up.
  --unsafe-commit          If the registry is dirty, unsafely commit the pending
                           migration without performing any actual clean-up.
  -h,--help                Show this help text

Subcommand delete-recovery-data:

Usage: moto-example delete-recovery-data --mig ARG
  Delete contents from the migrations data store.

Available options:
  -h,--help                Show this help text