-- | 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.CQRS.EventStore.Backend (EventStoreBackend(..), RawSnapshot) import Data.CQRS.GUID import Data.CQRS.Internal.PersistedEvent (PersistedEvent(..), mapPersistedEvent) import Data.CQRS.Serialize (decode', encode) import Data.Conduit (Source, ($=)) import qualified Data.Conduit.List as CL import Data.SafeCopy (SafeCopy) -- 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 e . (SafeCopy e) => EventStore e -> Int -> Source IO (PersistedEvent e) enumerateEventStore es minVersion = esbEnumerateAllEvents (esBackend es) minVersion $= CL.map (mapPersistedEvent decode') withTransaction :: EventStore e -> IO a -> IO a withTransaction (EventStore esb) = esbWithTransaction esb storeEvents :: SafeCopy e => EventStore e -> GUID -> Int -> [PersistedEvent e] -> IO () storeEvents (EventStore esb) guid v0 evs = esbStoreEvents esb guid v0 $ (map $ mapPersistedEvent $ encode) evs retrieveEvents :: SafeCopy e => EventStore e -> GUID -> Int -> Source IO (PersistedEvent e) retrieveEvents (EventStore esb) guid v0 = fmap (mapPersistedEvent decode') $ esbRetrieveEvents esb guid v0 writeSnapshot :: EventStore e -> GUID -> RawSnapshot -> IO () writeSnapshot (EventStore esb) = esbWriteSnapshot esb getLatestSnapshot :: EventStore e -> GUID -> IO (Maybe RawSnapshot) getLatestSnapshot (EventStore esb) = esbGetLatestSnapshot esb getLatestVersion :: EventStore e -> IO Int getLatestVersion (EventStore esb) = esbGetLatestVersion esb