{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Test.Hindsight.Store.CursorTests (cursorTests) where
import Control.Monad (forM_)
import Data.Map.Strict qualified as Map
import Data.UUID.V4 qualified as UUID
import Hindsight.Store
import Test.Hindsight.Examples (makeUserEvent)
import Test.Hindsight.Store.TestRunner (EventStoreTestRunner (..))
import Test.Tasty
import Test.Tasty.HUnit
cursorTests ::
forall backend.
(EventStore backend, StoreConstraints backend IO, Show (Cursor backend), Ord (Cursor backend)) =>
EventStoreTestRunner backend ->
[TestTree]
cursorTests :: forall backend.
(EventStore backend, StoreConstraints backend IO,
Show (Cursor backend), Ord (Cursor backend)) =>
EventStoreTestRunner backend -> [TestTree]
cursorTests EventStoreTestRunner backend
runner =
[ TestName -> Assertion -> TestTree
testCase TestName
"Per-Stream Cursor Extraction" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ EventStoreTestRunner backend
-> forall a. (BackendHandle backend -> IO a) -> Assertion
forall backend.
EventStoreTestRunner backend
-> forall a. (BackendHandle backend -> IO a) -> Assertion
withStore EventStoreTestRunner backend
runner BackendHandle backend -> Assertion
forall backend.
(EventStore backend, StoreConstraints backend IO,
Show (Cursor backend)) =>
BackendHandle backend -> Assertion
testPerStreamCursorExtraction
, TestName -> Assertion -> TestTree
testCase TestName
"Cursor Independence" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ EventStoreTestRunner backend
-> forall a. (BackendHandle backend -> IO a) -> Assertion
forall backend.
EventStoreTestRunner backend
-> forall a. (BackendHandle backend -> IO a) -> Assertion
withStore EventStoreTestRunner backend
runner BackendHandle backend -> Assertion
forall backend.
(EventStore backend, StoreConstraints backend IO,
Show (Cursor backend)) =>
BackendHandle backend -> Assertion
testCursorIndependence
, TestName -> Assertion -> TestTree
testCase TestName
"Stale Cursor Per Stream" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ EventStoreTestRunner backend
-> forall a. (BackendHandle backend -> IO a) -> Assertion
forall backend.
EventStoreTestRunner backend
-> forall a. (BackendHandle backend -> IO a) -> Assertion
withStore EventStoreTestRunner backend
runner BackendHandle backend -> Assertion
forall backend.
(EventStore backend, StoreConstraints backend IO,
Show (Cursor backend)) =>
BackendHandle backend -> Assertion
testStaleCursorPerStream
, TestName -> Assertion -> TestTree
testCase TestName
"Cursor Completeness" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ EventStoreTestRunner backend
-> forall a. (BackendHandle backend -> IO a) -> Assertion
forall backend.
EventStoreTestRunner backend
-> forall a. (BackendHandle backend -> IO a) -> Assertion
withStore EventStoreTestRunner backend
runner BackendHandle backend -> Assertion
forall backend.
(EventStore backend, StoreConstraints backend IO,
Show (Cursor backend), Ord (Cursor backend)) =>
BackendHandle backend -> Assertion
testCursorCompleteness
, TestName -> Assertion -> TestTree
testCase TestName
"Empty Stream Cursor Handling" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ EventStoreTestRunner backend
-> forall a. (BackendHandle backend -> IO a) -> Assertion
forall backend.
EventStoreTestRunner backend
-> forall a. (BackendHandle backend -> IO a) -> Assertion
withStore EventStoreTestRunner backend
runner BackendHandle backend -> Assertion
forall backend.
(EventStore backend, StoreConstraints backend IO,
Show (Cursor backend)) =>
BackendHandle backend -> Assertion
testEmptyStreamCursorHandling
]
testPerStreamCursorExtraction :: forall backend. (EventStore backend, StoreConstraints backend IO, Show (Cursor backend)) => BackendHandle backend -> IO ()
BackendHandle backend
store = do
streamA <- UUID -> StreamId
StreamId (UUID -> StreamId) -> IO UUID -> IO StreamId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO UUID
UUID.nextRandom
streamB <- StreamId <$> UUID.nextRandom
streamC <- StreamId <$> UUID.nextRandom
result1 <-
insertEvents store Nothing $
Transaction
( Map.fromList
[ (streamA, StreamWrite NoStream [makeUserEvent 1])
, (streamB, StreamWrite NoStream [makeUserEvent 10])
, (streamC, StreamWrite NoStream [makeUserEvent 100])
]
)
case result1 of
FailedInsertion EventStoreError backend
err -> TestName -> Assertion
forall a. HasCallStack => TestName -> IO a
assertFailure (TestName -> Assertion) -> TestName -> Assertion
forall a b. (a -> b) -> a -> b
$ TestName
"Initial multi-stream write failed: " TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ EventStoreError backend -> TestName
forall a. Show a => a -> TestName
show EventStoreError backend
err
SuccessfulInsertion (InsertionSuccess{Map StreamId (Cursor backend)
streamCursors :: Map StreamId (Cursor backend)
streamCursors :: forall backend.
InsertionSuccess backend -> Map StreamId (Cursor backend)
streamCursors}) -> do
case StreamId -> Map StreamId (Cursor backend) -> Maybe (Cursor backend)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup StreamId
streamA Map StreamId (Cursor backend)
streamCursors of
Maybe (Cursor backend)
Nothing -> TestName -> Assertion
forall a. HasCallStack => TestName -> IO a
assertFailure TestName
"Stream A cursor missing from streamCursors"
Just Cursor backend
cursorA -> do
result2 <-
BackendHandle backend
-> Maybe CorrelationId
-> Transaction [] backend
-> IO (InsertionResult backend)
forall backend (t :: * -> *) (m :: * -> *).
(EventStore backend, Traversable t, StoreConstraints backend m) =>
BackendHandle backend
-> Maybe CorrelationId
-> Transaction t backend
-> m (InsertionResult backend)
forall (t :: * -> *) (m :: * -> *).
(Traversable t, StoreConstraints backend m) =>
BackendHandle backend
-> Maybe CorrelationId
-> Transaction t backend
-> m (InsertionResult backend)
insertEvents BackendHandle backend
store Maybe CorrelationId
forall a. Maybe a
Nothing (Transaction [] backend -> IO (InsertionResult backend))
-> Transaction [] backend -> IO (InsertionResult backend)
forall a b. (a -> b) -> a -> b
$
StreamId
-> ExpectedVersion backend
-> SomeLatestEvent
-> Transaction [] backend
forall backend.
StreamId
-> ExpectedVersion backend
-> SomeLatestEvent
-> Transaction [] backend
singleEvent StreamId
streamA (Cursor backend -> ExpectedVersion backend
forall backend. Cursor backend -> ExpectedVersion backend
ExactVersion Cursor backend
cursorA) (Int -> SomeLatestEvent
makeUserEvent Int
2)
case result2 of
FailedInsertion EventStoreError backend
err -> TestName -> Assertion
forall a. HasCallStack => TestName -> IO a
assertFailure (TestName -> Assertion) -> TestName -> Assertion
forall a b. (a -> b) -> a -> b
$ TestName
"Append with stream A cursor failed: " TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ EventStoreError backend -> TestName
forall a. Show a => a -> TestName
show EventStoreError backend
err
SuccessfulInsertion InsertionSuccess backend
_ -> do
result3 <-
BackendHandle backend
-> Maybe CorrelationId
-> Transaction [] backend
-> IO (InsertionResult backend)
forall backend (t :: * -> *) (m :: * -> *).
(EventStore backend, Traversable t, StoreConstraints backend m) =>
BackendHandle backend
-> Maybe CorrelationId
-> Transaction t backend
-> m (InsertionResult backend)
forall (t :: * -> *) (m :: * -> *).
(Traversable t, StoreConstraints backend m) =>
BackendHandle backend
-> Maybe CorrelationId
-> Transaction t backend
-> m (InsertionResult backend)
insertEvents BackendHandle backend
store Maybe CorrelationId
forall a. Maybe a
Nothing (Transaction [] backend -> IO (InsertionResult backend))
-> Transaction [] backend -> IO (InsertionResult backend)
forall a b. (a -> b) -> a -> b
$
StreamId
-> ExpectedVersion backend
-> SomeLatestEvent
-> Transaction [] backend
forall backend.
StreamId
-> ExpectedVersion backend
-> SomeLatestEvent
-> Transaction [] backend
singleEvent StreamId
streamA (Cursor backend -> ExpectedVersion backend
forall backend. Cursor backend -> ExpectedVersion backend
ExactVersion Cursor backend
cursorA) (Int -> SomeLatestEvent
makeUserEvent Int
3)
case result3 of
FailedInsertion (ConsistencyError ConsistencyErrorInfo backend
_) -> () -> Assertion
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
InsertionResult backend
_ -> TestName -> Assertion
forall a. HasCallStack => TestName -> IO a
assertFailure TestName
"Should not be able to reuse stale cursor"
testCursorIndependence :: forall backend. (EventStore backend, StoreConstraints backend IO, Show (Cursor backend)) => BackendHandle backend -> IO ()
testCursorIndependence :: forall backend.
(EventStore backend, StoreConstraints backend IO,
Show (Cursor backend)) =>
BackendHandle backend -> Assertion
testCursorIndependence BackendHandle backend
store = do
streamA <- UUID -> StreamId
StreamId (UUID -> StreamId) -> IO UUID -> IO StreamId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO UUID
UUID.nextRandom
streamB <- StreamId <$> UUID.nextRandom
result1 <-
insertEvents store Nothing $
Transaction
( Map.fromList
[ (streamA, StreamWrite NoStream [makeUserEvent 1])
, (streamB, StreamWrite NoStream [makeUserEvent 10])
]
)
case result1 of
FailedInsertion EventStoreError backend
err -> TestName -> Assertion
forall a. HasCallStack => TestName -> IO a
assertFailure (TestName -> Assertion) -> TestName -> Assertion
forall a b. (a -> b) -> a -> b
$ TestName
"Initial write failed: " TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ EventStoreError backend -> TestName
forall a. Show a => a -> TestName
show EventStoreError backend
err
SuccessfulInsertion (InsertionSuccess{Map StreamId (Cursor backend)
streamCursors :: forall backend.
InsertionSuccess backend -> Map StreamId (Cursor backend)
streamCursors :: Map StreamId (Cursor backend)
streamCursors}) -> do
case (StreamId -> Map StreamId (Cursor backend) -> Maybe (Cursor backend)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup StreamId
streamA Map StreamId (Cursor backend)
streamCursors, StreamId -> Map StreamId (Cursor backend) -> Maybe (Cursor backend)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup StreamId
streamB Map StreamId (Cursor backend)
streamCursors) of
(Just Cursor backend
cursorA, Just Cursor backend
cursorB) -> do
result2 <-
BackendHandle backend
-> Maybe CorrelationId
-> Transaction [] backend
-> IO (InsertionResult backend)
forall backend (t :: * -> *) (m :: * -> *).
(EventStore backend, Traversable t, StoreConstraints backend m) =>
BackendHandle backend
-> Maybe CorrelationId
-> Transaction t backend
-> m (InsertionResult backend)
forall (t :: * -> *) (m :: * -> *).
(Traversable t, StoreConstraints backend m) =>
BackendHandle backend
-> Maybe CorrelationId
-> Transaction t backend
-> m (InsertionResult backend)
insertEvents BackendHandle backend
store Maybe CorrelationId
forall a. Maybe a
Nothing (Transaction [] backend -> IO (InsertionResult backend))
-> Transaction [] backend -> IO (InsertionResult backend)
forall a b. (a -> b) -> a -> b
$
StreamId
-> ExpectedVersion backend
-> SomeLatestEvent
-> Transaction [] backend
forall backend.
StreamId
-> ExpectedVersion backend
-> SomeLatestEvent
-> Transaction [] backend
singleEvent StreamId
streamA (Cursor backend -> ExpectedVersion backend
forall backend. Cursor backend -> ExpectedVersion backend
ExactVersion Cursor backend
cursorA) (Int -> SomeLatestEvent
makeUserEvent Int
2)
case result2 of
FailedInsertion EventStoreError backend
err -> TestName -> Assertion
forall a. HasCallStack => TestName -> IO a
assertFailure (TestName -> Assertion) -> TestName -> Assertion
forall a b. (a -> b) -> a -> b
$ TestName
"Stream A update failed: " TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ EventStoreError backend -> TestName
forall a. Show a => a -> TestName
show EventStoreError backend
err
SuccessfulInsertion InsertionSuccess backend
_ -> do
result3 <-
BackendHandle backend
-> Maybe CorrelationId
-> Transaction [] backend
-> IO (InsertionResult backend)
forall backend (t :: * -> *) (m :: * -> *).
(EventStore backend, Traversable t, StoreConstraints backend m) =>
BackendHandle backend
-> Maybe CorrelationId
-> Transaction t backend
-> m (InsertionResult backend)
forall (t :: * -> *) (m :: * -> *).
(Traversable t, StoreConstraints backend m) =>
BackendHandle backend
-> Maybe CorrelationId
-> Transaction t backend
-> m (InsertionResult backend)
insertEvents BackendHandle backend
store Maybe CorrelationId
forall a. Maybe a
Nothing (Transaction [] backend -> IO (InsertionResult backend))
-> Transaction [] backend -> IO (InsertionResult backend)
forall a b. (a -> b) -> a -> b
$
StreamId
-> ExpectedVersion backend
-> SomeLatestEvent
-> Transaction [] backend
forall backend.
StreamId
-> ExpectedVersion backend
-> SomeLatestEvent
-> Transaction [] backend
singleEvent StreamId
streamB (Cursor backend -> ExpectedVersion backend
forall backend. Cursor backend -> ExpectedVersion backend
ExactVersion Cursor backend
cursorB) (Int -> SomeLatestEvent
makeUserEvent Int
11)
case result3 of
FailedInsertion EventStoreError backend
err ->
TestName -> Assertion
forall a. HasCallStack => TestName -> IO a
assertFailure (TestName -> Assertion) -> TestName -> Assertion
forall a b. (a -> b) -> a -> b
$ TestName
"Stream B cursor should still be valid after stream A update: " TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ EventStoreError backend -> TestName
forall a. Show a => a -> TestName
show EventStoreError backend
err
SuccessfulInsertion InsertionSuccess backend
_ -> () -> Assertion
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
(Maybe (Cursor backend), Maybe (Cursor backend))
_ -> TestName -> Assertion
forall a. HasCallStack => TestName -> IO a
assertFailure TestName
"Missing cursors from initial transaction"
testStaleCursorPerStream :: forall backend. (EventStore backend, StoreConstraints backend IO, Show (Cursor backend)) => BackendHandle backend -> IO ()
testStaleCursorPerStream :: forall backend.
(EventStore backend, StoreConstraints backend IO,
Show (Cursor backend)) =>
BackendHandle backend -> Assertion
testStaleCursorPerStream BackendHandle backend
store = do
streamA <- UUID -> StreamId
StreamId (UUID -> StreamId) -> IO UUID -> IO StreamId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO UUID
UUID.nextRandom
streamB <- StreamId <$> UUID.nextRandom
result1 <-
insertEvents store Nothing $
Transaction
( Map.fromList
[ (streamA, StreamWrite NoStream [makeUserEvent 1])
, (streamB, StreamWrite NoStream [makeUserEvent 10])
]
)
case result1 of
FailedInsertion EventStoreError backend
err -> TestName -> Assertion
forall a. HasCallStack => TestName -> IO a
assertFailure (TestName -> Assertion) -> TestName -> Assertion
forall a b. (a -> b) -> a -> b
$ TestName
"Initial write failed: " TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ EventStoreError backend -> TestName
forall a. Show a => a -> TestName
show EventStoreError backend
err
SuccessfulInsertion (InsertionSuccess{Map StreamId (Cursor backend)
streamCursors :: forall backend.
InsertionSuccess backend -> Map StreamId (Cursor backend)
streamCursors :: Map StreamId (Cursor backend)
streamCursors}) -> do
case (StreamId -> Map StreamId (Cursor backend) -> Maybe (Cursor backend)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup StreamId
streamA Map StreamId (Cursor backend)
streamCursors, StreamId -> Map StreamId (Cursor backend) -> Maybe (Cursor backend)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup StreamId
streamB Map StreamId (Cursor backend)
streamCursors) of
(Just Cursor backend
cursorA, Just Cursor backend
cursorB) -> do
result2 <-
BackendHandle backend
-> Maybe CorrelationId
-> Transaction [] backend
-> IO (InsertionResult backend)
forall backend (t :: * -> *) (m :: * -> *).
(EventStore backend, Traversable t, StoreConstraints backend m) =>
BackendHandle backend
-> Maybe CorrelationId
-> Transaction t backend
-> m (InsertionResult backend)
forall (t :: * -> *) (m :: * -> *).
(Traversable t, StoreConstraints backend m) =>
BackendHandle backend
-> Maybe CorrelationId
-> Transaction t backend
-> m (InsertionResult backend)
insertEvents BackendHandle backend
store Maybe CorrelationId
forall a. Maybe a
Nothing (Transaction [] backend -> IO (InsertionResult backend))
-> Transaction [] backend -> IO (InsertionResult backend)
forall a b. (a -> b) -> a -> b
$
StreamId
-> ExpectedVersion backend
-> SomeLatestEvent
-> Transaction [] backend
forall backend.
StreamId
-> ExpectedVersion backend
-> SomeLatestEvent
-> Transaction [] backend
singleEvent StreamId
streamA (Cursor backend -> ExpectedVersion backend
forall backend. Cursor backend -> ExpectedVersion backend
ExactVersion Cursor backend
cursorA) (Int -> SomeLatestEvent
makeUserEvent Int
2)
case result2 of
FailedInsertion EventStoreError backend
err -> TestName -> Assertion
forall a. HasCallStack => TestName -> IO a
assertFailure (TestName -> Assertion) -> TestName -> Assertion
forall a b. (a -> b) -> a -> b
$ TestName
"Stream A update failed: " TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ EventStoreError backend -> TestName
forall a. Show a => a -> TestName
show EventStoreError backend
err
SuccessfulInsertion InsertionSuccess backend
_ -> do
result3 <-
BackendHandle backend
-> Maybe CorrelationId
-> Transaction [] backend
-> IO (InsertionResult backend)
forall backend (t :: * -> *) (m :: * -> *).
(EventStore backend, Traversable t, StoreConstraints backend m) =>
BackendHandle backend
-> Maybe CorrelationId
-> Transaction t backend
-> m (InsertionResult backend)
forall (t :: * -> *) (m :: * -> *).
(Traversable t, StoreConstraints backend m) =>
BackendHandle backend
-> Maybe CorrelationId
-> Transaction t backend
-> m (InsertionResult backend)
insertEvents BackendHandle backend
store Maybe CorrelationId
forall a. Maybe a
Nothing (Transaction [] backend -> IO (InsertionResult backend))
-> Transaction [] backend -> IO (InsertionResult backend)
forall a b. (a -> b) -> a -> b
$
Map StreamId (StreamWrite [] SomeLatestEvent backend)
-> Transaction [] backend
forall (t :: * -> *) backend.
Map StreamId (StreamWrite t SomeLatestEvent backend)
-> Transaction t backend
Transaction
( [(StreamId, StreamWrite [] SomeLatestEvent backend)]
-> Map StreamId (StreamWrite [] SomeLatestEvent backend)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
[ (StreamId
streamA, ExpectedVersion backend
-> [SomeLatestEvent] -> StreamWrite [] SomeLatestEvent backend
forall {k} (t :: k -> *) (e :: k) backend.
ExpectedVersion backend -> t e -> StreamWrite t e backend
StreamWrite (Cursor backend -> ExpectedVersion backend
forall backend. Cursor backend -> ExpectedVersion backend
ExactVersion Cursor backend
cursorA) [Int -> SomeLatestEvent
makeUserEvent Int
3])
, (StreamId
streamB, ExpectedVersion backend
-> [SomeLatestEvent] -> StreamWrite [] SomeLatestEvent backend
forall {k} (t :: k -> *) (e :: k) backend.
ExpectedVersion backend -> t e -> StreamWrite t e backend
StreamWrite (Cursor backend -> ExpectedVersion backend
forall backend. Cursor backend -> ExpectedVersion backend
ExactVersion Cursor backend
cursorB) [Int -> SomeLatestEvent
makeUserEvent Int
11])
]
)
case result3 of
FailedInsertion (ConsistencyError ConsistencyErrorInfo backend
_) -> () -> Assertion
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
InsertionResult backend
_ -> TestName -> Assertion
forall a. HasCallStack => TestName -> IO a
assertFailure TestName
"Transaction with stale cursor should fail atomically"
(Maybe (Cursor backend), Maybe (Cursor backend))
_ -> TestName -> Assertion
forall a. HasCallStack => TestName -> IO a
assertFailure TestName
"Missing cursors from initial transaction"
testCursorCompleteness :: forall backend. (EventStore backend, StoreConstraints backend IO, Show (Cursor backend), Ord (Cursor backend)) => BackendHandle backend -> IO ()
testCursorCompleteness :: forall backend.
(EventStore backend, StoreConstraints backend IO,
Show (Cursor backend), Ord (Cursor backend)) =>
BackendHandle backend -> Assertion
testCursorCompleteness BackendHandle backend
store = do
streamA <- UUID -> StreamId
StreamId (UUID -> StreamId) -> IO UUID -> IO StreamId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO UUID
UUID.nextRandom
streamB <- StreamId <$> UUID.nextRandom
streamC <- StreamId <$> UUID.nextRandom
result <-
insertEvents store Nothing $
Transaction
( Map.fromList
[ (streamA, StreamWrite NoStream [makeUserEvent 1, makeUserEvent 2])
, (streamB, StreamWrite NoStream [makeUserEvent 10])
, (streamC, StreamWrite NoStream [makeUserEvent 100, makeUserEvent 101, makeUserEvent 102])
]
)
case result of
FailedInsertion EventStoreError backend
err -> TestName -> Assertion
forall a. HasCallStack => TestName -> IO a
assertFailure (TestName -> Assertion) -> TestName -> Assertion
forall a b. (a -> b) -> a -> b
$ TestName
"Multi-stream write failed: " TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ EventStoreError backend -> TestName
forall a. Show a => a -> TestName
show EventStoreError backend
err
SuccessfulInsertion (InsertionSuccess{Cursor backend
finalCursor :: Cursor backend
finalCursor :: forall backend. InsertionSuccess backend -> Cursor backend
finalCursor, Map StreamId (Cursor backend)
streamCursors :: forall backend.
InsertionSuccess backend -> Map StreamId (Cursor backend)
streamCursors :: Map StreamId (Cursor backend)
streamCursors}) -> do
Map StreamId (Cursor backend) -> Int
forall k a. Map k a -> Int
Map.size Map StreamId (Cursor backend)
streamCursors Int -> Int -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Int
3
HasCallStack => TestName -> Bool -> Assertion
TestName -> Bool -> Assertion
assertBool TestName
"Stream A missing from cursors" (StreamId -> Map StreamId (Cursor backend) -> Bool
forall k a. Ord k => k -> Map k a -> Bool
Map.member StreamId
streamA Map StreamId (Cursor backend)
streamCursors)
HasCallStack => TestName -> Bool -> Assertion
TestName -> Bool -> Assertion
assertBool TestName
"Stream B missing from cursors" (StreamId -> Map StreamId (Cursor backend) -> Bool
forall k a. Ord k => k -> Map k a -> Bool
Map.member StreamId
streamB Map StreamId (Cursor backend)
streamCursors)
HasCallStack => TestName -> Bool -> Assertion
TestName -> Bool -> Assertion
assertBool TestName
"Stream C missing from cursors" (StreamId -> Map StreamId (Cursor backend) -> Bool
forall k a. Ord k => k -> Map k a -> Bool
Map.member StreamId
streamC Map StreamId (Cursor backend)
streamCursors)
[(StreamId, Cursor backend)]
-> ((StreamId, Cursor backend) -> Assertion) -> Assertion
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (Map StreamId (Cursor backend) -> [(StreamId, Cursor backend)]
forall k a. Map k a -> [(k, a)]
Map.toList Map StreamId (Cursor backend)
streamCursors) (((StreamId, Cursor backend) -> Assertion) -> Assertion)
-> ((StreamId, Cursor backend) -> Assertion) -> Assertion
forall a b. (a -> b) -> a -> b
$ \(StreamId
sid, Cursor backend
cursor) ->
HasCallStack => TestName -> Bool -> Assertion
TestName -> Bool -> Assertion
assertBool
(TestName
"Cursor for " TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ StreamId -> TestName
forall a. Show a => a -> TestName
show StreamId
sid TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ TestName
" violates ordering invariant")
(Cursor backend
cursor Cursor backend -> Cursor backend -> Bool
forall a. Ord a => a -> a -> Bool
<= Cursor backend
finalCursor)
case (StreamId -> Map StreamId (Cursor backend) -> Maybe (Cursor backend)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup StreamId
streamA Map StreamId (Cursor backend)
streamCursors, StreamId -> Map StreamId (Cursor backend) -> Maybe (Cursor backend)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup StreamId
streamB Map StreamId (Cursor backend)
streamCursors, StreamId -> Map StreamId (Cursor backend) -> Maybe (Cursor backend)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup StreamId
streamC Map StreamId (Cursor backend)
streamCursors) of
(Just Cursor backend
cursorA, Just Cursor backend
cursorB, Just Cursor backend
cursorC) -> do
resultA <- BackendHandle backend
-> Maybe CorrelationId
-> Transaction [] backend
-> IO (InsertionResult backend)
forall backend (t :: * -> *) (m :: * -> *).
(EventStore backend, Traversable t, StoreConstraints backend m) =>
BackendHandle backend
-> Maybe CorrelationId
-> Transaction t backend
-> m (InsertionResult backend)
forall (t :: * -> *) (m :: * -> *).
(Traversable t, StoreConstraints backend m) =>
BackendHandle backend
-> Maybe CorrelationId
-> Transaction t backend
-> m (InsertionResult backend)
insertEvents BackendHandle backend
store Maybe CorrelationId
forall a. Maybe a
Nothing (Transaction [] backend -> IO (InsertionResult backend))
-> Transaction [] backend -> IO (InsertionResult backend)
forall a b. (a -> b) -> a -> b
$ StreamId
-> ExpectedVersion backend
-> SomeLatestEvent
-> Transaction [] backend
forall backend.
StreamId
-> ExpectedVersion backend
-> SomeLatestEvent
-> Transaction [] backend
singleEvent StreamId
streamA (Cursor backend -> ExpectedVersion backend
forall backend. Cursor backend -> ExpectedVersion backend
ExactVersion Cursor backend
cursorA) (Int -> SomeLatestEvent
makeUserEvent Int
3)
resultB <- insertEvents store Nothing $ singleEvent streamB (ExactVersion cursorB) (makeUserEvent 11)
resultC <- insertEvents store Nothing $ singleEvent streamC (ExactVersion cursorC) (makeUserEvent 103)
case (resultA, resultB, resultC) of
(SuccessfulInsertion InsertionSuccess backend
_, SuccessfulInsertion InsertionSuccess backend
_, SuccessfulInsertion InsertionSuccess backend
_) -> () -> Assertion
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
(InsertionResult backend, InsertionResult backend,
InsertionResult backend)
_ -> TestName -> Assertion
forall a. HasCallStack => TestName -> IO a
assertFailure TestName
"One or more stream cursors were not usable"
(Maybe (Cursor backend), Maybe (Cursor backend),
Maybe (Cursor backend))
_ -> TestName -> Assertion
forall a. HasCallStack => TestName -> IO a
assertFailure TestName
"Failed to extract all cursors from map"
testEmptyStreamCursorHandling :: forall backend. (EventStore backend, StoreConstraints backend IO, Show (Cursor backend)) => BackendHandle backend -> IO ()
testEmptyStreamCursorHandling :: forall backend.
(EventStore backend, StoreConstraints backend IO,
Show (Cursor backend)) =>
BackendHandle backend -> Assertion
testEmptyStreamCursorHandling BackendHandle backend
store = do
streamA <- UUID -> StreamId
StreamId (UUID -> StreamId) -> IO UUID -> IO StreamId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO UUID
UUID.nextRandom
streamB <- StreamId <$> UUID.nextRandom
streamC <- StreamId <$> UUID.nextRandom
result <-
insertEvents store Nothing $
Transaction
( Map.fromList
[ (streamA, StreamWrite NoStream [makeUserEvent 1])
, (streamB, StreamWrite NoStream [])
, (streamC, StreamWrite NoStream [makeUserEvent 100])
]
)
case result of
FailedInsertion EventStoreError backend
err -> TestName -> Assertion
forall a. HasCallStack => TestName -> IO a
assertFailure (TestName -> Assertion) -> TestName -> Assertion
forall a b. (a -> b) -> a -> b
$ TestName
"Multi-stream with empty stream failed: " TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ EventStoreError backend -> TestName
forall a. Show a => a -> TestName
show EventStoreError backend
err
SuccessfulInsertion (InsertionSuccess{Map StreamId (Cursor backend)
streamCursors :: forall backend.
InsertionSuccess backend -> Map StreamId (Cursor backend)
streamCursors :: Map StreamId (Cursor backend)
streamCursors}) -> do
HasCallStack => TestName -> Bool -> Assertion
TestName -> Bool -> Assertion
assertBool TestName
"Stream A should have cursor (has events)" (StreamId -> Map StreamId (Cursor backend) -> Bool
forall k a. Ord k => k -> Map k a -> Bool
Map.member StreamId
streamA Map StreamId (Cursor backend)
streamCursors)
HasCallStack => TestName -> Bool -> Assertion
TestName -> Bool -> Assertion
assertBool TestName
"Stream C should have cursor (has events)" (StreamId -> Map StreamId (Cursor backend) -> Bool
forall k a. Ord k => k -> Map k a -> Bool
Map.member StreamId
streamC Map StreamId (Cursor backend)
streamCursors)
case StreamId -> Map StreamId (Cursor backend) -> Maybe (Cursor backend)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup StreamId
streamB Map StreamId (Cursor backend)
streamCursors of
Maybe (Cursor backend)
Nothing -> do
resultB <-
BackendHandle backend
-> Maybe CorrelationId
-> Transaction [] backend
-> IO (InsertionResult backend)
forall backend (t :: * -> *) (m :: * -> *).
(EventStore backend, Traversable t, StoreConstraints backend m) =>
BackendHandle backend
-> Maybe CorrelationId
-> Transaction t backend
-> m (InsertionResult backend)
forall (t :: * -> *) (m :: * -> *).
(Traversable t, StoreConstraints backend m) =>
BackendHandle backend
-> Maybe CorrelationId
-> Transaction t backend
-> m (InsertionResult backend)
insertEvents BackendHandle backend
store Maybe CorrelationId
forall a. Maybe a
Nothing (Transaction [] backend -> IO (InsertionResult backend))
-> Transaction [] backend -> IO (InsertionResult backend)
forall a b. (a -> b) -> a -> b
$
StreamId
-> ExpectedVersion backend
-> SomeLatestEvent
-> Transaction [] backend
forall backend.
StreamId
-> ExpectedVersion backend
-> SomeLatestEvent
-> Transaction [] backend
singleEvent StreamId
streamB ExpectedVersion backend
forall backend. ExpectedVersion backend
NoStream (Int -> SomeLatestEvent
makeUserEvent Int
10)
case resultB of
FailedInsertion EventStoreError backend
err -> TestName -> Assertion
forall a. HasCallStack => TestName -> IO a
assertFailure (TestName -> Assertion) -> TestName -> Assertion
forall a b. (a -> b) -> a -> b
$ TestName
"Stream B should not exist after empty write: " TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ EventStoreError backend -> TestName
forall a. Show a => a -> TestName
show EventStoreError backend
err
SuccessfulInsertion InsertionSuccess backend
_ -> () -> Assertion
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just Cursor backend
cursorB -> do
resultB <-
BackendHandle backend
-> Maybe CorrelationId
-> Transaction [] backend
-> IO (InsertionResult backend)
forall backend (t :: * -> *) (m :: * -> *).
(EventStore backend, Traversable t, StoreConstraints backend m) =>
BackendHandle backend
-> Maybe CorrelationId
-> Transaction t backend
-> m (InsertionResult backend)
forall (t :: * -> *) (m :: * -> *).
(Traversable t, StoreConstraints backend m) =>
BackendHandle backend
-> Maybe CorrelationId
-> Transaction t backend
-> m (InsertionResult backend)
insertEvents BackendHandle backend
store Maybe CorrelationId
forall a. Maybe a
Nothing (Transaction [] backend -> IO (InsertionResult backend))
-> Transaction [] backend -> IO (InsertionResult backend)
forall a b. (a -> b) -> a -> b
$
StreamId
-> ExpectedVersion backend
-> SomeLatestEvent
-> Transaction [] backend
forall backend.
StreamId
-> ExpectedVersion backend
-> SomeLatestEvent
-> Transaction [] backend
singleEvent StreamId
streamB (Cursor backend -> ExpectedVersion backend
forall backend. Cursor backend -> ExpectedVersion backend
ExactVersion Cursor backend
cursorB) (Int -> SomeLatestEvent
makeUserEvent Int
10)
case resultB of
FailedInsertion EventStoreError backend
err ->
TestName -> Assertion
forall a. HasCallStack => TestName -> IO a
assertFailure (TestName -> Assertion) -> TestName -> Assertion
forall a b. (a -> b) -> a -> b
$ TestName
"If empty stream gets cursor, it should be usable: " TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ EventStoreError backend -> TestName
forall a. Show a => a -> TestName
show EventStoreError backend
err
SuccessfulInsertion InsertionSuccess backend
_ -> () -> Assertion
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()