Skip to content

Commit 30b4c36

Browse files
committed
WIP: RefCtx
1 parent dca6656 commit 30b4c36

File tree

34 files changed

+586
-445
lines changed

34 files changed

+586
-445
lines changed

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

Lines changed: 9 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -133,7 +133,7 @@ benchSalt :: Bloom.Salt
133133
benchSalt = 4
134134

135135
benchmarks :: Run.RunDataCaching -> IO ()
136-
benchmarks !caching = withFS $ \hfs hbio -> do
136+
benchmarks !caching = withFS $ \hfs hbio refCtx -> do
137137
#ifdef NO_IGNORE_ASSERTS
138138
putStrLn "WARNING: Benchmarking in debug mode."
139139
putStrLn " To benchmark in release mode, pass:"
@@ -163,7 +163,7 @@ benchmarks !caching = withFS $ \hfs hbio -> do
163163
-- instead of sequentially.
164164
let keyRng0 = mkStdGen 17
165165

166-
(!runs, !blooms, !indexes, !handles) <- lookupsEnv runSizes keyRng0 hfs hbio caching
166+
(!runs, !blooms, !indexes, !handles) <- lookupsEnv runSizes keyRng0 hfs hbio refCtx caching
167167
putStrLn "<finished>"
168168

169169
traceMarkerIO "Computing statistics for generated runs"
@@ -210,7 +210,7 @@ benchmarks !caching = withFS $ \hfs hbio -> do
210210
"Calculate batches of keys, and perform disk lookups for each batch. This is roughly doing the same as benchPrepLookups, but also performing the disk I/O and resolving values. Net time/allocation is the result of subtracting the cost of benchGenKeyBatches."
211211
(\n -> do
212212
let wb_unused = WB.empty
213-
bracket (WBB.new hfs (FS.mkFsPath ["wbblobs_unused"])) releaseRef $ \wbblobs_unused ->
213+
bracket (WBB.new hfs refCtx (FS.mkFsPath ["wbblobs_unused"])) releaseRef $ \wbblobs_unused ->
214214
benchLookupsIO hbio arenaManager benchmarkResolveSerialisedValue
215215
wb_unused wbblobs_unused runs blooms indexes handles
216216
keyRng0 n)
@@ -308,13 +308,14 @@ totalNumEntriesSanityCheck l1 runSizes =
308308
sum [ 2^l1 * sizeFactor | (_, sizeFactor) <- runSizes ]
309309

310310
withFS ::
311-
(FS.HasFS IO FS.HandleIO -> FS.HasBlockIO IO FS.HandleIO -> IO a)
311+
(FS.HasFS IO FS.HandleIO -> FS.HasBlockIO IO FS.HandleIO -> RefCtx -> IO a)
312312
-> IO a
313313
withFS action =
314+
withRefCtx $ \refCtx ->
314315
FS.withIOHasBlockIO (FS.MountPoint "_bench_lookups") FS.defaultIOCtxParams $ \hfs hbio -> do
315316
exists <- FS.doesDirectoryExist hfs (FS.mkFsPath [""])
316317
unless exists $ error ("_bench_lookups directory does not exist")
317-
action hfs hbio
318+
action hfs hbio refCtx
318319

319320
-- | Input environment for benchmarking lookup functions.
320321
--
@@ -336,13 +337,14 @@ lookupsEnv ::
336337
-> StdGen -- ^ Key RNG
337338
-> FS.HasFS IO FS.HandleIO
338339
-> FS.HasBlockIO IO FS.HandleIO
340+
-> RefCtx
339341
-> Run.RunDataCaching
340342
-> IO ( V.Vector (Ref (Run IO FS.HandleIO))
341343
, V.Vector (Bloom SerialisedKey)
342344
, V.Vector Index
343345
, V.Vector (FS.Handle FS.HandleIO)
344346
)
345-
lookupsEnv runSizes keyRng0 hfs hbio caching = do
347+
lookupsEnv runSizes keyRng0 hfs hbio refCtx caching = do
346348
-- create the vector of initial keys
347349
(mvec :: VUM.MVector RealWorld UTxOKey) <- VUM.unsafeNew (totalNumEntries runSizes)
348350
!keyRng1 <- vectorOfUniforms mvec keyRng0
@@ -381,7 +383,7 @@ lookupsEnv runSizes keyRng0 hfs hbio caching = do
381383
putStr "DONE"
382384

