Skip to content

Commit 2eeb767

Browse files
authored
Merge pull request #448 from IntersectMBO/jdral/rename-table-handle
Rename `TableHandle` to `Table`
2 parents 669555b + 5d91d53 commit 2eeb767

File tree

27 files changed

+700
-701
lines changed

27 files changed

+700
-701
lines changed

bench/macro/lsm-tree-bench-wp8.hs

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -614,7 +614,7 @@ type LookupResults = V.Vector (K, LSM.LookupResult V ())
614614
sequentialIteration :: (Int -> LookupResults -> IO ())
615615
-> Int
616616
-> Int
617-
-> LSM.TableHandle IO K V B
617+
-> LSM.Table IO K V B
618618
-> Int
619619
-> MCG.MCG
620620
-> IO MCG.MCG
@@ -633,7 +633,7 @@ sequentialIteration output !initialSize !batchSize !tbl !b !g = do
633633

634634
sequentialIterations :: (Int -> LookupResults -> IO ())
635635
-> Int -> Int -> Int -> Word64
636-
-> LSM.TableHandle IO K V B
636+
-> LSM.Table IO K V B
637637
-> IO ()
638638
sequentialIterations output !initialSize !batchSize !batchCount !seed !tbl =
639639
void $ forFoldM_ g0 [ 0 .. batchCount - 1 ] $ \b g ->
@@ -645,7 +645,7 @@ sequentialIterations output !initialSize !batchSize !batchCount !seed !tbl =
645645
sequentialIterationLO :: (Int -> LookupResults -> IO ())
646646
-> Int
647647
-> Int
648-
-> LSM.TableHandle IO K V B
648+
-> LSM.Table IO K V B
649649
-> Int
650650
-> MCG.MCG
651651
-> IO MCG.MCG
@@ -661,7 +661,7 @@ sequentialIterationLO output !initialSize !batchSize !tbl !b !g = do
661661

662662
sequentialIterationsLO :: (Int -> LookupResults -> IO ())
663663
-> Int -> Int -> Int -> Word64
664-
-> LSM.TableHandle IO K V B
664+
-> LSM.Table IO K V B
665665
-> IO ()
666666
sequentialIterationsLO output !initialSize !batchSize !batchCount !seed !tbl =
667667
void $ forFoldM_ g0 [ 0 .. batchCount - 1 ] $ \b g ->
@@ -721,13 +721,13 @@ And the initial setup looks like this:
721721
pipelinedIteration :: (Int -> LookupResults -> IO ())
722722
-> Int
723723
-> Int
724-
-> MVar (LSM.TableHandle IO K V B, Map K (LSM.Update V B))
725-
-> MVar (LSM.TableHandle IO K V B, Map K (LSM.Update V B))
724+
-> MVar (LSM.Table IO K V B, Map K (LSM.Update V B))
725+
-> MVar (LSM.Table IO K V B, Map K (LSM.Update V B))
726726
-> MVar MCG.MCG
727727
-> MVar MCG.MCG
728-
-> LSM.TableHandle IO K V B
728+
-> LSM.Table IO K V B
729729
-> Int
730-
-> IO (LSM.TableHandle IO K V B)
730+
-> IO (LSM.Table IO K V B)
731731
pipelinedIteration output !initialSize !batchSize
732732
!syncTblIn !syncTblOut
733733
!syncRngIn !syncRngOut
@@ -738,7 +738,7 @@ pipelinedIteration output !initialSize !batchSize
738738
-- 1: perform the lookups
739739
lrs <- LSM.lookups ls tbl_n
740740

741-
-- 2. sync: receive updates and new table handle
741+
-- 2. sync: receive updates and new table
742742
putMVar syncRngOut g'
743743
(tbl_n1, delta) <- takeMVar syncTblIn
744744

@@ -751,7 +751,7 @@ pipelinedIteration output !initialSize !batchSize
751751
tbl_n2 <- LSM.duplicate tbl_n1
752752
LSM.updates is tbl_n2
753753

