Skip to content

Commit 93384cc

Browse files
committed
fix: restructure TableNotCompatibleError to TableUnionNotCompatibleError
1 parent 2f995b2 commit 93384cc

File tree

7 files changed

+66
-66
lines changed

7 files changed

+66
-66
lines changed

src/Database/LSMTree.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,7 @@ module Database.LSMTree (
1616
, Common.TableClosedError (..)
1717
, Common.TableCorruptedError (..)
1818
, Common.TableTooLargeError (..)
19-
, Common.TableNotCompatibleError (..)
19+
, Common.TableUnionNotCompatibleError (..)
2020
, Common.SnapshotExistsError (..)
2121
, Common.SnapshotDoesNotExistError (..)
2222
, Common.SnapshotCorruptedError (..)
@@ -129,7 +129,8 @@ import Data.Bifunctor (Bifunctor (..))
129129
import Data.Coerce (coerce)
130130
import Data.Kind (Type)
131131
import Data.List.NonEmpty (NonEmpty (..))
132-
import Data.Typeable (Proxy (..), Typeable, eqT, type (:~:) (Refl))
132+
import Data.Typeable (Proxy (..), Typeable, eqT, type (:~:) (Refl),
133+
typeRep)
133134
import qualified Data.Vector as V
134135
import Database.LSMTree.Common (BlobRef (BlobRef), IOLike, Range (..),
135136
SerialiseKey, SerialiseValue, Session, UnionCredits (..),
@@ -570,7 +571,7 @@ unions (t :| ts) =
570571
-> m (Internal.Table m h)
571572
checkTableType _ i (Internal.Table' (t' :: Internal.Table m h'))
572573
| Just Refl <- eqT @h @h' = pure t'
573-
| otherwise = throwIO (Common.ErrTableTypeMismatch 0 i)
574+
| otherwise = throwIO $ Common.ErrTableUnionHandleTypeMismatch 0 (typeRep $ Proxy @h) i (typeRep $ Proxy @h')
574575

575576
{-# SPECIALISE remainingUnionDebt :: Table IO k v b -> IO UnionDebt #-}
576577
remainingUnionDebt :: IOLike m => Table m k v b -> m UnionDebt

src/Database/LSMTree/Common.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ module Database.LSMTree.Common (
99
, Internal.TableClosedError (..)
1010
, Internal.TableCorruptedError (..)
1111
, Internal.TableTooLargeError (..)
12-
, Internal.TableNotCompatibleError (..)
12+
, Internal.TableUnionNotCompatibleError (..)
1313
, Internal.SnapshotExistsError (..)
1414
, Internal.SnapshotDoesNotExistError (..)
1515
, Internal.SnapshotCorruptedError (..)

src/Database/LSMTree/Internal.hs

Lines changed: 43 additions & 46 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ module Database.LSMTree.Internal (
2828
, TableClosedError (..)
2929
, TableCorruptedError (..)
3030
, TableTooLargeError (..)
31-
, TableNotCompatibleError (..)
31+
, TableUnionNotCompatibleError (..)
3232
, SnapshotExistsError (..)
3333
, SnapshotDoesNotExistError (..)
3434
, SnapshotCorruptedError (..)
@@ -1534,27 +1534,30 @@ duplicate t@Table{..} = do
15341534
tableArenaManager
15351535
content
15361536

1537-
15381537
{-------------------------------------------------------------------------------
15391538
Table union
15401539
-------------------------------------------------------------------------------}
15411540

1542-
-- | An operation was called with two tables that are not compatible.
1543-
data TableNotCompatibleError
1544-
= -- | An operation was called with two tables that are not of the same type.
1545-
--
1546-
-- TODO: This error is no longer used by 'unions'.
1547-
ErrTableTypeMismatch
1548-
-- | Vector index of table @t1@ involved in the mismatch
1549-
Int
1550-
-- | Vector index of table @t2@ involved in the mismatch
1551-
Int
1552-
| -- | An operation was called with two tables that are not in the same session.
1553-
ErrTableSessionMismatch
1554-
-- | Vector index of table @t1@ involved in the mismatch
1555-
Int
1556-
-- | Vector index of table @t2@ involved in the mismatch
1557-
Int
1541+
-- | A table union was constructed with two tables that are not compatible.
1542+
data TableUnionNotCompatibleError
1543+
= ErrTableUnionHandleTypeMismatch
1544+
-- | The index of the first table.
1545+
!Int
1546+
-- | The type of the filesystem handle of the first table.
1547+
!TypeRep
1548+
-- | The index of the second table.
1549+
!Int
1550+
-- | The type of the filesystem handle of the second table.
1551+
!TypeRep
1552+
| ErrTableUnionSessionMismatch
1553+
-- | The index of the first table.
1554+
!Int
1555+
-- | The session directory of the first table.
1556+
!FsErrorPath
1557+
-- | The index of the second table.
1558+
!Int
1559+
-- | The session directory of the second table.
1560+
!FsErrorPath
15581561
deriving stock (Show, Eq)
15591562
deriving anyclass (Exception)
15601563

@@ -1565,10 +1568,7 @@ unions ::
15651568
=> NonEmpty (Table m h)
15661569
-> m (Table m h)
15671570
unions ts = do
1568-
sesh <-
1569-
matchSessions ts >>= \case
1570-
Left (i, j) -> throwIO $ ErrTableSessionMismatch i j
1571-
Right sesh -> pure sesh
1571+
sesh <- ensureSessionsMatch ts
15721572

15731573
traceWith (sessionTracer sesh) $ TraceUnions (NE.map tableId ts)
15741574

@@ -1706,37 +1706,34 @@ writeBufferToNewRun SessionEnv {
17061706
tableWriteBuffer
17071707
tableWriteBufferBlobs
17081708

1709-
-- | Check that all tables in the session match. If so, return the matched
1710-
-- session. If there is a mismatch, return the list indices of the mismatching
1711-
-- tables.
1712-
--
1713-
-- TODO: compare LockFileHandle instead of SessionRoot (?). We can write an Eq
1714-
-- instance for LockFileHandle based on pointer equality, just like base does
1715-
-- for Handle.
1716-
matchSessions ::
1709+
{-# SPECIALISE ensureSessionsMatch ::
1710+
NonEmpty (Table IO h)
1711+
-> IO (Session IO h) #-}
1712+
-- | Check if all tables have the same session.
1713+
-- If so, return the session.
1714+
-- Otherwise, throw a 'TableUnionNotCompatibleError'.
1715+
ensureSessionsMatch ::
17171716
(MonadSTM m, MonadThrow m)
17181717
=> NonEmpty (Table m h)
1719-
-> m (Either (Int, Int) (Session m h))
1720-
matchSessions = \(t :| ts) ->
1721-
withSessionRoot t $ \root -> do
1722-
eith <- go root 1 ts
1723-
pure $ case eith of
1724-
Left i -> Left (0, i)
1725-
Right () -> Right (tableSession t)
1726-
where
1718+
-> m (Session m h)
1719+
ensureSessionsMatch (t :| ts) = do
1720+
let sesh = tableSession t
1721+
withOpenSession sesh $ \seshEnv -> do
1722+
let root = FS.mkFsErrorPath (sessionHasFS seshEnv) (getSessionRoot (sessionRoot seshEnv))
17271723
-- Check that the session roots for all tables are the same. There can only
17281724
-- be one *open/active* session per directory because of cooperative file
17291725
-- locks, so each unique *open* session has a unique session root. We check
17301726
-- that all the table's sessions are open at the same time while comparing
17311727
-- the session roots.
1732-
go _ _ [] = pure (Right ())
1733-
go root !i (t':ts') =
1734-
withSessionRoot t' $ \root' ->
1735-
if root == root'
1736-
then go root (i+1) ts'
1737-
else pure (Left i)
1738-
1739-
withSessionRoot t k = withOpenSession (tableSession t) $ k . sessionRoot
1728+
for_ (zip [1..] ts) $ \(i, t') -> do
1729+
let sesh' = tableSession t'
1730+
withOpenSession sesh' $ \seshEnv' -> do
1731+
let root' = FS.mkFsErrorPath (sessionHasFS seshEnv') (getSessionRoot (sessionRoot seshEnv'))
1732+
-- TODO: compare LockFileHandle instead of SessionRoot (?).
1733+
-- We can write an Eq instance for LockFileHandle based on pointer equality,
1734+
-- just like base does for Handle.
1735+
unless (root == root') $ throwIO $ ErrTableUnionSessionMismatch 0 root i root'
1736+
pure sesh
17401737

17411738
{-------------------------------------------------------------------------------
17421739
Table union: debt and credit

src/Database/LSMTree/Monoidal.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,7 @@ module Database.LSMTree.Monoidal (
3131
, Common.TableClosedError (..)
3232
, Common.TableCorruptedError (..)
3333
, Common.TableTooLargeError (..)
34-
, Common.TableNotCompatibleError (..)
34+
, Common.TableUnionNotCompatibleError (..)
3535
, Common.SnapshotExistsError (..)
3636
, Common.SnapshotDoesNotExistError (..)
3737
, Common.SnapshotCorruptedError (..)
@@ -149,8 +149,8 @@ import Data.Coerce (coerce)
149149
import Data.Kind (Type)
150150
import Data.List.NonEmpty (NonEmpty (..))
151151
import Data.Monoid (Sum (..))
152-
import Data.Proxy (Proxy (Proxy))
153-
import Data.Typeable (Typeable, eqT, type (:~:) (Refl))
152+
import Data.Typeable (Proxy (..), Typeable, eqT, type (:~:) (Refl),
153+
typeRep)
154154
import qualified Data.Vector as V
155155
import Database.LSMTree.Common (IOLike, Range (..), SerialiseKey,
156156
SerialiseValue (..), Session, UnionCredits (..),
@@ -719,7 +719,7 @@ unions (t :| ts) =
719719
-> m (Internal.Table m h)
720720
checkTableType _ i (Internal.MonoidalTable (t' :: Internal.Table m h'))
721721
| Just Refl <- eqT @h @h' = pure t'
722-
| otherwise = throwIO (Common.ErrTableTypeMismatch 0 i)
722+
| otherwise = throwIO $ Common.ErrTableUnionHandleTypeMismatch 0 (typeRep $ Proxy @h) i (typeRep $ Proxy @h')
723723

724724
{-# SPECIALISE remainingUnionDebt :: Table IO k v -> IO UnionDebt #-}
725725
-- | Return the current union debt. This debt can be reduced until it is paid

src/Database/LSMTree/Normal.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,7 @@ module Database.LSMTree.Normal (
3030
, Common.TableClosedError (..)
3131
, Common.TableCorruptedError (..)
3232
, Common.TableTooLargeError (..)
33-
, Common.TableNotCompatibleError (..)
33+
, Common.TableUnionNotCompatibleError (..)
3434
, Common.SnapshotExistsError (..)
3535
, Common.SnapshotDoesNotExistError (..)
3636
, Common.SnapshotCorruptedError (..)
@@ -140,7 +140,8 @@ import Control.Monad.Class.MonadThrow
140140
import Data.Bifunctor (Bifunctor (..))
141141
import Data.Kind (Type)
142142
import Data.List.NonEmpty (NonEmpty (..))
143-
import Data.Typeable (Typeable, eqT, type (:~:) (Refl))
143+
import Data.Typeable (Proxy (..), Typeable, eqT, type (:~:) (Refl),
144+
typeRep)
144145
import qualified Data.Vector as V
145146
import Database.LSMTree.Common (BlobRef (BlobRef), IOLike, Range (..),
146147
SerialiseKey, SerialiseValue, Session, UnionCredits (..),
@@ -839,7 +840,7 @@ unions (t :| ts) =
839840
-> m (Internal.Table m h)
840841
checkTableType _ i (Internal.NormalTable (t' :: Internal.Table m h'))
841842
| Just Refl <- eqT @h @h' = pure t'
842-
| otherwise = throwIO (Common.ErrTableTypeMismatch 0 i)
843+
| otherwise = throwIO $ Common.ErrTableUnionHandleTypeMismatch 0 (typeRep $ Proxy @h) i (typeRep $ Proxy @h')
843844

844845
{-# SPECIALISE remainingUnionDebt :: Table IO k v b -> IO UnionDebt #-}
845846
-- | Return the current union debt. This debt can be reduced until it is paid

test/Database/LSMTree/Model/Session.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -267,8 +267,8 @@ data Err
267267
| ErrSessionClosed
268268
| ErrTableClosed
269269
| ErrTableCorrupted
270-
| ErrTableTypeMismatch
271-
| ErrTableSessionMismatch
270+
| ErrTableUnionHandleTypeMismatch
271+
| ErrTableUnionSessionMismatch
272272
| ErrSnapshotExists !SnapshotName
273273
| ErrSnapshotDoesNotExist !SnapshotName
274274
| ErrSnapshotCorrupted !SnapshotName

test/Test/Database/LSMTree/StateMachine.hs

Lines changed: 8 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -94,7 +94,8 @@ import Database.LSMTree.Common (BlobRefInvalidError (..),
9494
SessionDirLockedError (..), SnapshotCorruptedError (..),
9595
SnapshotDoesNotExistError (..), SnapshotExistsError (..),
9696
SnapshotNotCompatibleError (..), TableClosedError (..),
97-
TableCorruptedError (..), TableNotCompatibleError (..))
97+
TableCorruptedError (..),
98+
TableUnionNotCompatibleError (..))
9899
import Database.LSMTree.Extras (showPowersOf)
99100
import Database.LSMTree.Extras.Generators (KeyForIndexCompact)
100101
import Database.LSMTree.Extras.NoThunks (propNoThunks)
@@ -483,7 +484,7 @@ handleSomeException e =
483484
, handleSessionClosedError <$> fromException e
484485
, handleTableClosedError <$> fromException e
485486
, handleTableCorruptedError <$> fromException e
486-
, handleTableNotCompatibleError <$> fromException e
487+
, handleTableUnionNotCompatibleError <$> fromException e
487488
, handleSnapshotExistsError <$> fromException e
488489
, handleSnapshotDoesNotExistError <$> fromException e
489490
, handleSnapshotCorruptedError <$> fromException e
@@ -528,12 +529,12 @@ handleTableClosedError = \case
528529

529530
handleTableCorruptedError :: TableCorruptedError -> Model.Err
530531
handleTableCorruptedError = \case
531-
ErrLookupByteCountDiscrepancy _ _ -> Model.ErrTableCorrupted
532+
ErrLookupByteCountDiscrepancy{} -> Model.ErrTableCorrupted
532533

533-
handleTableNotCompatibleError :: TableNotCompatibleError -> Model.Err
534-
handleTableNotCompatibleError = \case
535-
ErrTableTypeMismatch _ _ -> Model.ErrTableTypeMismatch
536-
ErrTableSessionMismatch _ _ -> Model.ErrTableSessionMismatch
534+
handleTableUnionNotCompatibleError :: TableUnionNotCompatibleError -> Model.Err
535+
handleTableUnionNotCompatibleError = \case
536+
ErrTableUnionHandleTypeMismatch{} -> Model.ErrTableUnionHandleTypeMismatch
537+
ErrTableUnionSessionMismatch{} -> Model.ErrTableUnionSessionMismatch
537538

538539
handleSnapshotExistsError :: SnapshotExistsError -> Model.Err
539540
handleSnapshotExistsError = \case

0 commit comments

Comments
 (0)