383385
-- return runs
384-
runs <- V.fromList <$> mapM Run.fromBuilder rbs
386+
runs <- V.fromList <$> mapM (Run.fromBuilder refCtx) rbs
385387
let blooms = V.map (\(DeRef r) -> Run.runFilter r) runs
386388
indexes = V.map (\(DeRef r) -> Run.runIndex r) runs
387389
handles = V.map (\(DeRef r) -> Run.runKOpsFile r) runs

bench/micro/Bench/Database/LSMTree/Internal/Lookup.hs

Lines changed: 9 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -90,7 +90,7 @@ benchSalt = 4
9090

9191
benchLookups :: Config -> Benchmark
9292
benchLookups conf@Config{name} =
93-
withEnv $ \ ~(_dir, arenaManager, _hasFS, hasBlockIO, wbblobs, rs, ks) ->
93+
withEnv $ \ ~(_dir, arenaManager, _hasFS, hasBlockIO, _refCtx, wbblobs, rs, ks) ->
9494
env ( pure ( V.map (\(DeRef r) -> Run.runFilter r) rs
9595
, V.map (\(DeRef r) -> Run.runIndex r) rs
9696
, V.map (\(DeRef r) -> Run.runKOpsFile r) rs
@@ -182,6 +182,7 @@ lookupsInBatchesEnv ::
182182
, ArenaManager RealWorld
183183
, FS.HasFS IO FS.HandleIO
184184
, FS.HasBlockIO IO FS.HandleIO
185+
, RefCtx
185186
, Ref (WBB.WriteBufferBlobs IO FS.HandleIO)
186187
, V.Vector (Ref (Run IO FS.HandleIO))
187188
, V.Vector SerialisedKey
@@ -192,10 +193,11 @@ lookupsInBatchesEnv Config {..} = do
192193
benchTmpDir <- createTempDirectory sysTmpDir "lookupsInBatchesEnv"
193194
(storedKeys, lookupKeys) <- lookupsEnv (mkStdGen 17) nentries npos nneg
194195
(hasFS, hasBlockIO) <- FS.ioHasBlockIO (FS.MountPoint benchTmpDir) (fromMaybe FS.defaultIOCtxParams ioctxps)
195-
wbblobs <- WBB.new hasFS (FS.mkFsPath ["0.wbblobs"])
196+
refCtx <- newRefCtx
197+
wbblobs <- WBB.new hasFS refCtx (FS.mkFsPath ["0.wbblobs"])
196198
wb <- WB.fromMap <$> traverse (traverse (WBB.addBlob hasFS wbblobs)) storedKeys
197199
let fsps = RunFsPaths (FS.mkFsPath []) (RunNumber 0)
198-
r <- Run.fromWriteBuffer hasFS hasBlockIO benchSalt runParams fsps wb wbblobs
200+
r <- Run.fromWriteBuffer hasFS hasBlockIO refCtx benchSalt runParams fsps wb wbblobs
199201
let NumEntries nentriesReal = Run.size r
200202
assertEqual nentriesReal nentries $ pure ()
201203
-- 42 to 43 entries per page
@@ -204,6 +206,7 @@ lookupsInBatchesEnv Config {..} = do
204206
, arenaManager
205207
, hasFS
206208
, hasBlockIO
209+
, refCtx
207210
, wbblobs
208211
, V.singleton r
209212
, lookupKeys
@@ -222,16 +225,18 @@ lookupsInBatchesCleanup ::
222225
, ArenaManager RealWorld
223226
, FS.HasFS IO FS.HandleIO
224227
, FS.HasBlockIO IO FS.HandleIO
228+
, RefCtx
225229
, Ref (WBB.WriteBufferBlobs IO FS.HandleIO)
226230
, V.Vector (Ref (Run IO FS.HandleIO))
227231
, V.Vector SerialisedKey
228232
)
229233
-> IO ()
230-
lookupsInBatchesCleanup (tmpDir, _arenaManager, _hasFS, hasBlockIO, wbblobs, rs, _) = do
234+
lookupsInBatchesCleanup (tmpDir, _arenaManager, _hasFS, hasBlockIO, refCtx, wbblobs, rs, _) = do
231235
FS.close hasBlockIO
232236
forM_ rs releaseRef
233237
releaseRef wbblobs
234238
removeDirectoryRecursive tmpDir
239+
closeRefCtx refCtx
235240

236241
-- | Generate keys to store and keys to lookup
237242
lookupsEnv ::

bench/micro/Bench/Database/LSMTree/Internal/Merge.hs

Lines changed: 15 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -234,7 +234,7 @@ runParams =
234234

235235
benchMerge :: Config -> Benchmark
236236
benchMerge conf@Config{name} =
237-
withEnv $ \ ~(_dir, hasFS, hasBlockIO, runs) ->
237+
withEnv $ \ ~(_dir, hasFS, hasBlockIO, refCtx, runs) ->
238238
bgroup name [
239239
bench "merge" $
240240
-- We'd like to do: `whnfAppIO (runs' -> ...) runs`.
@@ -252,7 +252,7 @@ benchMerge conf@Config{name} =
252252
Cr.perRunEnvWithCleanup
253253
((runs,) <$> newIORef Nothing)
254254
(releaseRun . snd) $ \(runs', ref) -> do
255-
!run <- merge hasFS hasBlockIO conf outputRunPaths runs'
255+
!run <- merge hasFS hasBlockIO refCtx conf outputRunPaths runs'
256256
writeIORef ref $ Just $ releaseRef run
257257
]
258258
where
@@ -270,15 +270,16 @@ benchMerge conf@Config{name} =
270270
merge ::
271271
FS.HasFS IO FS.HandleIO
272272
-> FS.HasBlockIO IO FS.HandleIO
273+
-> RefCtx
273274
-> Config
274275
-> Run.RunFsPaths
275276
-> InputRuns
276277
-> IO (Ref (Run IO FS.HandleIO))
277-
merge fs hbio Config {..} targetPaths runs = do
278+
merge fs hbio refCtx Config {..} targetPaths runs = do
278279
let f = fromMaybe const mergeResolve
279280
m <- fromMaybe (error "empty inputs, no merge created") <$>
280281
Merge.new fs hbio benchSalt runParams mergeType f targetPaths runs
281-
Merge.stepsToCompletion m stepSize
282+
Merge.stepsToCompletion refCtx m stepSize
282283

283284
fsPath :: FS.FsPath
284285
fsPath = FS.mkFsPath []
@@ -368,39 +369,44 @@ mergeEnv ::
368369
-> IO ( FilePath -- ^ Temporary directory
369370
, FS.HasFS IO FS.HandleIO
370371
, FS.HasBlockIO IO FS.HandleIO
372+
, RefCtx
371373
, InputRuns
372374
)
373375
mergeEnv config = do
374376
sysTmpDir <- getCanonicalTemporaryDirectory
375377
benchTmpDir <- createTempDirectory sysTmpDir "mergeEnv"
376378
(hasFS, hasBlockIO) <- FS.ioHasBlockIO (FS.MountPoint benchTmpDir) FS.defaultIOCtxParams
377-
runs <- randomRuns hasFS hasBlockIO config (mkStdGen 17)
378-
pure (benchTmpDir, hasFS, hasBlockIO, runs)
379+
refCtx <- newRefCtx
380+
runs <- randomRuns hasFS hasBlockIO refCtx config (mkStdGen 17)
381+
pure (benchTmpDir, hasFS, hasBlockIO, refCtx, runs)
379382

380383
mergeEnvCleanup ::
381384
( FilePath -- ^ Temporary directory
382385
, FS.HasFS IO FS.HandleIO
383386
, FS.HasBlockIO IO FS.HandleIO
387+
, RefCtx
384388
, InputRuns
385389
)
386390
-> IO ()
387-
mergeEnvCleanup (tmpDir, _hasFS, hasBlockIO, runs) = do
391+
mergeEnvCleanup (tmpDir, _hasFS, hasBlockIO, refCtx, runs) = do
388392
traverse_ releaseRef runs
389393
removeDirectoryRecursive tmpDir
390394
FS.close hasBlockIO
395+
checkForgottenRefs refCtx
391396

392397
-- | Generate keys and entries to insert into the write buffer.
393398
-- They are already serialised to exclude the cost from the benchmark.
394399
randomRuns ::
395400
FS.HasFS IO FS.HandleIO
396401
-> FS.HasBlockIO IO FS.HandleIO
402+
-> RefCtx
397403
-> Config
398404
-> StdGen
399405
-> IO InputRuns
400-
randomRuns hasFS hasBlockIO config@Config {..} rng0 = do
406+
randomRuns hasFS hasBlockIO refCtx config@Config {..} rng0 = do
401407
counter <- inputRunPathsCounter
402408
fmap V.fromList $
403-
mapM (unsafeCreateRun hasFS hasBlockIO benchSalt runParams fsPath counter) $
409+
mapM (unsafeCreateRun hasFS hasBlockIO refCtx benchSalt runParams fsPath counter) $
404410
zipWith
405411
(randomRunData config)
406412
nentries

0 commit comments

Comments
 (0)