-- | Event store functions. module Data.CQRS.Internal.EventStore ( EventStore , 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.Internal.PersistedEvent (PersistedEvent(..), mapPersistedEvent) import Data.CQRS.Serialize (decode') import Data.Enumerator (Enumerator, ($=)) import qualified Data.Enumerator.List as EL import Data.Serialize (Serialize, encode) -- 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 e . (Serialize e) => EventStore e -> Int -> Enumerator (PersistedEvent e) IO a enumerateEventStore es minVersion = esbEnumerateAllEvents (esBackend es) minVersion $= EL.map (mapPersistedEvent decode') withTransaction :: EventStore e -> IO a -> IO a withTransaction (EventStore esb) = esbWithTransaction esb storeEvents :: Serialize e => EventStore e -> GUID -> Int -> [PersistedEvent e] -> IO () storeEvents (EventStore esb) guid v0 evs = esbStoreEvents esb guid v0 $ (map $ mapPersistedEvent encode) evs retrieveEvents :: Serialize e => EventStore e -> GUID -> Int -> IO [PersistedEvent e] retrieveEvents (EventStore esb) guid v0 = liftM (map $ mapPersistedEvent decode') $ esbRetrieveEvents esb guid v0 writeSnapshot :: EventStore e -> GUID -> (Int, ByteString) -> IO () writeSnapshot (EventStore esb) = esbWriteSnapshot esb getLatestSnapshot :: EventStore e -> GUID -> IO (Maybe (Int, ByteString)) getLatestSnapshot (EventStore esb) = esbGetLatestSnapshot esb getLatestVersion :: EventStore e -> IO Int getLatestVersion (EventStore esb) = esbGetLatestVersion esb