-- | Event store functions. module Data.CQRS.Internal.EventStore ( EventStore , enumerateAllEvents , enumerateEventStore , getLatestSnapshot , getLatestVersion , retrieveEvents , storeEvents , withEventStore , withTransaction , writeSnapshot ) where import Control.Exception (bracket) import Control.Monad (liftM) import Data.ByteString (ByteString) import Data.CQRS.EventStore.Backend (EventStoreBackend(..)) import Data.CQRS.GUID import Data.CQRS.Serialize (decode') import Data.Enumerator (Enumerator, ($=)) import qualified Data.Enumerator.List as EL import Data.Serialize (Serialize, encode) -- Utilities. map1st :: (a -> c) -> (a, b) -> (c, b) map1st f (a,b) = (f a, b) map2nd :: (b -> c) -> (a,b) -> (a,c) map2nd f (a,b) = (a, f b) map3rd :: (c -> d) -> (a,b,c) -> (a,b,d) map3rd f (a,b,c) = (a,b,f c) -- Provide a type alias. data EventStore e = EventStore { esBackend :: EventStoreBackend } -- | Perform an IO action with an open event store. withEventStore :: (IO EventStoreBackend) -> (EventStore e -> IO a) -> IO a withEventStore open action = bracket (liftM EventStore open) (esbCloseEventStoreBackend . esBackend) action -- | Enumerate all the events from an event store that occur at or later -- than a given logical timestamp. enumerateEventStore :: forall a b e . (Serialize e) => EventStore e -> Int -> Enumerator (Int, (GUID a, Int, e)) IO b enumerateEventStore es minVersion = esbEnumerateAllEvents (esBackend es) minVersion $= EL.map (\(gv,(g,ev,ed)) -> (gv,(g,ev,decode' ed :: e))) withTransaction :: EventStore e -> IO a -> IO a withTransaction (EventStore esb) = esbWithTransaction esb storeEvents :: Serialize e => EventStore e -> GUID a -> Int -> [(e,Int)] -> IO () storeEvents (EventStore esb) guid v0 evs = esbStoreEvents esb guid v0 (map (map1st encode) evs) retrieveEvents :: Serialize e => EventStore e -> GUID a -> Int -> IO (Int,[e]) retrieveEvents (EventStore esb) guid v0 = liftM (map2nd $ map decode') $ esbRetrieveEvents esb guid v0 enumerateAllEvents :: forall a b e. Serialize e => EventStore e -> Int -> Enumerator (Int, (GUID a, Int, e)) IO b enumerateAllEvents (EventStore esb) v0 = esbEnumerateAllEvents esb v0 $= EL.map (map2nd $ map3rd decode') writeSnapshot :: EventStore e -> GUID a -> (Int, ByteString) -> IO () writeSnapshot (EventStore esb) = esbWriteSnapshot esb getLatestSnapshot :: EventStore e -> GUID a -> IO (Maybe (Int, ByteString)) getLatestSnapshot (EventStore esb) = esbGetLatestSnapshot esb getLatestVersion :: EventStore e -> IO Int getLatestVersion (EventStore esb) = esbGetLatestVersion esb