| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Moto.Registry
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
- data RegistryConf = RegistryConf {- registryConf_help :: String
- registryConf_parse :: String -> Either String r
- registryConf_with :: forall a. Df1 -> r -> (Registry -> IO a) -> IO a
 
- data Registry = Registry {- registry_state :: Df1 -> IO State
- registry_prepare :: Df1 -> MigId -> Direction -> IO (Either Err_Prepare Log)
- registry_abort :: Df1 -> MigId -> Direction -> IO (Either Err_Abort Log)
- registry_commit :: Df1 -> MigId -> Direction -> IO (Either Err_Commit Log)
 
- newAppendOnlyRegistry :: State -> (Log -> IO ()) -> IO Registry
- data State
- emptyState :: State
- updateState :: State -> Log -> Either Err_UpdateState State
- data Log
- data Err_Tainted = Err_Tainted
- data Err_Prepare
- data Err_Abort
- data Err_Commit
- data Err_UpdateState
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
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 
 | |
newAppendOnlyRegistry Source #
Arguments
| :: State | Initial registry state obtained by reading  | 
| -> (Log -> IO ()) | How to store a newly generated  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  | 
| -> 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
Create with emptyState and updateState.
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.
foldlMupdateStateemptyState::Foldablet => tLog->EitherErr_UpdateStateState
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  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  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  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. | 
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 | 
Instances
| Eq Err_Tainted Source # | |
| Defined in Moto.Registry | |
| Show Err_Tainted Source # | |
| Defined in Moto.Registry Methods showsPrec :: Int -> Err_Tainted -> ShowS # show :: Err_Tainted -> String # showList :: [Err_Tainted] -> ShowS # | |
| Exception Err_Tainted Source # | |
| Defined in Moto.Registry Methods toException :: Err_Tainted -> SomeException # fromException :: SomeException -> Maybe Err_Tainted # displayException :: Err_Tainted -> String # | |
data Err_Prepare Source #
Errors from registry_prepare.
Constructors
| Err_Prepare_Duplicate MigId | |
| Err_Prepare_NotFound MigId | |
| Err_Prepare_Dirty MigId Direction | 
Instances
| Eq Err_Prepare Source # | |
| Defined in Moto.Internal | |
| Show Err_Prepare Source # | |
| Defined in Moto.Internal Methods showsPrec :: Int -> Err_Prepare -> ShowS # show :: Err_Prepare -> String # showList :: [Err_Prepare] -> ShowS # | |
| Exception Err_Prepare Source # | |
| Defined in Moto.Internal Methods toException :: Err_Prepare -> SomeException # fromException :: SomeException -> Maybe Err_Prepare # displayException :: Err_Prepare -> String # | |
Errors from registry_abort.
Constructors
| Err_Abort_Clean | |
| Err_Abort_Dirty MigId Direction | 
Instances
| Eq Err_Abort Source # | |
| Show Err_Abort Source # | |
| Exception Err_Abort Source # | |
| Defined in Moto.Internal Methods toException :: Err_Abort -> SomeException # fromException :: SomeException -> Maybe Err_Abort # displayException :: Err_Abort -> String # | |
data Err_Commit Source #
Errors from registry_commit.
Constructors
| Err_Commit_Clean | |
| Err_Commit_Dirty MigId Direction | 
Instances
| Eq Err_Commit Source # | |
| Defined in Moto.Internal | |
| Show Err_Commit Source # | |
| Defined in Moto.Internal Methods showsPrec :: Int -> Err_Commit -> ShowS # show :: Err_Commit -> String # showList :: [Err_Commit] -> ShowS # | |
| Exception Err_Commit Source # | |
| Defined in Moto.Internal Methods toException :: Err_Commit -> SomeException # fromException :: SomeException -> Maybe Err_Commit # displayException :: Err_Commit -> String # | |
data Err_UpdateState Source #
Errors from updateState.
Constructors
| Err_UpdateState_Duplicate MigId | |
| Err_UpdateState_NotFound MigId | |
| Err_UpdateState_Clean | |
| Err_UpdateState_Dirty | 
Instances
| Eq Err_UpdateState Source # | |
| Defined in Moto.Internal Methods (==) :: Err_UpdateState -> Err_UpdateState -> Bool # (/=) :: Err_UpdateState -> Err_UpdateState -> Bool # | |
| Show Err_UpdateState Source # | |
| Defined in Moto.Internal Methods showsPrec :: Int -> Err_UpdateState -> ShowS # show :: Err_UpdateState -> String # showList :: [Err_UpdateState] -> ShowS # | |
| Exception Err_UpdateState Source # | |
| Defined in Moto.Internal Methods toException :: Err_UpdateState -> SomeException # | |