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.FFI

Description

Low level bindings to libmdbx functions.

Synopsis

Environment

data MdbxEnvFlags Source #

Flags for opening an environment.

newtype MdbxEnv Source #

Environment object, needed for all the operations.

Constructors

MdbxEnv (Ptr MdbxEnv) 

Instances

Instances details
Storable MdbxEnv Source # 
Instance details

Defined in Mdbx.FFI

type MdbxEnvMode = CUInt Source #

UNIX permissions to set on created files. Zero value means to open existing, but do not create.

mdbx_env_create :: IO (Int, MdbxEnv) Source #

Creates an environment. Represents a database in the file system.

mdbx_env_set_geometry :: MdbxEnv -> Int -> Int -> Int -> Int -> Int -> Int -> IO Int Source #

Sets geometry of an environment. All the parameters can receive -1 to keep the current value. Receives (expressed in bytes): size_lower, size_now, size_upper, growth_step, shrink_threshold, pagesize.

mdbx_env_open :: MdbxEnv -> String -> [MdbxEnvFlags] -> MdbxEnvMode -> IO Int Source #

Opens an environment. Receives name, flags and mode.

mdbx_env_close :: MdbxEnv -> IO Int Source #

Closes an environment.

Transaction

newtype MdbxTxn Source #

Transaction instance. Needed for all operations with data, even reading.

Constructors

MdbxTxn (Ptr MdbxTxn) 

Instances

Instances details
Storable MdbxTxn Source # 
Instance details

Defined in Mdbx.FFI

mdbx_txn_begin :: MdbxEnv -> Maybe MdbxTxn -> [MdbxTxnFlags] -> IO (Int, MdbxTxn) Source #

Begins a new transaction.

Arguments:

  • Environment.
  • Parent transaction, or Nothing.
  • Flags.

mdbx_txn_commit :: MdbxTxn -> IO Int Source #

Commits a transaction.

mdbx_txn_abort :: MdbxTxn -> IO Int Source #

Aborts a transaction.

mdbx_txn_env :: MdbxTxn -> IO MdbxEnv Source #

Gets the environment from a transaction.

Database

type MdbxDbi = CUInt Source #

Database instance. Represents a logical table in the database.

mdbx_dbi_open :: MdbxTxn -> Maybe String -> [MdbxDbFlags] -> IO (Int, MdbxDbi) Source #

Opens a database.

Arguments:

  • Transaction.
  • Name.
  • Flags.

mdbx_dbi_close :: MdbxEnv -> MdbxDbi -> IO Int Source #

Closes a database.

Data

data MdbxVal Source #

Binary blob representing a key or value in the database.

Constructors

MdbxVal 

Fields

Instances

Instances details
Eq MdbxVal Source # 
Instance details

Defined in Mdbx.FFI

Methods

(==) :: MdbxVal -> MdbxVal -> Bool #

(/=) :: MdbxVal -> MdbxVal -> Bool #

Show MdbxVal Source # 
Instance details

Defined in Mdbx.FFI

Storable MdbxVal Source # 
Instance details

Defined in Mdbx.FFI

emptyMdbxVal :: MdbxVal Source #

Sample empty value

CRUD

mdbx_put :: MdbxTxn -> MdbxDbi -> MdbxVal -> MdbxVal -> [MdbxPutFlags] -> IO Int Source #

Stores a key/value pair.

Arguments:

  • Transaction.
  • Database.
  • Key.
  • Value.

mdbx_get :: MdbxTxn -> MdbxDbi -> MdbxVal -> IO (Int, MdbxVal) Source #

Gets a value with the given key.

Arguments:

  • Transaction.
  • Database.
  • Key.

mdbx_del :: MdbxTxn -> MdbxDbi -> MdbxVal -> Maybe MdbxVal -> IO Int Source #

Gets a value with the given key.

Arguments:

  • Transaction.
  • Database.
  • Key.

Cursor

data MdbxCursorOp Source #

Flags for cursor operations.

newtype MdbxCursor Source #

Cursor instance. Used for efficient navigation in a database.

Constructors

MdbxCursor (Ptr MdbxCursor) 

Instances

Instances details
Storable MdbxCursor Source # 
Instance details

Defined in Mdbx.FFI

mdbx_cursor_open :: MdbxTxn -> MdbxDbi -> IO (Int, MdbxCursor) Source #

Opens a new cursor.

Arguments:

  • Transaction.
  • Database.

mdbx_cursor_close :: MdbxCursor -> IO () Source #

Closes a cursor.

mdbx_cursor_del :: MdbxCursor -> [MdbxPutFlags] -> IO Int Source #

Removes the current key/value pair.

mdbx_cursor_get :: MdbxCursor -> MdbxVal -> MdbxCursorOp -> IO (Int, MdbxVal, MdbxVal) Source #

Returns the current key/value pair.

mdbx_cursor_put :: MdbxCursor -> MdbxVal -> MdbxVal -> [MdbxPutFlags] -> IO Int Source #

Sets the value for the current key.

Arguments:

  • Cursor.
  • Key.
  • Value.
  • FLags.

mdbx_cursor_count :: MdbxCursor -> IO (Int, CSize) Source #

Returns the count of duplicates in the current key.

mdbx_strerror :: Int -> IO String Source #

Returns the description of a given error number.

mdbx_cmp :: MdbxTxn -> MdbxDbi -> MdbxVal -> MdbxVal -> IO Int Source #

Compares two values as a binary blob.

Error

data MdbxError Source #

Error codes for the different operations.

Conversion for types used in keys

mdbx_key_from_float :: Float -> Word32 Source #

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

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

mdbx_key_from_double :: Double -> Word64 Source #

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

mdbx_key_from_int32 :: Int32 -> Word32 Source #

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

mdbx_float_from_key :: Word32 -> Float Source #

Converts an unsigned Word to a Float value.

mdbx_double_from_key :: Word64 -> Double Source #

Converts an unsigned Word to a Double value.

mdbx_int32_from_key :: Word32 -> Int32 Source #

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

mdbx_int64_from_key :: Word64 -> Int64 Source #

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