{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE LambdaCase #-}
module Moto.Registry
(
IC.RegistryConf(..)
, I.Registry(..)
, newAppendOnlyRegistry
, I.State
, I.emptyState
, I.updateState
, I.Log(..)
, Err_Tainted(..)
, I.Err_Prepare(..)
, I.Err_Abort(..)
, I.Err_Commit(..)
, I.Err_UpdateState(..)
) where
import Control.Concurrent (readMVar, putMVar, takeMVar, newMVar)
import qualified Control.Exception.Safe as Ex
import qualified Data.Time as Time
import qualified Moto.Internal as I
import qualified Moto.Internal.Cli as IC
newAppendOnlyRegistry
:: I.State
-> (I.Log -> IO ())
-> IO I.Registry
newAppendOnlyRegistry !state0 putLog = do
mvState <- newMVar (Just state0)
let supdate :: (I.State -> Either e I.Log) -> IO (Either e I.Log)
supdate f = Ex.bracketOnError
(takeMVar mvState)
(\_ -> putMVar mvState Nothing)
(\case Nothing -> Ex.throwM Err_Tainted
Just s0 -> case f s0 of
Left e -> pure (Left e)
Right log_ -> case I.updateState s0 log_ of
Left e -> Ex.throwM e
Right !s1 -> do
putLog log_
putMVar mvState (Just s1)
pure (Right log_))
pure $ I.Registry
{ I.registry_state = \_ -> do
maybe (Ex.throwM Err_Tainted) pure =<< readMVar mvState
, I.registry_prepare = \_ mId d -> do
t <- Time.getCurrentTime
supdate $ \s -> case I.state_status s of
I.Dirty mId' d' -> Left (I.Err_Prepare_Dirty mId' d')
I.Clean -> case (d, elem mId (map fst (I.state_committed s))) of
(I.Forwards, True) -> Left (I.Err_Prepare_Duplicate mId)
(I.Backwards, False) -> Left (I.Err_Prepare_NotFound mId)
_ -> Right (I.Log_Prepare t mId d)
, I.registry_abort = \_ mId d -> do
t <- Time.getCurrentTime
supdate $ \s -> case I.state_status s of
I.Clean -> Left I.Err_Abort_Clean
I.Dirty mId' d'
| mId /= mId' || d /= d' -> Left (I.Err_Abort_Dirty mId' d')
| otherwise -> Right (I.Log_Abort t)
, I.registry_commit = \_ mId d -> do
t <- Time.getCurrentTime
supdate $ \s -> case I.state_status s of
I.Clean -> Left I.Err_Commit_Clean
I.Dirty mId' d'
| mId /= mId' || d /= d' -> Left (I.Err_Commit_Dirty mId' d')
| otherwise -> Right (I.Log_Commit t)
}
data Err_Tainted = Err_Tainted deriving (Eq, Show)
instance Ex.Exception Err_Tainted