@@ -14,14 +14,12 @@ import qualified Data.Vector as V
14
14
import Data.Void
15
15
import Data.Word
16
16
import Database.LSMTree hiding (withTable )
17
- import qualified Database.LSMTree.Common as Common
18
17
import Database.LSMTree.Extras
19
18
import Database.LSMTree.Extras.Orphans ()
20
19
import Database.LSMTree.Internal.Assertions (fromIntegralChecked )
21
20
import qualified Database.LSMTree.Internal.RawBytes as RB
22
- import Database.LSMTree.Internal.Serialise.Class
23
21
import GHC.Generics (Generic )
24
- import Prelude hiding (getContents )
22
+ import Prelude hiding (getContents , take )
25
23
import System.Directory (removeDirectoryRecursive )
26
24
import qualified System.FS.API as FS
27
25
import qualified System.FS.BlockIO.API as FS
@@ -35,9 +33,9 @@ benchmarks = bgroup "Bench.Database.LSMTree" [
35
33
benchLargeValueVsSmallValueBlob
36
34
, benchCursorScanVsRangeLookupScan
37
35
, benchInsertBatches
38
- , benchInsertsVsMupserts
39
- , benchLookupsInsertsVsMupserts
40
- , benchLookupInsertsVsLookupMupserts
36
+ , benchInsertsVsUpserts
37
+ , benchLookupsInsertsVsUpserts
38
+ , benchLookupInsertsVsLookupUpserts
41
39
]
42
40
43
41
{- ------------------------------------------------------------------------------
@@ -75,17 +73,13 @@ newtype V3 = V3 Word64
75
73
76
74
type B3 = Void
77
75
78
- -- Simple addition
79
- resolve :: V3 -> V3 -> V3
80
- resolve = (+)
81
-
82
76
instance ResolveValue V3 where
83
- resolveValue = resolveDeserialised resolve
77
+ resolve = (+)
84
78
85
- benchConfig :: Common. TableConfig
86
- benchConfig = Common. defaultTableConfig {
87
- Common. confWriteBufferAlloc = Common. AllocNumEntries (Common. NumEntries 20000 )
88
- , Common. confFencePointerIndex = Common. CompactIndex
79
+ benchConfig :: TableConfig
80
+ benchConfig = defaultTableConfig
81
+ { confWriteBufferAlloc = AllocNumEntries (NumEntries 20000 )
82
+ , confFencePointerIndex = CompactIndex
89
83
}
90
84
91
85
{- ------------------------------------------------------------------------------
@@ -142,12 +136,12 @@ benchLargeValueVsSmallValueBlob =
142
136
initialise inss = do
143
137
(tmpDir, hfs, hbio) <- mkFiles
144
138
s <- openSession nullTracer hfs hbio (FS. mkFsPath [] )
145
- t <- new s benchConfig
139
+ t <- newTableWith benchConfig s
146
140
V. mapM_ (inserts t) inss
147
141
pure (tmpDir, hfs, hbio, s, t)
148
142
149
143
cleanup (tmpDir, hfs, hbio, s, t) = do
150
- close t
144
+ closeTable t
151
145
closeSession s
152
146
cleanupFiles (tmpDir, hfs, hbio)
153
147
@@ -172,11 +166,11 @@ benchCursorScanVsRangeLookupScan =
172
166
bgroup " cursor-scan-vs-range-lookup-scan" [
173
167
bench " cursor-scan-full" $ whnfIO $ do
174
168
withCursor t $ \ c -> do
175
- readCursor initialSize c
169
+ take initialSize c
176
170
, bench " cursor-scan-chunked" $ whnfIO $ do
177
171
withCursor t $ \ c -> do
178
172
forM_ ([1 .. numChunks] :: [Int ]) $ \ _ -> do
179
- readCursor readSize c
173
+ take readSize c
180
174
, bench " range-scan-full" $ whnfIO $ do
181
175
rangeLookup t (FromToIncluding (K minBound ) (K maxBound ))
182
176
, bench " range-scan-chunked" $ whnfIO $ do
@@ -227,12 +221,12 @@ benchCursorScanVsRangeLookupScan =
227
221
initialise inss = do
228
222
(tmpDir, hfs, hbio) <- mkFiles
229
223
s <- openSession nullTracer hfs hbio (FS. mkFsPath [] )
230
- t <- new s benchConfig
224
+ t <- newTableWith benchConfig s
231
225
V. mapM_ (inserts t) inss
232
226
pure (tmpDir, hfs, hbio, s, t)
233
227
234
228
cleanup (tmpDir, hfs, hbio, s, t) = do
235
- close t
229
+ closeTable t
236
230
closeSession s
237
231
cleanupFiles (tmpDir, hfs, hbio)
238
232
@@ -251,9 +245,9 @@ benchInsertBatches =
251
245
! initialSize = 100_000
252
246
! batchSize = 256
253
247
254
- _benchConfig :: Common. TableConfig
248
+ _benchConfig :: TableConfig
255
249
_benchConfig = benchConfig {
256
- Common. confWriteBufferAlloc = Common. AllocNumEntries (Common. NumEntries 1000 )
250
+ confWriteBufferAlloc = AllocNumEntries (NumEntries 1000 )
257
251
}
258
252
259
253
randomInserts :: Int -> V. Vector (K , V2 , Maybe Void )
@@ -272,31 +266,31 @@ benchInsertBatches =
272
266
initialise = do
273
267
(tmpDir, hfs, hbio) <- mkFiles
274
268
s <- openSession nullTracer hfs hbio (FS. mkFsPath [] )
275
- t <- new s _benchConfig
269
+ t <- newTableWith _benchConfig s
276
270
pure (tmpDir, hfs, hbio, s, t)
277
271
278
272
cleanup (tmpDir, hfs, hbio, s, t) = do
279
- close t
273
+ closeTable t
280
274
closeSession s
281
275
cleanupFiles (tmpDir, hfs, hbio)
282
276
283
277
{- ------------------------------------------------------------------------------
284
- Inserts vs. Mupserts
278
+ Inserts vs. Upserts
285
279
-------------------------------------------------------------------------------}
286
280
287
- -- | Compare inserts and mupserts . The logical contents of the resulting
281
+ -- | Compare inserts and upserts . The logical contents of the resulting
288
282
-- database are the same.
289
- benchInsertsVsMupserts :: Benchmark
290
- benchInsertsVsMupserts =
283
+ benchInsertsVsUpserts :: Benchmark
284
+ benchInsertsVsUpserts =
291
285
env (pure $ snd $ randomEntriesGrouped 800_000 250 ) $ \ ess ->
292
286
env (pure $ V. map mkInserts ess) $ \ inss ->
293
- bgroup " inserts-vs-mupserts " [
287
+ bgroup " inserts-vs-upserts " [
294
288
bench " inserts" $
295
289
withEmptyTable $ \ (_, _, _, _, t) ->
296
290
V. mapM_ (inserts t) inss
297
- , bench " mupserts " $
291
+ , bench " upserts " $
298
292
withEmptyTable $ \ (_, _, _, _, t) ->
299
- V. mapM_ (mupserts t) ess
293
+ V. mapM_ (upserts t) ess
300
294
]
301
295
where
302
296
withEmptyTable =
@@ -311,18 +305,18 @@ benchInsertsVsMupserts =
311
305
)
312
306
313
307
{- ------------------------------------------------------------------------------
314
- Lookups plus Inserts vs. Mupserts
308
+ Lookups plus Inserts vs. Upserts
315
309
-------------------------------------------------------------------------------}
316
310
317
- -- | Compare lookups+inserts to mupserts . The former costs 2 LSMT operations,
318
- -- while Mupserts only cost 1 LSMT operation. The number of operations do not
311
+ -- | Compare lookups+inserts to upserts . The former costs 2 LSMT operations,
312
+ -- while Upserts only cost 1 LSMT operation. The number of operations do not
319
313
-- directly translate to the number of I\/O operations, but one can assume that
320
- -- lookup+insert is roughly twice as costly as mupsert .
321
- benchLookupsInsertsVsMupserts :: Benchmark
322
- benchLookupsInsertsVsMupserts =
314
+ -- lookup+insert is roughly twice as costly as upsert .
315
+ benchLookupsInsertsVsUpserts :: Benchmark
316
+ benchLookupsInsertsVsUpserts =
323
317
env (pure $ snd $ randomEntriesGrouped 800_000 250 ) $ \ ess ->
324
318
env (pure $ V. map mkInserts ess) $ \ inss ->
325
- bgroup " lookups-inserts-vs-mupserts " [
319
+ bgroup " lookups-inserts-vs-upserts " [
326
320
bench " lookups-inserts" $
327
321
withTable inss $ \ (_, _, _, _, t) ->
328
322
-- Insert the same keys again, but we sum the existing values in
@@ -333,12 +327,12 @@ benchLookupsInsertsVsMupserts =
333
327
lrs <- lookups t (V. map fst es)
334
328
let ins' = V. zipWith f es lrs
335
329
inserts t ins'
336
- , bench " mupserts " $
330
+ , bench " upserts " $
337
331
withTable inss $ \ (_, _, _, _, t) ->
338
332
-- Insert the same keys again, but we sum the existing values in
339
333
-- the table with the values we are going to insert: submit
340
- -- mupserts with the insert values.
341
- V. forM_ ess $ \ es -> mupserts t es
334
+ -- upserts with the insert values.
335
+ V. forM_ ess $ \ es -> upserts t es
342
336
]
343
337
where
344
338
f (k, v) = \ case
@@ -359,20 +353,20 @@ benchLookupsInsertsVsMupserts =
359
353
)
360
354
361
355
{- ------------------------------------------------------------------------------
362
- Lookup Inserts vs. Lookup Mupserts
356
+ Lookup Inserts vs. Lookup Upserts
363
357
-------------------------------------------------------------------------------}
364
358
365
- -- | Compare lookups after inserts against lookups after mupserts .
366
- benchLookupInsertsVsLookupMupserts :: Benchmark
367
- benchLookupInsertsVsLookupMupserts =
359
+ -- | Compare lookups after inserts against lookups after upserts .
360
+ benchLookupInsertsVsLookupUpserts :: Benchmark
361
+ benchLookupInsertsVsLookupUpserts =
368
362
env (pure $ snd $ randomEntriesGrouped 80_000 250 ) $ \ ess ->
369
363
env (pure $ V. map mkInserts ess) $ \ inss ->
370
- bgroup " lookup-inserts-vs-lookup-mupserts " [
364
+ bgroup " lookup-inserts-vs-lookup-upserts " [
371
365
bench " lookup-inserts" $
372
366
withInsertTable inss $ \ (_, _, _, _, t) -> do
373
367
V. forM_ ess $ \ es -> lookups t (V. map fst es)
374
- , bench " lookup-mupserts " $
375
- withMupsertTable ess $ \ (_, _, _, _, t) -> do
368
+ , bench " lookup-upserts " $
369
+ withUpsertTable ess $ \ (_, _, _, _, t) -> do
376
370
V. forM_ ess $ \ es -> lookups t (V. map fst es)
377
371
]
378
372
where
@@ -393,14 +387,14 @@ benchLookupInsertsVsLookupMupserts =
393
387
cleanupFiles (tmpDir, hfs, hbio)
394
388
)
395
389
396
- withMupsertTable ess =
390
+ withUpsertTable ess =
397
391
perRunEnvWithCleanup
398
- -- Mupsert the same key 10 times. The results in a logical database
392
+ -- Upsert the same key 10 times. The results in a logical database
399
393
-- containing the original keys with the original value *10.
400
394
(do (tmpDir, hfs, hbio) <- mkFiles
401
395
(s, t) <- mkTable hfs hbio benchConfig
402
396
V. forM_ [1 .. 10 ] $ \ (_:: Int ) ->
403
- V. mapM_ (mupserts t) ess
397
+ V. mapM_ (upserts t) ess
404
398
pure (tmpDir, hfs, hbio, s, t)
405
399
)
406
400
(\ (tmpDir, hfs, hbio, s, t) -> do
@@ -458,7 +452,7 @@ mkTable ::
458
452
)
459
453
mkTable hfs hbio conf = do
460
454
sesh <- openSession nullTracer hfs hbio (FS. mkFsPath [] )
461
- t <- new sesh conf
455
+ t <- newTableWith conf sesh
462
456
pure (sesh, t)
463
457
464
458
cleanupTable ::
@@ -467,5 +461,5 @@ cleanupTable ::
467
461
)
468
462
-> IO ()
469
463
cleanupTable (s, t) = do
470
- close t
464
+ closeTable t
471
465
closeSession s
0 commit comments