754-
-- 4. sync: send the updates and new table handle
754+
-- 4. sync: send the updates and new table
755755
let delta' :: Map K (LSM.Update V B)
756756
!delta' = Map.fromList (V.toList is)
757757
putMVar syncTblOut (tbl_n2, delta')
@@ -769,7 +769,7 @@ pipelinedIteration output !initialSize !batchSize
769769

770770
pipelinedIterations :: (Int -> LookupResults -> IO ())
771771
-> Int -> Int -> Int -> Word64
772-
-> LSM.TableHandle IO K V B
772+
-> LSM.Table IO K V B
773773
-> IO ()
774774
pipelinedIterations output !initialSize !batchSize !batchCount !seed tbl_0 = do
775775
n <- getNumCapabilities

bench/micro/Bench/Database/LSMTree/Monoidal.hs

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -240,16 +240,16 @@ mkNormalTable ::
240240
-> FS.HasBlockIO IO FS.HandleIO
241241
-> Normal.TableConfig
242242
-> IO ( Normal.Session IO
243-
, Normal.TableHandle IO K V B
243+
, Normal.Table IO K V B
244244
)
245245
mkNormalTable hfs hbio conf = do
246246
sesh <- Normal.openSession nullTracer hfs hbio (FS.mkFsPath [])
247-
th <- Normal.new sesh conf
248-
pure (sesh, th)
247+
t <- Normal.new sesh conf
248+
pure (sesh, t)
249249

250250
cleanupNormalTable ::
251251
( Normal.Session IO
252-
, Normal.TableHandle IO K V B
252+
, Normal.Table IO K V B
253253
)
254254
-> IO ()
255255
cleanupNormalTable (s, t) = do
@@ -261,16 +261,16 @@ mkMonoidalTable ::
261261
-> FS.HasBlockIO IO FS.HandleIO
262262
-> Monoidal.TableConfig
263263
-> IO ( Monoidal.Session IO
264-
, Monoidal.TableHandle IO K V
264+
, Monoidal.Table IO K V
265265
)
266266
mkMonoidalTable hfs hbio conf = do
267267
sesh <- Monoidal.openSession nullTracer hfs hbio (FS.mkFsPath [])
268-
th <- Monoidal.new sesh conf
269-
pure (sesh, th)
268+
t <- Monoidal.new sesh conf
269+
pure (sesh, t)
270270

271271
cleanupMonoidalTable ::
272272
( Monoidal.Session IO
273-
, Monoidal.TableHandle IO K V
273+
, Monoidal.Table IO K V
274274
)
275275
-> IO ()
276276
cleanupMonoidalTable (s, t) = do

bench/micro/Bench/Database/LSMTree/Normal.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -75,15 +75,15 @@ benchLargeValueVsSmallValueBlob :: Benchmark
7575
benchLargeValueVsSmallValueBlob =
7676
env mkEntries $ \es -> bgroup "large-value-vs-small-value-blob" [
7777
env (mkGrouped (mkV1 es)) $ \ ~(ess, kss) -> bgroup "V1" [
78-
withEnv ess $ \ ~(_, _, _, _, t :: Normal.TableHandle IO K V1 B1) -> do
78+
withEnv ess $ \ ~(_, _, _, _, t :: Normal.Table IO K V1 B1) -> do
7979
bench "lookups-large-value" $ whnfIO $
8080
V.mapM_ (flip Normal.lookups t) kss
8181
]
8282
, env (mkGrouped (mkV2 es)) $ \ ~(ess, kss) -> bgroup "V2" [
83-
withEnv ess $ \ ~(_, _, _, _, t :: Normal.TableHandle IO K V2 B2) -> do
83+
withEnv ess $ \ ~(_, _, _, _, t :: Normal.Table IO K V2 B2) -> do
8484
bench "lookups-small-value" $ whnfIO $
8585
V.mapM_ (flip Normal.lookups t) kss
86-
, withEnv ess $ \ ~(_, _, _, s, t :: Normal.TableHandle IO K V2 B2) -> do
86+
, withEnv ess $ \ ~(_, _, _, s, t :: Normal.Table IO K V2 B2) -> do
8787
bench "lookups-small-value-blob" $ whnfIO $ do
8888
V.forM_ kss $ \ks -> do
8989
lrs <- Normal.lookups ks t
@@ -147,7 +147,7 @@ benchCursorScanVsRangeLookupScan :: Benchmark
147147
benchCursorScanVsRangeLookupScan =
148148
env mkEntries $ \es ->
149149
env (mkGrouped es) $ \ ess ->
150-
withEnv ess $ \ ~(_, _, _, _, t :: Normal.TableHandle IO K V2 B2) ->
150+
withEnv ess $ \ ~(_, _, _, _, t :: Normal.Table IO K V2 B2) ->
151151
bgroup "cursor-scan-vs-range-lookup-scan" [
152152
bench "cursor-scan-full" $ whnfIO $ do
153153
Normal.withCursor t $ \c -> do

doc/format-directory.md

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -58,7 +58,7 @@ snapshots). This is because the metadata is held in memory for open LSM handles.
5858
The `${n}.wbblobs` file format is the same as the `${n}.blobs` format used for
5959
runs: the concatenation of all the blobs written out so far. These files can be
6060
shared between open tables (created using `duplicate`), and so can contain
61-
blobs inserted via many table handles.
61+
blobs inserted via many tables.
6262

6363
The `${n}.wbblobs` files are ephemeral. They are never included into snapshots
6464
and are not referenced from any `.checksums` file.

doc/format-run.md

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -172,8 +172,8 @@ properties. In particular initially we will support a compact index type.
172172
For more general purpose applications one can foresee the need for a more
173173
ordinary index type.
174174

175-
The type of index in use is metadata that must be known for the whole LSM table
176-
handle. It does not vary per run.
175+
The type of index in use is metadata that must be known for the whole LSM table.
176+
It does not vary per run.
177177

178178
Independently of the concrete index serialization format, the type and the
179179
version of the format are stored at the beginning as a 32-bit number called the

src-extras/Database/LSMTree/Extras/NoThunks.hs

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -84,26 +84,26 @@ prop_NoThunks x =
8484
Public API
8585
-------------------------------------------------------------------------------}
8686

87-
-- | Also checks 'NoThunks' for the 'Normal.TableHandle's that are known to be
87+
-- | Also checks 'NoThunks' for the 'Normal.Table's that are known to be
8888
-- open in the 'Common.Session'.
8989
instance (NoThunksIOLike m, Typeable m, Typeable (PrimState m))
9090
=> NoThunks (Session' m ) where
9191
showTypeOf (_ :: Proxy (Session' m)) = "Session'"
9292
wNoThunks ctx (Session' s) = wNoThunks ctx s
9393

9494
-- | Does not check 'NoThunks' for the 'Common.Session' that this
95-
-- 'Normal.TableHandle' belongs to.
95+
-- 'Normal.Table' belongs to.
9696
instance (NoThunksIOLike m, Typeable m, Typeable (PrimState m))
9797
=> NoThunks (NormalTable m k v blob) where
9898
showTypeOf (_ :: Proxy (NormalTable m k v blob)) = "NormalTable"
99-
wNoThunks ctx (NormalTable th) = wNoThunks ctx th
99+
wNoThunks ctx (NormalTable t) = wNoThunks ctx t
100100

101101
{-------------------------------------------------------------------------------
102102
Internal
103103
-------------------------------------------------------------------------------}
104104

105105
deriving stock instance Generic (Internal.Session m h)
106-
-- | Also checks 'NoThunks' for the 'Internal.TableHandle's that are known to be
106+
-- | Also checks 'NoThunks' for the 'Internal.Table's that are known to be
107107
-- open in the 'Internal.Session'.
108108
deriving anyclass instance (NoThunksIOLike m, Typeable m, Typeable h, Typeable (PrimState m))
109109
=> NoThunks (Internal.Session m h)
@@ -116,20 +116,20 @@ deriving stock instance Generic (SessionEnv m h)
116116
deriving anyclass instance (NoThunksIOLike m, Typeable m, Typeable h, Typeable (PrimState m))
117117
=> NoThunks (SessionEnv m h)
118118

119-
deriving stock instance Generic (Internal.TableHandle m h)
119+
deriving stock instance Generic (Internal.Table m h)
120120
-- | Does not check 'NoThunks' for the 'Internal.Session' that this
121-
-- 'Internal.TableHandle' belongs to.
121+
-- 'Internal.Table' belongs to.
122122
deriving anyclass instance (NoThunksIOLike m, Typeable m, Typeable h, Typeable (PrimState m))
123-
=> NoThunks (Internal.TableHandle m h)
123+
=> NoThunks (Internal.Table m h)
124124

125-
deriving stock instance Generic (TableHandleState m h)
125+
deriving stock instance Generic (TableState m h)
126126
deriving anyclass instance (NoThunksIOLike m, Typeable m, Typeable h, Typeable (PrimState m))
127-
=> NoThunks (TableHandleState m h)
127+
=> NoThunks (TableState m h)
128128

129-
deriving stock instance Generic (TableHandleEnv m h)
130-
deriving via AllowThunksIn ["tableSession", "tableSessionEnv"] (TableHandleEnv m h)
129+
deriving stock instance Generic (TableEnv m h)
130+
deriving via AllowThunksIn ["tableSession", "tableSessionEnv"] (TableEnv m h)
131131
instance (NoThunksIOLike m, Typeable m, Typeable h, Typeable (PrimState m))
132-
=> NoThunks (TableHandleEnv m h)
132+
=> NoThunks (TableEnv m h)
133133

134134
-- | Does not check 'NoThunks' for the 'Internal.Session' that this
135135
-- 'Internal.Cursor' belongs to.

src/Database/LSMTree/Common.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -82,7 +82,7 @@ instance IOLike IO
8282
Sessions
8383
-------------------------------------------------------------------------------}
8484

85-
-- | A session provides context that is shared across multiple table handles.
85+
-- | A session provides context that is shared across multiple tables.
8686
--
8787
-- Sessions are needed to support sharing between multiple table instances.
8888
-- Sharing occurs when tables are duplicated using 'duplicate', or when tables
@@ -171,8 +171,8 @@ openSession tr hfs hbio dir = Internal.Session' <$> Internal.openSession tr hfs
171171
-- | Close the table session. 'closeSession' is idempotent. All subsequent
172172
-- operations on the session or the tables within it will throw an exception.
173173
--
174-
-- This also closes any open table handles and cursors in the session. It would
175-
-- typically be good practice however to close all table handles first rather
174+
-- This also closes any open tables and cursors in the session. It would
175+
-- typically be good practice however to close all tables first rather
176176
-- than relying on this for cleanup.
177177
--
178178
-- Closing a table session allows the session to be opened again elsewhere, for
@@ -242,12 +242,12 @@ listSnapshots (Internal.Session' sesh) = Internal.listSnapshots sesh
242242
--
243243
-- Though blob references are handle-like, they /do not/ keep files open. As
244244
-- such, when a blob reference is returned by a lookup, modifying the
245-
-- corresponding table handle, cursor, or session /may/ cause the blob reference
245+
-- corresponding table, cursor, or session /may/ cause the blob reference
246246
-- to be invalidated (i.e.., the blob has gone missing because the blob file was
247247
-- removed). These operations include:
248248
--
249249
-- * Updates (e.g., inserts, deletes, mupserts)
250-
-- * Closing table handles
250+
-- * Closing tables
251251
-- * Closing cursors
252252
-- * Closing sessions
253253
--
@@ -256,7 +256,7 @@ listSnapshots (Internal.Session' sesh) = Internal.listSnapshots sesh
256256
-- do /not/ invalidate blob references. These operations do not modify the
257257
-- logical contents or state of a table.
258258
--
259-
-- [Blob reference validity] as long as the table handle or cursor that the blob
259+
-- [Blob reference validity] as long as the table or cursor that the blob
260260
-- reference originated from is not updated or closed, the blob reference will
261261
-- be valid.
262262
--

0 commit comments

Comments
 (0)