Skip to content

Commit 48e22c4

Browse files
authored
Merge pull request #458 from IntersectMBO/mheinzel/tweak-api
Tweak API
2 parents 7c6863c + 7903d6c commit 48e22c4

File tree

16 files changed

+266
-265
lines changed

16 files changed

+266
-265
lines changed

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

Lines changed: 11 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -407,20 +407,18 @@ doSetup' gopts opts = do
407407
LSM.mkSnapshotName "bench"
408408

409409
LSM.withSession (mkTracer gopts) hasFS hasBlockIO (FS.mkFsPath []) $ \session -> do
410-
tbh <- LSM.new @IO @K @V @B session (mkTableConfigSetup gopts opts LSM.defaultTableConfig)
410+
tbl <- LSM.new @IO @K @V @B session (mkTableConfigSetup gopts opts LSM.defaultTableConfig)
411411

412412
forM_ (groupsOfN 256 [ 0 .. initialSize gopts ]) $ \batch -> do
413413
-- TODO: this procedure simply inserts all the keys into initial lsm tree
414414
-- We might want to do deletes, so there would be delete-insert pairs
415415
-- Let's do that when we can actually test that benchmark works.
416-
--
417-
-- TODO: LSM.inserts has annoying order
418-
flip LSM.inserts tbh $ V.fromList [
416+
LSM.inserts tbl $ V.fromList [
419417
(makeKey (fromIntegral i), theValue, Nothing)
420418
| i <- NE.toList batch
421419
]
422420

423-
LSM.snapshot name tbh
421+
LSM.createSnapshot name tbl
424422

425423
-------------------------------------------------------------------------------
426424
-- dry-run
@@ -579,7 +577,7 @@ doRun gopts opts = do
579577
-- necessary for testing to load the whole snapshot).
580578
tbl <- if check opts
581579
then LSM.new @IO @K @V @B session (mkTableConfigRun gopts LSM.defaultTableConfig)
582-
else LSM.open @IO @K @V @B session (mkTableConfigOverride gopts) name
580+
else LSM.openSnapshot @IO @K @V @B session (mkTableConfigOverride gopts) name
583581

