Skip to content

Commit

Permalink
WIP
Browse files Browse the repository at this point in the history
  • Loading branch information
phadej committed Apr 25, 2024
1 parent e57ec32 commit c8499be
Show file tree
Hide file tree
Showing 2 changed files with 49 additions and 2 deletions.
50 changes: 48 additions & 2 deletions bench/macro/lsm-tree-bench-wp8.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,20 +2,24 @@
{-# LANGUAGE NoFieldSelectors #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
module Main (main) where

import Control.Applicative ((<**>))
import Control.Exception (bracket)
import qualified Crypto.Hash.SHA256 as SHA256
import qualified Data.Binary as B
import qualified Data.ByteString as BS
import qualified Data.ByteString.Short as SBS
import Data.Void (Void)
import Data.Word (Word64)
import qualified Options.Applicative as O
import qualified System.Clock as Clock
import qualified System.FS.API as FS
import qualified System.FS.IO as FsIO

-- We should be able to write this benchmark
-- using only use public lsm-tree interface
import qualified Database.LSMTree.Common as LSM (mkSnapshotName)
import qualified Database.LSMTree.Normal as LSM

-------------------------------------------------------------------------------
Expand Down Expand Up @@ -105,8 +109,24 @@ timed_ action = do
-- setup
-------------------------------------------------------------------------------

-- https://input-output-hk.github.io/fs-sim
doSetup :: GlobalOpts -> SetupOpts -> IO ()
doSetup _gopts _opts = return ()
doSetup gopts _opts = do
let mountPoint :: FS.MountPoint
mountPoint = FS.MountPoint gopts.rootDir

let someFs :: FS.SomeHasFS IO
someFs = FS.SomeHasFS (FsIO.ioHasFS mountPoint)

name <- maybe (fail "invalid snapshot name") return $
LSM.mkSnapshotName "bench"

withSession someFs (FS.mkFsPath []) $ \session -> do
tbh <- LSM.new @IO @K @V @B session defaultTableConfig

-- TODO: insert data into initial table

LSM.snapshot name tbh

-------------------------------------------------------------------------------
-- main
Expand All @@ -124,3 +144,29 @@ main = do
where
cliP = O.info ((,) <$> globalOptsP <*> cmdP <**> O.helper) O.fullDesc
prefs = O.prefs O.showHelpOnEmpty

-------------------------------------------------------------------------------
-- utils
-------------------------------------------------------------------------------

withSession :: FS.SomeHasFS IO -> FS.FsPath -> (LSM.Session IO -> IO r) -> IO r
withSession fs path = bracket (LSM.openSession fs path) LSM.closeSession

defaultTableConfig :: LSM.TableConfig
defaultTableConfig = LSM.TableConfig
{ LSM.tcMaxBufferMemory = 1000
, LSM.tcMaxBloomFilterMemory = 1000
, LSM.tcBitPrecision = ()
}

-------------------------------------------------------------------------------
-- TODO
-------------------------------------------------------------------------------

_unused :: ()
_unused = const ()
( makeKey
, theValue
, timed
, timed_
)
1 change: 1 addition & 0 deletions lsm-tree.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -351,6 +351,7 @@ benchmark lsm-tree-bench-wp8
, bytestring
, clock
, cryptohash-sha256
, fs-api
, lsm-tree
, optparse-applicative
, primitive
Expand Down

0 comments on commit c8499be

Please sign in to comment.