libmdbx-0.2.1.1: Bindings for libmdbx, an embedded key/value store
Copyright(c) 2021 Francisco Vallarino
LicenseBSD-3-Clause (see the LICENSE file)
Maintainerfjvallarino@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Mdbx.API

Description

Thin wrappers over the low level API to provide MonadIO support and exception based error handling.

Synopsis

Keys

keyCmp :: MonadIO m => MdbxTxn -> MdbxDbi -> MdbxVal -> MdbxVal -> m Int Source #

Compares two keys and returns -1, 0 or 1 if key1 is lower, equal or greater than key2.

Environment

envOpen :: (MonadIO m, MonadFail m) => String -> MdbxEnvGeometry -> [MdbxEnvFlags] -> m MdbxEnv Source #

Opens an environment.

When using the multi-threaded runtime, the MdbxNotls flag is required at environment creation. Failing to include it in the list of flags will result in a random crash.

envClose :: (MonadIO m, MonadFail m) => MdbxEnv -> m () Source #

Close an environment.

Transaction

txnBegin :: (MonadIO m, MonadFail m) => MdbxEnv -> Maybe MdbxTxn -> [MdbxTxnFlags] -> m MdbxTxn Source #

Begins a transaction.

txnCommit :: (MonadIO m, MonadFail m) => MdbxTxn -> m () Source #

Commits a transaction.

txnAbort :: (MonadIO m, MonadFail m) => MdbxTxn -> m () Source #

Aborts a transaction.

Database

dbiOpen :: (MonadIO m, MonadFail m) => MdbxEnv -> Maybe String -> [MdbxDbFlags] -> m MdbxDbi Source #

Opens a database (table).

dbiClose :: (MonadIO m, MonadFail m) => MdbxEnv -> MdbxDbi -> m () Source #

Closes a database.

Data manipulation

itemPut :: (MonadIO m, MonadFail m) => MdbxTxn -> MdbxDbi -> MdbxVal -> MdbxVal -> [MdbxPutFlags] -> m () Source #

Saves the provided key/value pair.

itemGet :: (MonadIO m, MonadFail m) => MdbxTxn -> MdbxDbi -> MdbxVal -> m (Maybe MdbxVal) Source #

Returns the value associated to the given key, if any.

itemDel :: (MonadIO m, MonadFail m) => MdbxTxn -> MdbxDbi -> MdbxVal -> Maybe MdbxVal -> m () Source #

Deletes the value associated with the given key, if any.

Cursors

cursorOpen :: (MonadIO m, MonadFail m) => MdbxTxn -> MdbxDbi -> m MdbxCursor Source #

Opens a cursor.

cursorClose :: (MonadIO m, MonadFail m) => MdbxCursor -> m () Source #

Closes a cursor.

cursorPut :: (MonadIO m, MonadFail m) => MdbxCursor -> MdbxVal -> MdbxVal -> [MdbxPutFlags] -> m () Source #

Stores the provided value at the given key, positioning the cursor on it.

cursorDel :: (MonadIO m, MonadFail m) => MdbxCursor -> [MdbxPutFlags] -> m () Source #

Deletes the value at the current position.

cursorFirst :: (MonadIO m, MonadFail m) => MdbxCursor -> m (Maybe (MdbxVal, MdbxVal)) Source #

Moves to the first key on the database.

cursorLast :: (MonadIO m, MonadFail m) => MdbxCursor -> m (Maybe (MdbxVal, MdbxVal)) Source #

Moves to the last key on the database.

cursorAt :: (MonadIO m, MonadFail m) => MdbxCursor -> MdbxVal -> m (Maybe (MdbxVal, MdbxVal)) Source #

Moves to the given key.

cursorRange :: (MonadIO m, MonadFail m) => MdbxCursor -> MdbxVal -> m (Maybe (MdbxVal, MdbxVal)) Source #

Moves to the given key or first greater than it. Useful for searching.

cursorNext :: (MonadIO m, MonadFail m) => MdbxCursor -> m (Maybe (MdbxVal, MdbxVal)) Source #

Moves to the next key.

cursorPrev :: (MonadIO m, MonadFail m) => MdbxCursor -> m (Maybe (MdbxVal, MdbxVal)) Source #

Moves to the previous key.

cursorMove :: (MonadIO m, MonadFail m) => MdbxCursor -> MdbxVal -> MdbxCursorOp -> m (Maybe (MdbxVal, MdbxVal)) Source #

Moves the cursor using the provided operation.

Conversion for types used in keys

keyFromFloat :: Float -> Word32 Source #

Converts a Float value to an unsigned Word that can be used by libmdbx's compare function.

keyFromDouble :: Double -> Word64 Source #

Converts a Double value to an unsigned Word that can be used by libmdbx's compare function.

keyFromInt32 :: Int32 -> Word32 Source #

Converts a 32bits signed Int value to an unsigned Word that can be used by libmdbx's compare function.

keyFromInt64 :: Int64 -> Word64 Source #

Converts a 64bits signed Int value to an unsigned Word that can be used by libmdbx's compare function.

floatFromKey :: Word32 -> Float Source #

Converts an unsigned Word to a Float value.

doubleFromKey :: Word64 -> Double Source #

Converts an unsigned Word to a Double value.

int32FromKey :: Word32 -> Int32 Source #

Converts an unsigned Word value to a 32bits signed Int.

int64FromKey :: Word64 -> Int64 Source #

Converts an unsigned Word value to a 64bits signed Int.