@@ -36,7 +36,7 @@ module Database.LSMTree.Internal.Unsafe (
3636 , Session (.. )
3737 , SessionState (.. )
3838 , SessionEnv (.. )
39- , withOpenSession
39+ , withKeepSessionOpen
4040 -- ** Implementation of public API
4141 , withSession
4242 , openSession
@@ -45,7 +45,7 @@ module Database.LSMTree.Internal.Unsafe (
4545 , Table (.. )
4646 , TableState (.. )
4747 , TableEnv (.. )
48- , withOpenTable
48+ , withKeepTableOpen
4949 -- ** Implementation of public API
5050 , ResolveSerialisedValue
5151 , withTable
@@ -217,7 +217,7 @@ data CursorTrace =
217217data Session m h = Session {
218218 -- | The primary purpose of this 'RWVar' is to ensure consistent views of
219219 -- the open-/closedness of a session when multiple threads require access
220- -- to the session's fields (see 'withOpenSession '). We use more
220+ -- to the session's fields (see 'withKeepSessionOpen '). We use more
221221 -- fine-grained synchronisation for various mutable parts of an open
222222 -- session.
223223 --
@@ -280,21 +280,21 @@ data SessionClosedError
280280 deriving stock (Show , Eq )
281281 deriving anyclass (Exception )
282282
283- {-# INLINE withOpenSession #-}
284- {-# SPECIALISE withOpenSession ::
283+ {-# INLINE withKeepSessionOpen #-}
284+ {-# SPECIALISE withKeepSessionOpen ::
285285 Session IO h
286286 -> (SessionEnv IO h -> IO a)
287287 -> IO a #-}
288- -- | 'withOpenSession ' ensures that the session stays open for the duration of the
289- -- provided continuation.
288+ -- | 'withKeepSessionOpen ' ensures that the session stays open for the duration of
289+ -- the provided continuation.
290290--
291291-- NOTE: any operation except 'sessionClose' can use this function.
292- withOpenSession ::
292+ withKeepSessionOpen ::
293293 (MonadSTM m , MonadThrow m )
294294 => Session m h
295295 -> (SessionEnv m h -> m a )
296296 -> m a
297- withOpenSession sesh action = RW. withReadAccess (sessionState sesh) $ \ case
297+ withKeepSessionOpen sesh action = RW. withReadAccess (sessionState sesh) $ \ case
298298 SessionClosed -> throwIO ErrSessionClosed
299299 SessionOpen seshEnv -> action seshEnv
300300
@@ -527,7 +527,7 @@ data Table m h = Table {
527527 tableConfig :: ! TableConfig
528528 -- | The primary purpose of this 'RWVar' is to ensure consistent views of
529529 -- the open-/closedness of a table when multiple threads require access to
530- -- the table's fields (see 'withOpenTable '). We use more fine-grained
530+ -- the table's fields (see 'withKeepTableOpen '). We use more fine-grained
531531 -- synchronisation for various mutable parts of an open table.
532532 , tableState :: ! (RWVar m (TableState m h ))
533533 , tableArenaManager :: ! (ArenaManager (PrimState m ))
@@ -616,21 +616,21 @@ data TableClosedError
616616 deriving stock (Show , Eq )
617617 deriving anyclass (Exception )
618618
619- -- | 'withOpenTable ' ensures that the table stays open for the duration of the
619+ -- | 'withKeepTableOpen ' ensures that the table stays open for the duration of the
620620-- provided continuation.
621621--
622622-- NOTE: any operation except 'close' can use this function.
623- {-# INLINE withOpenTable #-}
624- {-# SPECIALISE withOpenTable ::
623+ {-# INLINE withKeepTableOpen #-}
624+ {-# SPECIALISE withKeepTableOpen ::
625625 Table IO h
626626 -> (TableEnv IO h -> IO a)
627627 -> IO a #-}
628- withOpenTable ::
628+ withKeepTableOpen ::
629629 (MonadSTM m , MonadThrow m )
630630 => Table m h
631631 -> (TableEnv m h -> m a )
632632 -> m a
633- withOpenTable t action = RW. withReadAccess (tableState t) $ \ case
633+ withKeepTableOpen t action = RW. withReadAccess (tableState t) $ \ case
634634 TableClosed -> throwIO ErrTableClosed
635635 TableOpen tEnv -> action tEnv
636636
@@ -664,7 +664,7 @@ new ::
664664 -> m (Table m h )
665665new sesh conf = do
666666 traceWith (sessionTracer sesh) TraceNewTable
667- withOpenSession sesh $ \ seshEnv ->
667+ withKeepSessionOpen sesh $ \ seshEnv ->
668668 withActionRegistry $ \ reg -> do
669669 am <- newArenaManager
670670 tc <- newEmptyTableContent seshEnv reg
@@ -771,7 +771,7 @@ lookups ::
771771 -> m (V. Vector (Maybe (Entry SerialisedValue (WeakBlobRef m h ))))
772772lookups resolve ks t = do
773773 traceWith (tableTracer t) $ TraceLookups (V. length ks)
774- withOpenTable t $ \ tEnv ->
774+ withKeepTableOpen t $ \ tEnv ->
775775 RW. withReadAccess (tableContent tEnv) $ \ tc -> do
776776 case tableUnionLevel tc of
777777 NoUnion -> lookupsRegular tEnv tc
@@ -883,7 +883,7 @@ updates ::
883883updates resolve es t = do
884884 traceWith (tableTracer t) $ TraceUpdates (V. length es)
885885 let conf = tableConfig t
886- withOpenTable t $ \ tEnv -> do
886+ withKeepTableOpen t $ \ tEnv -> do
887887 let hfs = tableHasFS tEnv
888888 modifyWithActionRegistry_
889889 (RW. unsafeAcquireWriteAccess (tableContent tEnv))
@@ -929,7 +929,7 @@ retrieveBlobs ::
929929 -> V. Vector (WeakBlobRef m h )
930930 -> m (V. Vector SerialisedBlob )
931931retrieveBlobs sesh wrefs =
932- withOpenSession sesh $ \ seshEnv ->
932+ withKeepSessionOpen sesh $ \ seshEnv ->
933933 let hbio = sessionHasBlockIO seshEnv in
934934 handle (\ (BlobRef. WeakBlobRefInvalid i) ->
935935 throwIO (ErrBlobRefInvalid i)) $
@@ -1035,7 +1035,7 @@ newCursor ::
10351035 -> OffsetKey
10361036 -> Table m h
10371037 -> m (Cursor m h )
1038- newCursor ! resolve ! offsetKey t = withOpenTable t $ \ tEnv -> do
1038+ newCursor ! resolve ! offsetKey t = withKeepTableOpen t $ \ tEnv -> do
10391039 let cursorSession = tableSession t
10401040 let cursorSessionEnv = tableSessionEnv tEnv
10411041 cursorId <- uniqueToCursorId <$>
@@ -1045,7 +1045,7 @@ newCursor !resolve !offsetKey t = withOpenTable t $ \tEnv -> do
10451045
10461046 -- We acquire a read-lock on the session open-state to prevent races, see
10471047 -- 'sessionOpenTables'.
1048- withOpenSession cursorSession $ \ _ -> do
1048+ withKeepSessionOpen cursorSession $ \ _ -> do
10491049 withActionRegistry $ \ reg -> do
10501050 (wb, wbblobs, cursorRuns, cursorUnion) <-
10511051 dupTableContent reg (tableContent tEnv)
@@ -1220,7 +1220,7 @@ saveSnapshot ::
12201220 -> m ()
12211221saveSnapshot snap label t = do
12221222 traceWith (tableTracer t) $ TraceSnapshot snap
1223- withOpenTable t $ \ tEnv ->
1223+ withKeepTableOpen t $ \ tEnv ->
12241224 withActionRegistry $ \ reg -> do -- TODO: use the action registry for all side effects
12251225 let hfs = tableHasFS tEnv
12261226 hbio = tableHasBlockIO tEnv
@@ -1327,7 +1327,7 @@ openTableFromSnapshot ::
13271327openTableFromSnapshot policyOveride sesh snap label resolve =
13281328 wrapFileCorruptedErrorAsSnapshotCorruptedError snap $ do
13291329 traceWith (sessionTracer sesh) $ TraceOpenTableFromSnapshot snap policyOveride
1330- withOpenSession sesh $ \ seshEnv -> do
1330+ withKeepSessionOpen sesh $ \ seshEnv -> do
13311331 withActionRegistry $ \ reg -> do
13321332 let hfs = sessionHasFS seshEnv
13331333 hbio = sessionHasBlockIO seshEnv
@@ -1411,7 +1411,7 @@ doesSnapshotExist ::
14111411 => Session m h
14121412 -> SnapshotName
14131413 -> m Bool
1414- doesSnapshotExist sesh snap = withOpenSession sesh (doesSnapshotDirExist snap)
1414+ doesSnapshotExist sesh snap = withKeepSessionOpen sesh (doesSnapshotDirExist snap)
14151415
14161416-- | Internal helper: Variant of 'doesSnapshotExist' that does not take a session lock.
14171417doesSnapshotDirExist :: SnapshotName -> SessionEnv m h -> m Bool
@@ -1431,7 +1431,7 @@ deleteSnapshot ::
14311431 -> m ()
14321432deleteSnapshot sesh snap = do
14331433 traceWith (sessionTracer sesh) $ TraceDeleteSnapshot snap
1434- withOpenSession sesh $ \ seshEnv -> do
1434+ withKeepSessionOpen sesh $ \ seshEnv -> do
14351435 let snapDir = Paths. namedSnapshotDir (sessionRoot seshEnv) snap
14361436 snapshotExists <- doesSnapshotDirExist snap seshEnv
14371437 unless snapshotExists $ throwIO (ErrSnapshotDoesNotExist snap)
@@ -1445,7 +1445,7 @@ listSnapshots ::
14451445 -> m [SnapshotName ]
14461446listSnapshots sesh = do
14471447 traceWith (sessionTracer sesh) TraceListSnapshots
1448- withOpenSession sesh $ \ seshEnv -> do
1448+ withKeepSessionOpen sesh $ \ seshEnv -> do
14491449 let hfs = sessionHasFS seshEnv
14501450 root = sessionRoot seshEnv
14511451 contents <- FS. listDirectory hfs (Paths. snapshotsDir (sessionRoot seshEnv))
@@ -1473,10 +1473,10 @@ duplicate ::
14731473 -> m (Table m h )
14741474duplicate t@ Table {.. } = do
14751475 traceWith tableTracer TraceDuplicate
1476- withOpenTable t $ \ TableEnv {.. } -> do
1476+ withKeepTableOpen t $ \ TableEnv {.. } -> do
14771477 -- We acquire a read-lock on the session open-state to prevent races, see
14781478 -- 'sessionOpenTables'.
1479- withOpenSession tableSession $ \ _ -> do
1479+ withKeepSessionOpen tableSession $ \ _ -> do
14801480 withActionRegistry $ \ reg -> do
14811481 -- The table contents escape the read access, but we just added references
14821482 -- to each run so it is safe.
@@ -1566,7 +1566,7 @@ unionsInOpenSession ::
15661566 -> m (Table m h )
15671567unionsInOpenSession reg sesh seshEnv conf ts = do
15681568 mts <- forM (NE. toList ts) $ \ t ->
1569- withOpenTable t $ \ tEnv ->
1569+ withKeepTableOpen t $ \ tEnv ->
15701570 RW. withReadAccess (tableContent tEnv) $ \ tc ->
15711571 -- tableContentToMergingTree duplicates all runs and merges
15721572 -- so the ones from the tableContent here do not escape
@@ -1681,7 +1681,7 @@ ensureSessionsMatch ::
16811681 -> m (Session m h )
16821682ensureSessionsMatch (t :| ts) = do
16831683 let sesh = tableSession t
1684- withOpenSession sesh $ \ seshEnv -> do
1684+ withKeepSessionOpen sesh $ \ seshEnv -> do
16851685 let root = FS. mkFsErrorPath (sessionHasFS seshEnv) (getSessionRoot (sessionRoot seshEnv))
16861686 -- Check that the session roots for all tables are the same. There can only
16871687 -- be one *open/active* session per directory because of cooperative file
@@ -1690,7 +1690,7 @@ ensureSessionsMatch (t :| ts) = do
16901690 -- the session roots.
16911691 for_ (zip [1 .. ] ts) $ \ (i, t') -> do
16921692 let sesh' = tableSession t'
1693- withOpenSession sesh' $ \ seshEnv' -> do
1693+ withKeepSessionOpen sesh' $ \ seshEnv' -> do
16941694 let root' = FS. mkFsErrorPath (sessionHasFS seshEnv') (getSessionRoot (sessionRoot seshEnv'))
16951695 -- TODO: compare LockFileHandle instead of SessionRoot (?).
16961696 -- We can write an Eq instance for LockFileHandle based on pointer equality,
@@ -1718,7 +1718,7 @@ remainingUnionDebt ::
17181718 => Table m h -> m UnionDebt
17191719remainingUnionDebt t = do
17201720 traceWith (tableTracer t) TraceRemainingUnionDebt
1721- withOpenTable t $ \ tEnv -> do
1721+ withKeepTableOpen t $ \ tEnv -> do
17221722 RW. withReadAccess (tableContent tEnv) $ \ tableContent -> do
17231723 case tableUnionLevel tableContent of
17241724 NoUnion ->
@@ -1741,7 +1741,7 @@ supplyUnionCredits ::
17411741 => ResolveSerialisedValue -> Table m h -> UnionCredits -> m UnionCredits
17421742supplyUnionCredits resolve t credits = do
17431743 traceWith (tableTracer t) $ TraceSupplyUnionCredits credits
1744- withOpenTable t $ \ tEnv -> do
1744+ withKeepTableOpen t $ \ tEnv -> do
17451745 -- We also want to mutate the table content to re-build the union cache,
17461746 -- but we don't need to hold a writer lock while we work on the tree
17471747 -- itself.
0 commit comments