584582
-- In checking mode, compare each output against a pure reference.
585583
checkvar <- newIORef $ pureReference
@@ -631,11 +629,11 @@ sequentialIteration h output !initialSize !batchSize !tbl !b !g =
631629
let (!g', ls, is) = generateBatch initialSize batchSize g b
632630

633631
-- lookups
634-
results <- timeLatency tref $ LSM.lookups ls tbl
632+
results <- timeLatency tref $ LSM.lookups tbl ls
635633
output b (V.zip ls (fmap (fmap (const ())) results))
636634

637635
-- deletes and inserts
638-
_ <- timeLatency tref $ LSM.updates is tbl
636+
_ <- timeLatency tref $ LSM.updates tbl is
639637

640638
-- continue to the next batch
641639
return g'
@@ -666,7 +664,7 @@ sequentialIterationLO output !initialSize !batchSize !tbl !b !g = do
666664
let (!g', ls, _is) = generateBatch initialSize batchSize g b
667665

668666
-- lookups
669-
results <- LSM.lookups ls tbl
667+
results <- LSM.lookups tbl ls
670668
output b (V.zip ls (fmap (fmap (const ())) results))
671669

672670
-- continue to the next batch
@@ -751,7 +749,7 @@ pipelinedIteration h output !initialSize !batchSize
751749
let (!g', !ls, !is) = generateBatch initialSize batchSize g b
752750

753751
-- 1: perform the lookups
754-
lrs <- timeLatency tref $ LSM.lookups ls tbl_n
752+
lrs <- timeLatency tref $ LSM.lookups tbl_n ls
755753

756754
-- 2. sync: receive updates and new table
757755
tbl_n1 <- timeLatency tref $ do
@@ -767,7 +765,7 @@ pipelinedIteration h output !initialSize !batchSize
767765
-- 3. perform the inserts and report outputs (in any order)
768766
tbl_n2 <- timeLatency tref $ do
769767
tbl_n2 <- LSM.duplicate tbl_n1
770-
LSM.updates is tbl_n2
768+
LSM.updates tbl_n2 is
771769
pure tbl_n2
772770

773771
-- 4. sync: send the updates and new table
@@ -808,9 +806,9 @@ pipelinedIterations h output !initialSize !batchSize !batchCount !seed tbl_0 = d
808806
tbl_1 <- LSM.duplicate tbl_0
809807
let prelude = do
810808
let (g1, ls0, is0) = generateBatch initialSize batchSize g0 0
811-
lrs0 <- LSM.lookups ls0 tbl_0
809+
lrs0 <- LSM.lookups tbl_0 ls0
812810
output 0 $! V.zip ls0 (fmap (fmap (const ())) lrs0)
813-
LSM.updates is0 tbl_1
811+
LSM.updates tbl_1 is0
814812
let !delta = Map.fromList (V.toList is0)
815813
putMVar syncTblA2B (tbl_1, delta)
816814
putMVar syncRngA2B g1

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

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -69,13 +69,13 @@ benchInsertsVsMupserts =
6969
env (pure $ snd $ randomEntriesGrouped 800_000 250) $ \ess -> bgroup "inserts-vs-mupserts" [
7070
env (pure $ V.map mkNormalInserts ess) $ \inss -> bench "normal-inserts" $
7171
withEmptyNormalTable $ \(_, _, _, _, t) ->
72-
V.mapM_ (flip Normal.inserts t) inss
72+
V.mapM_ (Normal.inserts t) inss
7373
, env (pure $ V.map mkMonoidalInserts ess) $ \inss -> bench "monoidal-inserts" $
7474
withEmptyMonoidalTable $ \(_, _, _, _, t) ->
75-
V.mapM_ (flip Monoidal.inserts t) inss
75+
V.mapM_ (Monoidal.inserts t) inss
7676
, env (pure $ V.map mkMonoidalMupserts ess) $ \mupss -> bench "monoidal-mupserts" $
7777
withEmptyMonoidalTable $ \(_, _, _, _, t) ->
78-
V.mapM_ (flip Monoidal.mupserts t) mupss
78+
V.mapM_ (Monoidal.mupserts t) mupss
7979
]
8080
where
8181
withEmptyNormalTable =
@@ -114,15 +114,15 @@ benchLookupsInsertsVsMupserts =
114114
-- the existing values, sum those with the insert values, then
115115
-- insert the updated values.
116116
V.forM_ inss $ \ins -> do
117-
lrs <- Monoidal.lookups (V.map fst ins) t
117+
lrs <- Monoidal.lookups t (V.map fst ins)
118118
let ins' = V.zipWith f ins lrs
119-
Monoidal.inserts ins' t
119+
Monoidal.inserts t ins'
120120
, env (pure $ V.map mkMonoidalMupserts ess) $ \mupss -> bench "mupserts" $
121121
withMonoidalTable mupss $ \(_, _, _, _, t) ->
122122
-- Insert the same keys again, but we sum the existing values in
123123
-- the table with the values we are going to insert: submit
124124
-- mupserts with the insert values.
125-
V.forM_ mupss $ \mups -> Monoidal.mupserts mups t
125+
V.forM_ mupss $ \mups -> Monoidal.mupserts t mups
126126
]
127127
where
128128
f (k, v) = \case
@@ -133,7 +133,7 @@ benchLookupsInsertsVsMupserts =
133133
-- Make a monoidal table and fill it up
134134
(do (tmpDir, hfs, hbio) <- mkFiles
135135
(s, t) <- mkMonoidalTable hfs hbio benchConfig
136-
V.mapM_ (flip Monoidal.inserts t) inss
136+
V.mapM_ (Monoidal.inserts t) inss
137137
pure (tmpDir, hfs, hbio, s, t)
138138
)
139139
(\(tmpDir, hfs, hbio, s, t) -> do
@@ -148,10 +148,10 @@ benchNormalResolveVsMonoidalResolve =
148148
env (pure $ snd $ randomEntriesGrouped 80_000 250) $ \ess -> bgroup "normal-resolve-vs-monoidal-resolve" [
149149
env (pure $ V.map mkNormalInserts ess) $ \inss -> bench "normal-lookups" $
150150
withNormalTable inss $ \(_, _, _, _, t) -> do
151-
V.forM_ inss $ \ins -> Normal.lookups (V.map fst3 ins) t
151+
V.forM_ inss $ \ins -> Normal.lookups t (V.map fst3 ins)
152152
, env (pure $ V.map mkMonoidalInserts ess) $ \inss -> bench "monoidal-lookups" $
153153
withMonoidalTable inss $ \(_, _, _, _, t) -> do
154-
V.forM_ inss $ \ins -> Monoidal.lookups (V.map fst ins) t
154+
V.forM_ inss $ \ins -> Monoidal.lookups t (V.map fst ins)
155155
]
156156
where
157157
fst3 (x,_,_) = x
@@ -165,7 +165,7 @@ benchNormalResolveVsMonoidalResolve =
165165
(s, t) <- mkNormalTable hfs hbio benchConfig
166166
V.forM_ [1..10] $ \(i::Int) -> do
167167
let inss' = (V.map . V.map) (\(k, v, b) -> (k, fromIntegral i * v, b)) inss
168-
V.mapM_ (flip Normal.inserts t) inss'
168+
V.mapM_ (Normal.inserts t) inss'
169169
pure (tmpDir, hfs, hbio, s, t)
170170
)
171171
(\(tmpDir, hfs, hbio, s, t) -> do
@@ -180,7 +180,7 @@ benchNormalResolveVsMonoidalResolve =
180180
(do (tmpDir, hfs, hbio) <- mkFiles
181181
(s, t) <- mkMonoidalTable hfs hbio benchConfig
182182
V.forM_ [1..10] $ \(_::Int) ->
183-
V.mapM_ (flip Monoidal.mupserts t) inss
183+
V.mapM_ (Monoidal.mupserts t) inss
184184
pure (tmpDir, hfs, hbio, s, t)
185185
)
186186
(\(tmpDir, hfs, hbio, s, t) -> do

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

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -78,16 +78,16 @@ benchLargeValueVsSmallValueBlob =
7878
env (mkGrouped (mkV1 es)) $ \ ~(ess, kss) -> bgroup "V1" [
7979
withEnv ess $ \ ~(_, _, _, _, t :: Normal.Table IO K V1 B1) -> do
8080
bench "lookups-large-value" $ whnfIO $
81-
V.mapM_ (flip Normal.lookups t) kss
81+
V.mapM_ (Normal.lookups t) kss
8282
]
8383
, env (mkGrouped (mkV2 es)) $ \ ~(ess, kss) -> bgroup "V2" [
8484
withEnv ess $ \ ~(_, _, _, _, t :: Normal.Table IO K V2 B2) -> do
8585
bench "lookups-small-value" $ whnfIO $
86-
V.mapM_ (flip Normal.lookups t) kss
86+
V.mapM_ (Normal.lookups t) kss
8787
, withEnv ess $ \ ~(_, _, _, s, t :: Normal.Table IO K V2 B2) -> do
8888
bench "lookups-small-value-blob" $ whnfIO $ do
8989
V.forM_ kss $ \ks -> do
90-
lrs <- Normal.lookups ks t
90+
lrs <- Normal.lookups t ks
9191
Normal.retrieveBlobs s (V.fromList $ toList $ Compose lrs)
9292
]
9393
]
@@ -123,7 +123,7 @@ benchLargeValueVsSmallValueBlob =
123123
(tmpDir, hfs, hbio) <- mkFiles
124124
s <- Normal.openSession nullTracer hfs hbio (FS.mkFsPath [])
125125
t <- Normal.new s benchConfig
126-
V.mapM_ (flip Normal.inserts t) inss
126+
V.mapM_ (Normal.inserts t) inss
127127
pure (tmpDir, hfs, hbio, s, t)
128128

129129
cleanup (tmpDir, hfs, hbio, s, t) = do
@@ -158,10 +158,10 @@ benchCursorScanVsRangeLookupScan =
158158
forM_ [1 .. numChunks] $ \(_ :: Int) -> do
159159
Normal.readCursor readSize c
160160
, bench "range-scan-full" $ whnfIO $ do
161-
Normal.rangeLookup (Normal.FromToIncluding (K minBound) (K maxBound)) t
161+
Normal.rangeLookup t (Normal.FromToIncluding (K minBound) (K maxBound))
162162
, bench "range-scan-chunked" $ whnfIO $ do
163163
forM_ ranges $ \r -> do
164-
Normal.rangeLookup r t
164+
Normal.rangeLookup t r
165165
]
166166
where
167167
initialSize, batchSize, numChunks :: Int
@@ -208,7 +208,7 @@ benchCursorScanVsRangeLookupScan =
208208
(tmpDir, hfs, hbio) <- mkFiles
209209
s <- Normal.openSession nullTracer hfs hbio (FS.mkFsPath [])
210210
t <- Normal.new s benchConfig
211-
V.mapM_ (flip Normal.inserts t) inss
211+
V.mapM_ (Normal.inserts t) inss
212212
pure (tmpDir, hfs, hbio, s, t)
213213

214214
cleanup (tmpDir, hfs, hbio, s, t) = do
@@ -226,7 +226,7 @@ benchInsertBatches =
226226
env genInserts $ \iss ->
227227
withEnv $ \ ~(_, _, _, _, t :: Normal.Table IO Word64 Word64 Void) -> do
228228
bench "benchInsertBatches" $ whnfIO $
229-
V.mapM_ (flip Normal.inserts t) iss
229+
V.mapM_ (Normal.inserts t) iss
230230
where
231231
!initialSize = 100_000
232232
!batchSize = 256

src/Database/LSMTree/Internal.hs

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -58,8 +58,8 @@ module Database.LSMTree.Internal (
5858
, readCursorWhile
5959
-- * Snapshots
6060
, SnapshotLabel
61-
, snapshot
62-
, open
61+
, createSnapshot
62+
, openSnapshot
6363
, deleteSnapshot
6464
, listSnapshots
6565
-- * Mutiple writable tables
@@ -297,8 +297,8 @@ data SessionEnv m h = SessionEnv {
297297
--
298298
-- Tables are assigned unique identifiers using 'sessionUniqCounter' to
299299
-- ensure that modifications to the set of known tables are independent.
300-
-- Each identifier is added only once in 'new', 'open' or 'duplicate', and
301-
-- is deleted only once in 'close' or 'closeSession'.
300+
-- Each identifier is added only once in 'new', 'openSnapshot' or
301+
-- 'duplicate', and is deleted only once in 'close' or 'closeSession'.
302302
--
303303
-- * A new table may only insert its own identifier when it has acquired the
304304
-- 'sessionState' read-lock. This is to prevent races with 'closeSession'.
@@ -1056,23 +1056,23 @@ readCursorWhile resolve keyIsWanted n Cursor {..} fromEntry = do
10561056
Snapshots
10571057
-------------------------------------------------------------------------------}
10581058

1059-
{-# SPECIALISE snapshot ::
1059+
{-# SPECIALISE createSnapshot ::
10601060
ResolveSerialisedValue
10611061
-> SnapshotName
10621062
-> SnapshotLabel
10631063
-> SnapshotTableType
10641064
-> Table IO h
10651065
-> IO Int #-}
1066-
-- | See 'Database.LSMTree.Normal.snapshot''.
1067-
snapshot ::
1066+
-- | See 'Database.LSMTree.Normal.createSnapshot''.
1067+
createSnapshot ::
10681068
(MonadFix m, MonadMask m, MonadMVar m, MonadST m, MonadSTM m)
10691069
=> ResolveSerialisedValue
10701070
-> SnapshotName
10711071
-> SnapshotLabel
10721072
-> SnapshotTableType
10731073
-> Table m h
10741074
-> m Int
1075-
snapshot resolve snap label tableType t = do
1075+
createSnapshot resolve snap label tableType t = do
10761076
traceWith (tableTracer t) $ TraceSnapshot snap
10771077
let conf = tableConfig t
10781078
withOpenTable t $ \thEnv -> do
@@ -1120,16 +1120,16 @@ snapshot resolve snap label tableType t = do
11201120

11211121
pure $! numSnapRuns snappedLevels
11221122

1123-
{-# SPECIALISE open ::
1123+
{-# SPECIALISE openSnapshot ::
11241124
Session IO h
11251125
-> SnapshotLabel
11261126
-> SnapshotTableType
11271127
-> TableConfigOverride
11281128
-> SnapshotName
11291129
-> ResolveSerialisedValue
11301130
-> IO (Table IO h) #-}
1131-
-- | See 'Database.LSMTree.Normal.open'.
1132-
open ::
1131+
-- | See 'Database.LSMTree.Normal.openSnapshot'.
1132+
openSnapshot ::
11331133
(MonadFix m, MonadMask m, MonadMVar m, MonadST m, MonadSTM m)
11341134
=> Session m h
11351135
-> SnapshotLabel -- ^ Expected label
@@ -1138,7 +1138,7 @@ open ::
11381138
-> SnapshotName
11391139
-> ResolveSerialisedValue
11401140
-> m (Table m h)
1141-
open sesh label tableType override snap resolve = do
1141+
openSnapshot sesh label tableType override snap resolve = do
11421142
traceWith (sessionTracer sesh) $ TraceOpenSnapshot snap override
11431143
withOpenSession sesh $ \seshEnv -> do
11441144
withTempRegistry $ \reg -> do

0 commit comments

Comments
 (0)