Copyright | (c) 2021 Francisco Vallarino |
---|---|
License | BSD-3-Clause (see the LICENSE file) |
Maintainer | fjvallarino@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Types used by the library. Mainly re exports the types generated by c2hs in the FFI module, while it also adds some types used by the high level interface.
Synopsis
- data MdbxEnv
- data MdbxTxn
- type MdbxDbi = CUInt
- data MdbxCursor
- data MdbxVal = MdbxVal {}
- type MdbxEnvMode = CUInt
- data MdbxEnvFlags
- data MdbxTxnFlags
- data MdbxDbFlags
- data MdbxPutFlags
- data MdbxCursorOp
- data MdbxEnvGeometry = MdbxEnvGeometry {
- envSizeMin :: Int
- envSizeNow :: Int
- envSizeMax :: Int
- envGrowthStep :: Int
- envShrinkThreshold :: Int
- envPageSize :: Int
- class MdbxItem i where
- newtype NullByteString = NullByteString {}
- newtype NullText = NullText {
- unNullText :: Text
Re-exported from FFI
Environment object, needed for all the operations.
Transaction instance. Needed for all operations with data, even reading.
data MdbxCursor Source #
Cursor instance. Used for efficient navigation in a database.
Instances
Storable MdbxCursor Source # | |
Defined in Mdbx.FFI sizeOf :: MdbxCursor -> Int # alignment :: MdbxCursor -> Int # peekElemOff :: Ptr MdbxCursor -> Int -> IO MdbxCursor # pokeElemOff :: Ptr MdbxCursor -> Int -> MdbxCursor -> IO () # peekByteOff :: Ptr b -> Int -> IO MdbxCursor # pokeByteOff :: Ptr b -> Int -> MdbxCursor -> IO () # peek :: Ptr MdbxCursor -> IO MdbxCursor # poke :: Ptr MdbxCursor -> MdbxCursor -> IO () # |
Binary blob representing a key or value in the database.
Instances
Eq MdbxVal Source # | |
Show MdbxVal Source # | |
Storable MdbxVal Source # | |
type MdbxEnvMode = CUInt Source #
UNIX permissions to set on created files. Zero value means to open existing, but do not create.
data MdbxEnvFlags Source #
Flags for opening an environment.
Instances
data MdbxTxnFlags Source #
Flags for a transaction.
Instances
data MdbxDbFlags Source #
Flags for a database.
MdbxDbDefaults | |
MdbxReversekey | |
MdbxDupsort | |
MdbxIntegerkey | |
MdbxDupfixed | |
MdbxIntegerdup | |
MdbxReversedup | |
MdbxCreate | |
MdbxDbAccede |
Instances
data MdbxPutFlags Source #
Flags for all data related operations.
MdbxUpsert | |
MdbxNooverwrite | |
MdbxNodupdata | |
MdbxCurrent | |
MdbxAlldups | |
MdbxReserve | |
MdbxAppend | |
MdbxAppenddup | |
MdbxMultiple |
Instances
data MdbxCursorOp Source #
Flags for cursor operations.
Instances
High level interface
data MdbxEnvGeometry Source #
Geometry of the database. The most important parameter is the maximum size, that defaults to 1024Mb. All other values default to -1, meaning the current value will be kept.
MdbxEnvGeometry | |
|
Instances
Eq MdbxEnvGeometry Source # | |
Defined in Mdbx.Types (==) :: MdbxEnvGeometry -> MdbxEnvGeometry -> Bool # (/=) :: MdbxEnvGeometry -> MdbxEnvGeometry -> Bool # | |
Show MdbxEnvGeometry Source # | |
Defined in Mdbx.Types showsPrec :: Int -> MdbxEnvGeometry -> ShowS # show :: MdbxEnvGeometry -> String # showList :: [MdbxEnvGeometry] -> ShowS # | |
Default MdbxEnvGeometry Source # | |
Defined in Mdbx.Types def :: MdbxEnvGeometry # |
class MdbxItem i where Source #
Converts an instance to/from the representation needed by libmdbx. This type is used for both keys and values. The fields on the type must be strict, otherwise unexpected crashes due to lazy IO delaying low level memory access may happen.
Only ByteString
, Text
instances are provided, since they are commonly used
as the key when storing/retrieving a value.
For your own types, in general, you will want to use a serialization library such as binary, and apply the newtype deriving via trick.
MdbxItemBinary
is provided to simplify using Binary
instances as keys or values with libmdbx, while MdbxItemStore
provides the same functionality for Store
instances. With those
helpers, creating custom types compatible with libmdbx is easy:
data User = User { _username :: !Text, _password :: !Text } deriving (Eq, Show, Generic, Store) deriving via (MdbxItemBinary User) instance MdbxItem User
Note 1: if you plan on using a custom type as the key, be careful if it
contains Text
or ByteString
instances, since these types have a length field
which is serialized before the data. This causes issues when using libmdbx,
since it depends on key ordering and the length field will make shorter
instances lower than longer ones, even if the content indicates the opposite.
You can use the provided NullByteString
or NullText
types if your data type
is an instance of Binary
or Store
. Otherwise, it is
simpler to use Text
or ByteString
as the key.
Note 2: If your key type contains Word16 or longer fields, you should make
it an instance of Binary
, not Store
, since Store uses
platform dependent endianess and this affects libmdbx's comparison functions.
Given Binary uses network order (big endian) for encoding, the comparison
functions will work as expected. Failing to do this may cause unexpected issues
when retrieving data, in particular when using cursors.
Note 3: The behavior when using signed integers or floating point numbers as
part of the key is undefined. To be able to use these types in the key, you
should store them as a Word of the appropriate size and convert them with the
conversion functions included in API
.
fromMdbxVal :: MdbxVal -> IO i Source #
Converts a block of memory provided by libmdbx to a user data type. There are no guarantees provided by the library that the block of memory matches the expected type; a crash can happen when trying to deserialize an incorrect type.
toMdbxVal :: i -> (MdbxVal -> IO b) -> IO b Source #
Converts a user data type to a block of memory.
Instances
MdbxItem ByteString Source # | |
Defined in Mdbx.Types fromMdbxVal :: MdbxVal -> IO ByteString Source # toMdbxVal :: ByteString -> (MdbxVal -> IO b) -> IO b Source # | |
MdbxItem Text Source # | |
MdbxItem NullText Source # | |
MdbxItem NullByteString Source # | |
Defined in Mdbx.Binary fromMdbxVal :: MdbxVal -> IO NullByteString Source # toMdbxVal :: NullByteString -> (MdbxVal -> IO b) -> IO b Source # | |
Store a => MdbxItem (MdbxItemStore a) Source # | |
Defined in Mdbx.Store fromMdbxVal :: MdbxVal -> IO (MdbxItemStore a) Source # toMdbxVal :: MdbxItemStore a -> (MdbxVal -> IO b) -> IO b Source # | |
Binary a => MdbxItem (MdbxItemBinary a) Source # | |
Defined in Mdbx.Binary fromMdbxVal :: MdbxVal -> IO (MdbxItemBinary a) Source # toMdbxVal :: MdbxItemBinary a -> (MdbxVal -> IO b) -> IO b Source # |
Helper types
newtype NullByteString Source #
Newtype wrapping a ByteString
that provides a Binary
instance
using NULL terminated C strings, which allows for using them as part of a custom
data type representing a key.
This is not possible with regular ByteString
and Text
instances since their
Binary
instances are serialized with the size field first. Given
that libmdbx compares keys as an unstructured sequence of bytes, this can cause
issues since longer strings are considered greater than shorter ones, even if
their content indicates otherwise.
Instances
Newtype wrapping a Text
that provides a Binary
instance using
NULL terminated C strings, which allows for using them as part of a custom data
type representing a key.
Check NullByteString
for the rationale.