22
33module Bench.Database.LSMTree.Internal.Lookup (benchmarks ) where
44
5- import Control.Exception (assert )
65import Control.Monad
76import Control.Monad.ST.Strict (stToIO )
87import Control.RefCount
@@ -11,16 +10,16 @@ import Criterion.Main (Benchmark, bench, bgroup, env, envWithCleanup,
1110import Data.Arena (ArenaManager , closeArena , newArena ,
1211 newArenaManager , withArena )
1312import Data.Bifunctor (Bifunctor (.. ))
13+ import Data.ByteString (ByteString )
1414import qualified Data.List as List
1515import Data.Map.Strict (Map )
1616import qualified Data.Map.Strict as Map
1717import Data.Maybe (fromMaybe )
1818import qualified Data.Vector as V
1919import Database.LSMTree.Extras.Orphans ()
20- import Database.LSMTree.Extras.Random (frequency ,
20+ import Database.LSMTree.Extras.Random (frequency , randomByteStringR ,
2121 sampleUniformWithReplacement , uniformWithoutReplacement )
2222import Database.LSMTree.Extras.UTxO
23- import Database.LSMTree.Internal.BlobRef (BlobSpan (.. ))
2423import Database.LSMTree.Internal.Entry (Entry (.. ), NumEntries (.. ))
2524import Database.LSMTree.Internal.Lookup (bloomQueries , indexSearches ,
2625 intraPageLookups , lookupsIO , prepLookups )
@@ -34,6 +33,7 @@ import Database.LSMTree.Internal.Serialise
3433import qualified Database.LSMTree.Internal.WriteBuffer as WB
3534import qualified Database.LSMTree.Internal.WriteBufferBlobs as WBB
3635import GHC.Exts (RealWorld )
36+ import GHC.Stack (HasCallStack )
3737import Prelude hiding (getContents )
3838import System.Directory (removeDirectoryRecursive )
3939import qualified System.FS.API as FS
@@ -83,7 +83,7 @@ benchmarks = bgroup "Bench.Database.LSMTree.Internal.Lookup" [
8383
8484benchLookups :: Config -> Benchmark
8585benchLookups conf@ Config {name} =
86- withEnv $ \ ~ (_dir, arenaManager, hasFS , hasBlockIO, rs, ks) ->
86+ withEnv $ \ ~ (_dir, arenaManager, _hasFS , hasBlockIO, wbblobs , rs, ks) ->
8787 env ( pure ( V. map (\ (DeRef r) -> Run. runFilter r) rs
8888 , V. map (\ (DeRef r) -> Run. runIndex r) rs
8989 , V. map (\ (DeRef r) -> Run. runKOpsFile r) rs
@@ -126,28 +126,24 @@ benchLookups conf@Config{name} =
126126 ( do arena <- newArena arenaManager
127127 (rkixs, ioops) <- stToIO (prepLookups arena blooms indexes kopsFiles ks)
128128 ioress <- FS. submitIO hasBlockIO ioops
129- wbblobs <- WBB. new hasFS (FS. mkFsPath [] )
130- pure (rkixs, ioops, ioress, arena, wbblobs)
129+ pure (rkixs, ioops, ioress, arena)
131130 )
132- (\ (_, _, _, arena, wbblobs) -> do
133- closeArena arenaManager arena
134- releaseRef wbblobs)
135- (\ ~ (rkixs, ioops, ioress, _, wbblobs_unused) -> do
136- ! _ <- intraPageLookups resolveV WB. empty wbblobs_unused
131+ (\ (_, _, _, arena) -> closeArena arenaManager arena)
132+ (\ ~ (rkixs, ioops, ioress, _) -> do
133+ ! _ <- intraPageLookups resolveV WB. empty wbblobs
137134 rs ks rkixs ioops ioress
138135 pure () )
139136 -- The whole shebang: lookup preparation, doing the IO, and then
140137 -- performing intra-page-lookups. Again, we evaluate the result to
141138 -- WHNF because it is the same result that intraPageLookups produces
142139 -- (see above).
143- , let wb_unused = WB. empty in
144- env (WBB. new hasFS (FS. mkFsPath [] )) $ \ wbblobs_unused ->
145- bench " Lookups in IO" $
140+ , bench " Lookups in IO" $
146141 whnfAppIO (\ ks' -> lookupsIO hasBlockIO arenaManager resolveV
147- wb_unused wbblobs_unused
142+ WB. empty wbblobs
148143 rs blooms indexes kopsFiles ks') ks
149144 ]
150- -- TODO: consider adding benchmarks that also use the write buffer
145+ -- TODO: consider adding benchmarks that also use the write buffer
146+ -- (then we can't just use 'WB.empty', but must take it from the env)
151147 where
152148 withEnv = envWithCleanup
153149 (lookupsInBatchesEnv conf)
@@ -181,6 +177,7 @@ lookupsInBatchesEnv ::
181177 , ArenaManager RealWorld
182178 , FS. HasFS IO FS. HandleIO
183179 , FS. HasBlockIO IO FS. HandleIO
180+ , Ref (WBB. WriteBufferBlobs IO FS. HandleIO )
184181 , V. Vector (Ref (Run IO FS. HandleIO ))
185182 , V. Vector SerialisedKey
186183 )
@@ -191,19 +188,19 @@ lookupsInBatchesEnv Config {..} = do
191188 (storedKeys, lookupKeys) <- lookupsEnv (mkStdGen 17 ) nentries npos nneg
192189 let hasFS = FS. ioHasFS (FS. MountPoint benchTmpDir)
193190 hasBlockIO <- FS. ioHasBlockIO hasFS (fromMaybe FS. defaultIOCtxParams ioctxps)
194- let wb = WB. fromMap storedKeys
195- fsps = RunFsPaths ( FS. mkFsPath [] ) ( RunNumber 0 )
196- wbblobs <- WBB. new hasFS (FS. mkFsPath [] )
191+ wbblobs <- WBB. new hasFS ( FS. mkFsPath [ " 0.wbblobs " ])
192+ wb <- WB. fromMap <$> traverse ( traverse ( WBB. addBlob hasFS wbblobs)) storedKeys
193+ let fsps = RunFsPaths (FS. mkFsPath [] ) ( RunNumber 0 )
197194 r <- Run. fromWriteBuffer hasFS hasBlockIO caching (RunAllocFixed 10 ) fsps wb wbblobs
198195 let NumEntries nentriesReal = Run. size r
199- assert (nentriesReal == nentries) $ pure ()
200- let npagesReal = Run. sizeInPages r
201- assert (getNumPages npagesReal * 42 <= nentriesReal) $ pure ()
202- assert (getNumPages npagesReal * 43 >= nentriesReal) $ pure ()
196+ assertEqual nentriesReal nentries $ pure ()
197+ -- 42 to 43 entries per page
198+ assertEqual (nentriesReal `div` getNumPages (Run. sizeInPages r)) 42 $ pure ()
203199 pure ( benchTmpDir
204200 , arenaManager
205201 , hasFS
206202 , hasBlockIO
203+ , wbblobs
207204 , V. singleton r
208205 , lookupKeys
209206 )
@@ -213,13 +210,15 @@ lookupsInBatchesCleanup ::
213210 , ArenaManager RealWorld
214211 , FS. HasFS IO FS. HandleIO
215212 , FS. HasBlockIO IO FS. HandleIO
213+ , Ref (WBB. WriteBufferBlobs IO FS. HandleIO )
216214 , V. Vector (Ref (Run IO FS. HandleIO ))
217215 , V. Vector SerialisedKey
218216 )
219217 -> IO ()
220- lookupsInBatchesCleanup (tmpDir, _arenaManager, _hasFS, hasBlockIO, rs, _) = do
218+ lookupsInBatchesCleanup (tmpDir, _arenaManager, _hasFS, hasBlockIO, wbblobs, rs, _) = do
221219 FS. close hasBlockIO
222220 forM_ rs releaseRef
221+ releaseRef wbblobs
223222 removeDirectoryRecursive tmpDir
224223
225224-- | Generate keys to store and keys to lookup
@@ -228,8 +227,8 @@ lookupsEnv ::
228227 -> Int -- ^ Number of stored key\/operation pairs
229228 -> Int -- ^ Number of positive lookups
230229 -> Int -- ^ Number of negative lookups
231- -> IO ( Map SerialisedKey (Entry SerialisedValue BlobSpan )
232- , V. Vector ( SerialisedKey )
230+ -> IO ( Map SerialisedKey (Entry SerialisedValue SerialisedBlob )
231+ , V. Vector SerialisedKey
233232 )
234233lookupsEnv g nentries npos nneg = do
235234 let (g1, g') = R. split g
@@ -242,25 +241,26 @@ lookupsEnv g nentries npos nneg = do
242241 lookups <- generate $ shuffle (negLookups ++ posLookups)
243242
244243 let entries' = Map. mapKeys serialiseKey
245- $ Map. map (bimap serialiseValue id ) entries
244+ $ Map. map (bimap serialiseValue serialiseBlob ) entries
246245 lookups' = V. fromList $ fmap serialiseKey lookups
247- assert (Map. size entries' == nentries) $ pure ()
248- assert (length lookups' == npos + nneg) $ pure ()
246+ assertEqual (Map. size entries') ( nentries) $ pure ()
247+ assertEqual (length lookups') ( npos + nneg) $ pure ()
249248 pure (entries', lookups')
250249
251250-- TODO: tweak distribution
252- randomEntry :: StdGen -> (Entry UTxOValue BlobSpan , StdGen )
251+ randomEntry :: StdGen -> (Entry UTxOValue ByteString , StdGen )
253252randomEntry g = frequency [
254253 (20 , \ g' -> let (! v, ! g'') = uniform g' in (Insert v, g''))
255254 , (1 , \ g' -> let (! v, ! g'') = uniform g'
256- (! b, ! g''') = genBlobSpan g''
255+ (! b, ! g''') = randomByteStringR ( 0 , 2000 ) g'' -- < 2kB
257256 in (InsertWithBlob v b, g'''))
258257 , (2 , \ g' -> let (! v, ! g'') = uniform g' in (Mupdate v, g''))
259258 , (2 , \ g' -> (Delete , g'))
260259 ] g
261260
262- genBlobSpan :: RandomGen g => g -> (BlobSpan , g )
263- genBlobSpan ! g =
264- let (off, ! g') = uniform g
265- (len, ! g'') = uniform g'
266- in (BlobSpan off len, g'')
261+ -- | Assertions on the generated environment should also be checked for release
262+ -- builds, so don't use 'Control.Exception.assert'.
263+ assertEqual :: (HasCallStack , Eq a , Show a ) => a -> a -> b -> b
264+ assertEqual x y
265+ | x == y = id
266+ | otherwise = error $ show x ++ " /= " ++ show y
0 commit comments