{-# LANGUAGE CPP #-}
module RocksDB (
Options,
withOptions,
optionsSetCreateIfMissing,
optionsSetMaxOpenFiles,
optionsSetCompression,
optionsIncreaseParallelism,
optionsOptimizeLevelStyleCompaction,
ReadOptions,
withReadOptions,
WriteOptions,
withWriteOptions,
writeOptionsDisableWAL,
RocksDB,
withRocksDB,
put,
get,
multiGet,
delete,
write,
checkpoint,
WriteBatch,
withWriteBatch,
writeBatchPut,
writeBatchDelete,
BlockTableOptions,
withBlockTableOptions,
blockBasedOptionsSetFilterPolicy,
optionsSetBlockBasedTableFactory,
FilterPolicy,
withFilterPolicyBloom,
) where
import Control.Exception (bracket)
import Control.Monad (forM)
import Data.ByteString (ByteString)
import Data.ByteString.Unsafe (unsafePackMallocCStringLen,
unsafeUseAsCStringLen)
import Data.Foldable.WithIndex (ifor_)
import Data.Word (Word64)
import Foreign.C.String (peekCString, withCString)
import Foreign.C.Types (CInt, CSize)
import Foreign.Marshal.Alloc (alloca, free)
import Foreign.Marshal.Array (allocaArray)
import Foreign.Marshal.Utils (withMany)
import Foreign.Ptr (Ptr, nullPtr)
import Foreign.Storable (peek, peekElemOff, poke, pokeElemOff)
import RocksDB.FFI
#if MIN_VERSION_base(4,18,0)
import Foreign.C.ConstPtr (ConstPtr (..))
#endif
#if MIN_VERSION_base(4,18,0)
constPtr :: Ptr a -> ConstPtr a
constPtr :: forall a. Ptr a -> ConstPtr a
constPtr = Ptr a -> ConstPtr a
forall a. Ptr a -> ConstPtr a
ConstPtr
#else
constPtr :: Ptr a -> Ptr a
constPtr = id
#endif
withErrPtr :: (ErrPtr -> IO r) -> IO r
withErrPtr :: forall r. (ErrPtr -> IO r) -> IO r
withErrPtr ErrPtr -> IO r
kont = (ErrPtr -> IO r) -> IO r
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((ErrPtr -> IO r) -> IO r) -> (ErrPtr -> IO r) -> IO r
forall a b. (a -> b) -> a -> b
$ \ErrPtr
ptr -> do
ErrPtr -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ErrPtr
ptr CString
forall a. Ptr a
nullPtr
r
x <- ErrPtr -> IO r
kont ErrPtr
ptr
CString
ptr' <- ErrPtr -> IO CString
forall a. Storable a => Ptr a -> IO a
peek ErrPtr
ptr
if CString
ptr' CString -> CString -> Bool
forall a. Eq a => a -> a -> Bool
== CString
forall a. Ptr a
nullPtr
then () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
else CString -> IO ()
forall a. Ptr a -> IO ()
free CString
ptr'
r -> IO r
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return r
x
assertErrPtr :: String -> ErrPtr -> IO ()
assertErrPtr :: String -> ErrPtr -> IO ()
assertErrPtr String
fun ErrPtr
ptr = do
CString
ptr' <- ErrPtr -> IO CString
forall a. Storable a => Ptr a -> IO a
peek ErrPtr
ptr
if CString
ptr' CString -> CString -> Bool
forall a. Eq a => a -> a -> Bool
== CString
forall a. Ptr a
nullPtr
then () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
else do
String
msg <- CString -> IO String
peekCString CString
ptr'
String -> IO ()
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
fun String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
msg
newtype Options = Options (Ptr OPTIONS)
withOptions :: (Options -> IO r) -> IO r
withOptions :: forall r. (Options -> IO r) -> IO r
withOptions Options -> IO r
kont = IO (Ptr OPTIONS)
-> (Ptr OPTIONS -> IO ()) -> (Ptr OPTIONS -> IO r) -> IO r
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket
IO (Ptr OPTIONS)
rocksdb_options_create
Ptr OPTIONS -> IO ()
rocksdb_options_destroy
(\Ptr OPTIONS
ptr -> Options -> IO r
kont (Ptr OPTIONS -> Options
Options Ptr OPTIONS
ptr))
optionsSetCreateIfMissing :: Options -> Bool -> IO ()
optionsSetCreateIfMissing :: Options -> Bool -> IO ()
optionsSetCreateIfMissing (Options Ptr OPTIONS
ptr) Bool
v =
Ptr OPTIONS -> CUChar -> IO ()
rocksdb_options_set_create_if_missing Ptr OPTIONS
ptr (if Bool
v then CUChar
1 else CUChar
0)
optionsIncreaseParallelism :: Options -> Int -> IO ()
optionsIncreaseParallelism :: Options -> Int -> IO ()
optionsIncreaseParallelism (Options Ptr OPTIONS
ptr) Int
v =
Ptr OPTIONS -> CInt -> IO ()
rocksdb_options_increase_parallelism Ptr OPTIONS
ptr (Int -> CInt
intToCInt Int
v)
optionsSetMaxOpenFiles :: Options -> Int -> IO ()
optionsSetMaxOpenFiles :: Options -> Int -> IO ()
optionsSetMaxOpenFiles (Options Ptr OPTIONS
ptr) Int
v =
Ptr OPTIONS -> CInt -> IO ()
rocksdb_options_set_max_open_files Ptr OPTIONS
ptr (Int -> CInt
intToCInt Int
v)
optionsOptimizeLevelStyleCompaction :: Options -> Word64 -> IO ()
optionsOptimizeLevelStyleCompaction :: Options -> Word64 -> IO ()
optionsOptimizeLevelStyleCompaction (Options Ptr OPTIONS
ptr) Word64
v =
Ptr OPTIONS -> Word64 -> IO ()
rocksdb_options_optimize_level_style_compaction Ptr OPTIONS
ptr Word64
v
optionsSetCompression :: Options -> Int -> IO ()
optionsSetCompression :: Options -> Int -> IO ()
optionsSetCompression (Options Ptr OPTIONS
ptr) Int
v =
Ptr OPTIONS -> CInt -> IO ()
rocksdb_options_set_compression Ptr OPTIONS
ptr (Int -> CInt
intToCInt Int
v)
newtype ReadOptions = ReadOptions (Ptr READOPTIONS)
withReadOptions :: (ReadOptions -> IO r) -> IO r
withReadOptions :: forall r. (ReadOptions -> IO r) -> IO r
withReadOptions ReadOptions -> IO r
kont = IO (Ptr READOPTIONS)
-> (Ptr READOPTIONS -> IO ()) -> (Ptr READOPTIONS -> IO r) -> IO r
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket
IO (Ptr READOPTIONS)
rocksdb_readoptions_create
Ptr READOPTIONS -> IO ()
rocksdb_readoptions_destroy
(\Ptr READOPTIONS
ptr -> ReadOptions -> IO r
kont (Ptr READOPTIONS -> ReadOptions
ReadOptions Ptr READOPTIONS
ptr))
newtype WriteOptions = WriteOptions (Ptr WRITEOPTIONS)
withWriteOptions :: (WriteOptions -> IO r) -> IO r
withWriteOptions :: forall r. (WriteOptions -> IO r) -> IO r
withWriteOptions WriteOptions -> IO r
kont = IO (Ptr WRITEOPTIONS)
-> (Ptr WRITEOPTIONS -> IO ())
-> (Ptr WRITEOPTIONS -> IO r)
-> IO r
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket
IO (Ptr WRITEOPTIONS)
rocksdb_writeoptions_create
Ptr WRITEOPTIONS -> IO ()
rocksdb_writeoptions_destroy
(\Ptr WRITEOPTIONS
ptr -> WriteOptions -> IO r
kont (Ptr WRITEOPTIONS -> WriteOptions
WriteOptions Ptr WRITEOPTIONS
ptr))
writeOptionsDisableWAL :: WriteOptions -> Bool -> IO ()
writeOptionsDisableWAL :: WriteOptions -> Bool -> IO ()
writeOptionsDisableWAL (WriteOptions Ptr WRITEOPTIONS
opts) Bool
disable =
Ptr WRITEOPTIONS -> CInt -> IO ()
rocksdb_writeoptions_disable_WAL Ptr WRITEOPTIONS
opts (if Bool
disable then CInt
1 else CInt
0)
data RocksDB = RocksDB (Ptr DB) ErrPtr
withRocksDB :: Options -> FilePath -> (RocksDB -> IO r) -> IO r
withRocksDB :: forall r. Options -> String -> (RocksDB -> IO r) -> IO r
withRocksDB (Options Ptr OPTIONS
opt) String
path RocksDB -> IO r
kont =
String -> (CString -> IO r) -> IO r
forall a. String -> (CString -> IO a) -> IO a
withCString String
path ((CString -> IO r) -> IO r) -> (CString -> IO r) -> IO r
forall a b. (a -> b) -> a -> b
$ \CString
path' ->
(ErrPtr -> IO r) -> IO r
forall r. (ErrPtr -> IO r) -> IO r
withErrPtr ((ErrPtr -> IO r) -> IO r) -> (ErrPtr -> IO r) -> IO r
forall a b. (a -> b) -> a -> b
$ \ErrPtr
errptr ->
IO (Ptr DB) -> (Ptr DB -> IO ()) -> (Ptr DB -> IO r) -> IO r
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (CString -> ErrPtr -> IO (Ptr DB)
rocksdb_open' CString
path' ErrPtr
errptr) Ptr DB -> IO ()
rocksdb_close ((Ptr DB -> IO r) -> IO r) -> (Ptr DB -> IO r) -> IO r
forall a b. (a -> b) -> a -> b
$ \Ptr DB
ptr ->
RocksDB -> IO r
kont (Ptr DB -> ErrPtr -> RocksDB
RocksDB Ptr DB
ptr ErrPtr
errptr)
where
rocksdb_open' :: CString -> ErrPtr -> IO (Ptr DB)
rocksdb_open' CString
path' ErrPtr
errptr = do
Ptr DB
ptr <- Ptr OPTIONS -> CString -> ErrPtr -> IO (Ptr DB)
rocksdb_open Ptr OPTIONS
opt CString
path' ErrPtr
errptr
String -> ErrPtr -> IO ()
assertErrPtr String
"rocksdb_open" ErrPtr
errptr
Ptr DB -> IO (Ptr DB)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DB
ptr
put :: RocksDB -> WriteOptions -> ByteString -> ByteString -> IO ()
put :: RocksDB -> WriteOptions -> ByteString -> ByteString -> IO ()
put (RocksDB Ptr DB
dbPtr ErrPtr
errPtr) (WriteOptions Ptr WRITEOPTIONS
opts) ByteString
key ByteString
val =
ByteString -> (CStringLen -> IO ()) -> IO ()
forall a. ByteString -> (CStringLen -> IO a) -> IO a
unsafeUseAsCStringLen ByteString
key ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(CString
kp, Int
kl) ->
ByteString -> (CStringLen -> IO ()) -> IO ()
forall a. ByteString -> (CStringLen -> IO a) -> IO a
unsafeUseAsCStringLen ByteString
val ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(CString
vp, Int
vl) -> do
Ptr DB
-> Ptr WRITEOPTIONS
-> CString
-> CSize
-> CString
-> CSize
-> ErrPtr
-> IO ()
rocksdb_put Ptr DB
dbPtr Ptr WRITEOPTIONS
opts CString
kp (Int -> CSize
intToCSize Int
kl) CString
vp (Int -> CSize
intToCSize Int
vl) ErrPtr
errPtr
String -> ErrPtr -> IO ()
assertErrPtr String
"rocksdb_put" ErrPtr
errPtr
get :: RocksDB -> ReadOptions -> ByteString -> IO (Maybe ByteString)
get :: RocksDB -> ReadOptions -> ByteString -> IO (Maybe ByteString)
get (RocksDB Ptr DB
dbPtr ErrPtr
errPtr) (ReadOptions Ptr READOPTIONS
opts) ByteString
key =
ByteString
-> (CStringLen -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a. ByteString -> (CStringLen -> IO a) -> IO a
unsafeUseAsCStringLen ByteString
key ((CStringLen -> IO (Maybe ByteString)) -> IO (Maybe ByteString))
-> (CStringLen -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \(CString
kp, Int
kl) ->
(Ptr CSize -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CSize -> IO (Maybe ByteString)) -> IO (Maybe ByteString))
-> (Ptr CSize -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr CSize
vlPtr -> do
CString
vp <- Ptr DB
-> Ptr READOPTIONS
-> CString
-> CSize
-> Ptr CSize
-> ErrPtr
-> IO CString
rocksdb_get Ptr DB
dbPtr Ptr READOPTIONS
opts CString
kp (Int -> CSize
intToCSize Int
kl) Ptr CSize
vlPtr ErrPtr
errPtr
String -> ErrPtr -> IO ()
assertErrPtr String
"rocksdb_get" ErrPtr
errPtr
CSize
vl <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek Ptr CSize
vlPtr
if CString
vp CString -> CString -> Bool
forall a. Eq a => a -> a -> Bool
== CString
forall a. Ptr a
nullPtr
then Maybe ByteString -> IO (Maybe ByteString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
else ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> IO ByteString -> IO (Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CStringLen -> IO ByteString
unsafePackMallocCStringLen (CString
vp, CSize -> Int
csizeToInt CSize
vl)
multiGet :: RocksDB -> ReadOptions -> [ByteString] -> IO [Maybe ByteString]
multiGet :: RocksDB -> ReadOptions -> [ByteString] -> IO [Maybe ByteString]
multiGet (RocksDB Ptr DB
db ErrPtr
_errPtr) (ReadOptions Ptr READOPTIONS
opts) [ByteString]
keys =
Int
-> (Ptr (ConstPtr CChar) -> IO [Maybe ByteString])
-> IO [Maybe ByteString]
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray Int
n ((Ptr (ConstPtr CChar) -> IO [Maybe ByteString])
-> IO [Maybe ByteString])
-> (Ptr (ConstPtr CChar) -> IO [Maybe ByteString])
-> IO [Maybe ByteString]
forall a b. (a -> b) -> a -> b
$ \Ptr (ConstPtr CChar)
kps ->
Int
-> (Ptr CSize -> IO [Maybe ByteString]) -> IO [Maybe ByteString]
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray Int
n ((Ptr CSize -> IO [Maybe ByteString]) -> IO [Maybe ByteString])
-> (Ptr CSize -> IO [Maybe ByteString]) -> IO [Maybe ByteString]
forall a b. (a -> b) -> a -> b
$ \Ptr CSize
kls ->
Int -> (ErrPtr -> IO [Maybe ByteString]) -> IO [Maybe ByteString]
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray Int
n ((ErrPtr -> IO [Maybe ByteString]) -> IO [Maybe ByteString])
-> (ErrPtr -> IO [Maybe ByteString]) -> IO [Maybe ByteString]
forall a b. (a -> b) -> a -> b
$ \ErrPtr
vps ->
Int
-> (Ptr CSize -> IO [Maybe ByteString]) -> IO [Maybe ByteString]
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray Int
n ((Ptr CSize -> IO [Maybe ByteString]) -> IO [Maybe ByteString])
-> (Ptr CSize -> IO [Maybe ByteString]) -> IO [Maybe ByteString]
forall a b. (a -> b) -> a -> b
$ \Ptr CSize
vls ->
Int -> (ErrPtr -> IO [Maybe ByteString]) -> IO [Maybe ByteString]
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray Int
n ((ErrPtr -> IO [Maybe ByteString]) -> IO [Maybe ByteString])
-> (ErrPtr -> IO [Maybe ByteString]) -> IO [Maybe ByteString]
forall a b. (a -> b) -> a -> b
$ \ErrPtr
errs ->
(ByteString
-> (CStringLen -> IO [Maybe ByteString]) -> IO [Maybe ByteString])
-> [ByteString]
-> ([CStringLen] -> IO [Maybe ByteString])
-> IO [Maybe ByteString]
forall a b res.
(a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
withMany ByteString
-> (CStringLen -> IO [Maybe ByteString]) -> IO [Maybe ByteString]
forall a. ByteString -> (CStringLen -> IO a) -> IO a
unsafeUseAsCStringLen [ByteString]
keys (([CStringLen] -> IO [Maybe ByteString]) -> IO [Maybe ByteString])
-> ([CStringLen] -> IO [Maybe ByteString]) -> IO [Maybe ByteString]
forall a b. (a -> b) -> a -> b
$ \[CStringLen]
keys' -> do
[CStringLen] -> (Int -> CStringLen -> IO ()) -> IO ()
forall i (t :: * -> *) (f :: * -> *) a b.
(FoldableWithIndex i t, Applicative f) =>
t a -> (i -> a -> f b) -> f ()
ifor_ [CStringLen]
keys' ((Int -> CStringLen -> IO ()) -> IO ())
-> (Int -> CStringLen -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Int
i (CString
kp, Int
kl) -> do
Ptr (ConstPtr CChar) -> Int -> ConstPtr CChar -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr (ConstPtr CChar)
kps Int
i (CString -> ConstPtr CChar
forall a. Ptr a -> ConstPtr a
constPtr CString
kp)
Ptr CSize -> Int -> CSize -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr CSize
kls Int
i (Int -> CSize
intToCSize Int
kl)
Ptr DB
-> Ptr READOPTIONS
-> CSize
-> Ptr (ConstPtr CChar)
-> Ptr CSize
-> ErrPtr
-> Ptr CSize
-> ErrPtr
-> IO ()
rocksdb_multi_get Ptr DB
db Ptr READOPTIONS
opts (Int -> CSize
intToCSize Int
n) Ptr (ConstPtr CChar)
kps Ptr CSize
kls ErrPtr
vps Ptr CSize
vls ErrPtr
errs
[Int] -> (Int -> IO (Maybe ByteString)) -> IO [Maybe ByteString]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [ Int
0 .. Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1 ] ((Int -> IO (Maybe ByteString)) -> IO [Maybe ByteString])
-> (Int -> IO (Maybe ByteString)) -> IO [Maybe ByteString]
forall a b. (a -> b) -> a -> b
$ \Int
i -> do
CString
vp <- ErrPtr -> Int -> IO CString
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff ErrPtr
vps Int
i
CSize
vl <- Ptr CSize -> Int -> IO CSize
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr CSize
vls Int
i
if CString
vp CString -> CString -> Bool
forall a. Eq a => a -> a -> Bool
== CString
forall a. Ptr a
nullPtr
then Maybe ByteString -> IO (Maybe ByteString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
else ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> IO ByteString -> IO (Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CStringLen -> IO ByteString
unsafePackMallocCStringLen (CString
vp, CSize -> Int
csizeToInt CSize
vl)
where
n :: Int
n = [ByteString] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ByteString]
keys
delete :: RocksDB -> WriteOptions -> ByteString -> IO ()
delete :: RocksDB -> WriteOptions -> ByteString -> IO ()
delete (RocksDB Ptr DB
dbPtr ErrPtr
errPtr) (WriteOptions Ptr WRITEOPTIONS
opts) ByteString
key =
ByteString -> (CStringLen -> IO ()) -> IO ()
forall a. ByteString -> (CStringLen -> IO a) -> IO a
unsafeUseAsCStringLen ByteString
key ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(CString
kp, Int
kl) -> do
Ptr DB -> Ptr WRITEOPTIONS -> CString -> CSize -> ErrPtr -> IO ()
rocksdb_delete Ptr DB
dbPtr Ptr WRITEOPTIONS
opts CString
kp (Int -> CSize
intToCSize Int
kl) ErrPtr
errPtr
String -> ErrPtr -> IO ()
assertErrPtr String
"rocksdb_delete" ErrPtr
errPtr
write :: RocksDB -> WriteOptions -> WriteBatch -> IO ()
write :: RocksDB -> WriteOptions -> WriteBatch -> IO ()
write (RocksDB Ptr DB
dbPtr ErrPtr
errPtr) (WriteOptions Ptr WRITEOPTIONS
opts) (WriteBatch Ptr WRITEBATCH
batch) = do
Ptr DB -> Ptr WRITEOPTIONS -> Ptr WRITEBATCH -> ErrPtr -> IO ()
rocksdb_write Ptr DB
dbPtr Ptr WRITEOPTIONS
opts Ptr WRITEBATCH
batch ErrPtr
errPtr
String -> ErrPtr -> IO ()
assertErrPtr String
"rocksdb_write" ErrPtr
errPtr
checkpoint :: RocksDB -> FilePath -> IO ()
checkpoint :: RocksDB -> String -> IO ()
checkpoint (RocksDB Ptr DB
dbPtr ErrPtr
errPtr) String
path =
String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withCString String
path ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
path' ->
IO (Ptr CHECKPOINT)
-> (Ptr CHECKPOINT -> IO ()) -> (Ptr CHECKPOINT -> IO ()) -> IO ()
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket IO (Ptr CHECKPOINT)
rocksdb_checkpoint_object_create' Ptr CHECKPOINT -> IO ()
rocksdb_checkpoint_object_destroy ((Ptr CHECKPOINT -> IO ()) -> IO ())
-> (Ptr CHECKPOINT -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr CHECKPOINT
cp -> do
Ptr CHECKPOINT -> CString -> Word64 -> ErrPtr -> IO ()
rocksdb_checkpoint_create Ptr CHECKPOINT
cp CString
path' Word64
0 ErrPtr
errPtr
String -> ErrPtr -> IO ()
assertErrPtr String
"rocksdb_checkpoint_create" ErrPtr
errPtr
where
rocksdb_checkpoint_object_create' :: IO (Ptr CHECKPOINT)
rocksdb_checkpoint_object_create' = do
Ptr CHECKPOINT
cp <- Ptr DB -> ErrPtr -> IO (Ptr CHECKPOINT)
rocksdb_checkpoint_object_create Ptr DB
dbPtr ErrPtr
errPtr
String -> ErrPtr -> IO ()
assertErrPtr String
"rocksdb_checkpoint_object_create" ErrPtr
errPtr
Ptr CHECKPOINT -> IO (Ptr CHECKPOINT)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CHECKPOINT
cp
newtype WriteBatch = WriteBatch (Ptr WRITEBATCH)
withWriteBatch :: (WriteBatch -> IO r) -> IO r
withWriteBatch :: forall r. (WriteBatch -> IO r) -> IO r
withWriteBatch WriteBatch -> IO r
kont = IO (Ptr WRITEBATCH)
-> (Ptr WRITEBATCH -> IO ()) -> (Ptr WRITEBATCH -> IO r) -> IO r
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket
IO (Ptr WRITEBATCH)
rocksdb_writebatch_create
Ptr WRITEBATCH -> IO ()
rocksdb_writebatch_destroy
(\Ptr WRITEBATCH
ptr -> WriteBatch -> IO r
kont (Ptr WRITEBATCH -> WriteBatch
WriteBatch Ptr WRITEBATCH
ptr))
writeBatchPut :: WriteBatch -> ByteString -> ByteString -> IO ()
writeBatchPut :: WriteBatch -> ByteString -> ByteString -> IO ()
writeBatchPut (WriteBatch Ptr WRITEBATCH
batch) ByteString
key ByteString
val =
ByteString -> (CStringLen -> IO ()) -> IO ()
forall a. ByteString -> (CStringLen -> IO a) -> IO a
unsafeUseAsCStringLen ByteString
key ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(CString
kp, Int
kl) ->
ByteString -> (CStringLen -> IO ()) -> IO ()
forall a. ByteString -> (CStringLen -> IO a) -> IO a
unsafeUseAsCStringLen ByteString
val ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(CString
vp, Int
vl) ->
Ptr WRITEBATCH -> CString -> CSize -> CString -> CSize -> IO ()
rocksdb_writebatch_put Ptr WRITEBATCH
batch CString
kp (Int -> CSize
intToCSize Int
kl) CString
vp (Int -> CSize
intToCSize Int
vl)
writeBatchDelete :: WriteBatch -> ByteString -> IO ()
writeBatchDelete :: WriteBatch -> ByteString -> IO ()
writeBatchDelete (WriteBatch Ptr WRITEBATCH
batch) ByteString
key =
ByteString -> (CStringLen -> IO ()) -> IO ()
forall a. ByteString -> (CStringLen -> IO a) -> IO a
unsafeUseAsCStringLen ByteString
key ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(CString
kp, Int
kl) ->
Ptr WRITEBATCH -> CString -> CSize -> IO ()
rocksdb_writebatch_delete Ptr WRITEBATCH
batch CString
kp (Int -> CSize
intToCSize Int
kl)
newtype BlockTableOptions = BlockTableOptions (Ptr BLOCKTABLEOPTIONS)
withBlockTableOptions :: (BlockTableOptions -> IO r) -> IO r
withBlockTableOptions :: forall r. (BlockTableOptions -> IO r) -> IO r
withBlockTableOptions BlockTableOptions -> IO r
kont = IO (Ptr BLOCKTABLEOPTIONS)
-> (Ptr BLOCKTABLEOPTIONS -> IO ())
-> (Ptr BLOCKTABLEOPTIONS -> IO r)
-> IO r
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket
IO (Ptr BLOCKTABLEOPTIONS)
rocksdb_block_based_options_create
Ptr BLOCKTABLEOPTIONS -> IO ()
rocksdb_block_based_options_destroy
(\Ptr BLOCKTABLEOPTIONS
ptr -> BlockTableOptions -> IO r
kont (Ptr BLOCKTABLEOPTIONS -> BlockTableOptions
BlockTableOptions Ptr BLOCKTABLEOPTIONS
ptr))
blockBasedOptionsSetFilterPolicy :: BlockTableOptions -> FilterPolicy -> IO ()
blockBasedOptionsSetFilterPolicy :: BlockTableOptions -> FilterPolicy -> IO ()
blockBasedOptionsSetFilterPolicy (BlockTableOptions Ptr BLOCKTABLEOPTIONS
opts) (FilterPolicy Ptr FILTERPOLICY
policy) =
Ptr BLOCKTABLEOPTIONS -> Ptr FILTERPOLICY -> IO ()
rocksdb_block_based_options_set_filter_policy Ptr BLOCKTABLEOPTIONS
opts Ptr FILTERPOLICY
policy
optionsSetBlockBasedTableFactory :: Options -> BlockTableOptions -> IO ()
optionsSetBlockBasedTableFactory :: Options -> BlockTableOptions -> IO ()
optionsSetBlockBasedTableFactory (Options Ptr OPTIONS
opts) (BlockTableOptions Ptr BLOCKTABLEOPTIONS
ptr) =
Ptr OPTIONS -> Ptr BLOCKTABLEOPTIONS -> IO ()
rocksdb_options_set_block_based_table_factory Ptr OPTIONS
opts Ptr BLOCKTABLEOPTIONS
ptr
newtype FilterPolicy = FilterPolicy (Ptr FILTERPOLICY)
withFilterPolicyBloom :: Int -> (FilterPolicy -> IO r) -> IO r
withFilterPolicyBloom :: forall r. Int -> (FilterPolicy -> IO r) -> IO r
withFilterPolicyBloom Int
bits_per_key FilterPolicy -> IO r
kont = IO (Ptr FILTERPOLICY)
-> (Ptr FILTERPOLICY -> IO ())
-> (Ptr FILTERPOLICY -> IO r)
-> IO r
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket
(CInt -> IO (Ptr FILTERPOLICY)
rocksdb_filterpolicy_create_bloom (Int -> CInt
intToCInt Int
bits_per_key))
(\Ptr FILTERPOLICY
_ -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
(\Ptr FILTERPOLICY
ptr -> FilterPolicy -> IO r
kont (Ptr FILTERPOLICY -> FilterPolicy
FilterPolicy Ptr FILTERPOLICY
ptr))
intToCSize :: Int -> CSize
intToCSize :: Int -> CSize
intToCSize = Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral
csizeToInt :: CSize -> Int
csizeToInt :: CSize -> Int
csizeToInt = CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
intToCInt :: Int -> CInt
intToCInt :: Int -> CInt
intToCInt = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral