moto-0.0.4: General purpose migrations library

Safe HaskellNone
LanguageHaskell2010

Moto.Registry

Contents

Description

This module exports tools for implementing a registry that moto can use in order to keep track of the migrations that have been run so far.

It's unlikely that you'll need to concern yourself with this module as an end user of moto.

Please import as:

import qualified Moto.Registry as Moto
Synopsis

Command-line support

data RegistryConf Source #

Configuration for the Registry that we'll use to keep track of the migrations we've run so far.

Constructors

RegistryConf 

Fields

Registry

data Registry Source #

Migrations registry, keeping track of what migrations have been run so far, as well as those that are running.

Consider using newAppendOnlyRegistry as an easy way to create a Registry.

Constructors

Registry 

Fields

  • registry_state :: Df1 -> IO State

    Current registry state.

    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.

  • registry_prepare :: Df1 -> MigId -> Direction -> IO (Either Err_Prepare Log)

    Register a new pending change in the registry.

    Returns the Log_Prepare that describes this change to the registry.

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

  • registry_abort :: Df1 -> MigId -> Direction -> IO (Either Err_Abort Log)

    Abort the pending change in the given Direction most recently introduced via registry_prepare, expected to be identified by the given MigId.

    Returns the Log_Abort that describes this change to the registry.

    If there is no pending change to be aborted (that is, if the status is Clean), then Err_Abort_Clean shall be returned.

    If the currently pending migration's identifier is different from the the given MigId, or if its execution was intended for a Direction different than the one specified here, then Err_Abort_Dirty shall be returned.

    After a successful call to registry_abort, the registry will be left in a Clean status.

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

  • registry_commit :: Df1 -> MigId -> Direction -> IO (Either Err_Commit Log)

    Commit the pending change in the given Direction most recently introduced via registry_prepare, expected to be identified by the given MigId.

    Returns the Log_Commit that describes this change to the registry.

    This is the first commit in the two-phase commit mechanism to registering migrations as executed (registry_prepare is the first).

    If there is no pending change to be committed (that is, if the status is Clean), then Err_Commit_Clean shall be returned.

    If the currently pending migration's identifier is different from the the given MigId, or if its execution was intended for a Direction different than the one specified here, then Err_Commit_Dirty shall be returned.

    After a successful call to registry_commit, the registry will be left in a Clean status.

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

newAppendOnlyRegistry Source #

Arguments

:: State

Initial registry state obtained by reading Logs from the backing append-only storage and running updateState on them.

-> (Log -> IO ())

How to store a newly generated Log in the backing append-only storage.

If this function throws an exception, then the execption will propagated as usual, but also, this registry will be marked as tained and each subsequent operation on it will throw Err_Tainted.

-> IO Registry 

Create a Registry backed by an append-only Log storage.

This registry maintains its internal State in memory as long as it is possible to successfuly store all the changes in the underlying append-only storage. If at some point this fails unrecoverably, then Err_Tainted will be thrown by the functions acting on this Registry.

It's important to acquire some kind of exclusive lock on the underlying storage, so that other applications can't poke it while our Registry is running.

State

data State Source #

Internal State of a Registry.

Create with emptyState and updateState.

Instances
Eq State Source # 
Instance details

Defined in Moto.Internal

Methods

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

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

Show State Source # 
Instance details

Defined in Moto.Internal

Methods

showsPrec :: Int -> State -> ShowS #

show :: State -> String #

showList :: [State] -> ShowS #

emptyState :: State Source #

A clean State without any committed migrations.

updateState :: State -> Log -> Either Err_UpdateState State Source #

Modify a State by applying a Log to it, if possible.

Use emptyState as the initial state.

foldlM updateState emptyState
  :: Foldable t
  => t Log
  -> Either Err_UpdateState State

data Log Source #

A State can be described as a list of Logs ordered chronologically (see updateState).

Constructors

Log_Prepare UTCTime MigId Direction

A particular migration identified by MigId is going to be executed in the specified Direction.

This is the first commit in the two-phase commit approach to registering a migration as executed.

The time when this log entry was created is mentioned as well.

Log_Commit UTCTime

The migration most recently prepared for execution with Log_Prepare is being committed.

This is the second commit in the two-phase commit approach to registering a migration as executed.

The time when this log entry was created is mentioned as well.

Log_Abort UTCTime

The migration most recently prepared for execution with Log_Prepare is being aborted.

This undoes the first commit in the two-phase commit approach to registering a migration as executed.

The time when this log entry was created is mentioned as well.

Instances
Eq Log Source # 
Instance details

Defined in Moto.Internal

Methods

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

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

Read Log Source # 
Instance details

Defined in Moto.Internal

Show Log Source # 
Instance details

Defined in Moto.Internal

Methods

showsPrec :: Int -> Log -> ShowS #

show :: Log -> String #

showList :: [Log] -> ShowS #

Errors

data Err_Tainted Source #

The Registry is tainted, meaning our last attempt to interact with the registry's backing storage failed. We can't be certain about the current state of the Registry.

Constructors

Err_Tainted