Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module is a thin wrapper above lmdb.h.
Provisions for performance, convenience, or safety:
- Errors are shifted to
LMDB_Error
Haskell exceptions - flag fields and enums are represented with Haskell types
- MDB_env includes its own write mutex for Haskell's threads
- MDB_RESERVE operations use their own functions
- Databases types are divided for user-defined comparisons
- Boolean-option functions are divided into two functions
- MDB_NOTLS is added implicitly, and may not be removed
- unix mode is set to 0660 (user+group read-write)
Some functions come in two forms based on safe
vs. unsafe
FFI bindings. Unsafe FFI bindings are unsuitable for databases
with user-defined comparison operations. (Though, if you plan
to load a database with MDB_APPEND or MDB_APPENDDUP, you can
use an unsafe dbi for just that portion.)
Despite these provisions, developers must still be cautious:
- MDB_val objects are invalid outside their transaction.
- Don't use write operations on a read-only transaction.
- Use 'bound threads' for write transactions.
A slightly higher level API is planned, mostly to provide safer and more convenient access compared to raw MDB_val objects.
Features not implemented:
- functions directly using file handles
- user-defined relocation functions
- alloc-avoiding renew and reset operations
- MDB_MULTIPLE is not currently supported (todo)
- data LMDB_Version = LMDB_Version {}
- lmdb_version :: LMDB_Version
- lmdb_dyn_version :: IO LMDB_Version
- data LMDB_Error = LMDB_Error {}
- data MDB_ErrCode
- data MDB_env
- data MDB_dbi
- data MDB_dbi'
- data MDB_txn
- data MDB_txnid
- data MDB_cursor
- data MDB_cursor'
- data MDB_val
- mv_size :: MDB_val -> CSize
- mv_data :: MDB_val -> Ptr Word8
- data MDB_stat
- ms_psize :: MDB_stat -> CUInt
- ms_depth :: MDB_stat -> CUInt
- ms_branch_pages :: MDB_stat -> CSize
- ms_leaf_pages :: MDB_stat -> CSize
- ms_overflow_pages :: MDB_stat -> CSize
- ms_entries :: MDB_stat -> CSize
- data MDB_envinfo
- me_mapaddr :: MDB_envinfo -> Ptr ()
- me_mapsize :: MDB_envinfo -> CSize
- me_last_pgno :: MDB_envinfo -> CSize
- me_last_txnid :: MDB_envinfo -> MDB_txnid
- me_maxreaders :: MDB_envinfo -> CUInt
- me_numreaders :: MDB_envinfo -> CUInt
- type MDB_cmp_func = Ptr MDB_val -> Ptr MDB_val -> IO CInt
- wrapCmpFn :: MDB_cmp_func -> IO (FunPtr MDB_cmp_func)
- data MDB_EnvFlag
- data MDB_DbFlag
- data MDB_cursor_op
- data MDB_WriteFlag
- data MDB_WriteFlags
- compileWriteFlags :: [MDB_WriteFlag] -> MDB_WriteFlags
- mdb_env_create :: IO MDB_env
- mdb_env_open :: MDB_env -> FilePath -> [MDB_EnvFlag] -> IO ()
- mdb_env_copy :: MDB_env -> FilePath -> IO ()
- mdb_env_stat :: MDB_env -> IO MDB_stat
- mdb_env_info :: MDB_env -> IO MDB_envinfo
- mdb_env_sync :: MDB_env -> IO ()
- mdb_env_sync_flush :: MDB_env -> IO ()
- mdb_env_close :: MDB_env -> IO ()
- mdb_env_set_flags :: MDB_env -> [MDB_EnvFlag] -> IO ()
- mdb_env_unset_flags :: MDB_env -> [MDB_EnvFlag] -> IO ()
- mdb_env_get_flags :: MDB_env -> IO [MDB_EnvFlag]
- mdb_env_get_path :: MDB_env -> IO FilePath
- mdb_env_set_mapsize :: MDB_env -> Int -> IO ()
- mdb_env_set_maxreaders :: MDB_env -> Int -> IO ()
- mdb_env_get_maxreaders :: MDB_env -> IO Int
- mdb_env_set_maxdbs :: MDB_env -> Int -> IO ()
- mdb_env_get_maxkeysize :: MDB_env -> IO Int
- mdb_txn_begin :: MDB_env -> Maybe MDB_txn -> Bool -> IO MDB_txn
- mdb_txn_env :: MDB_txn -> MDB_env
- mdb_txn_commit :: MDB_txn -> IO ()
- mdb_txn_abort :: MDB_txn -> IO ()
- mdb_dbi_open :: MDB_txn -> String -> [MDB_DbFlag] -> IO MDB_dbi
- mdb_stat :: MDB_txn -> MDB_dbi -> IO MDB_stat
- mdb_dbi_flags :: MDB_txn -> MDB_dbi -> IO [MDB_DbFlag]
- mdb_dbi_close :: MDB_env -> MDB_dbi -> IO ()
- mdb_drop :: MDB_txn -> MDB_dbi -> IO ()
- mdb_clear :: MDB_txn -> MDB_dbi -> IO ()
- mdb_set_compare :: MDB_txn -> MDB_dbi -> FunPtr MDB_cmp_func -> IO ()
- mdb_set_dupsort :: MDB_txn -> MDB_dbi -> FunPtr MDB_cmp_func -> IO ()
- mdb_dbi_open' :: MDB_txn -> String -> [MDB_DbFlag] -> IO MDB_dbi'
- mdb_stat' :: MDB_txn -> MDB_dbi' -> IO MDB_stat
- mdb_dbi_flags' :: MDB_txn -> MDB_dbi' -> IO [MDB_DbFlag]
- mdb_dbi_close' :: MDB_env -> MDB_dbi' -> IO ()
- mdb_drop' :: MDB_txn -> MDB_dbi' -> IO ()
- mdb_clear' :: MDB_txn -> MDB_dbi' -> IO ()
- mdb_get :: MDB_txn -> MDB_dbi -> MDB_val -> IO (Maybe MDB_val)
- mdb_put :: MDB_WriteFlags -> MDB_txn -> MDB_dbi -> MDB_val -> MDB_val -> IO Bool
- mdb_del :: MDB_txn -> MDB_dbi -> MDB_val -> Maybe MDB_val -> IO Bool
- mdb_reserve :: MDB_WriteFlags -> MDB_txn -> MDB_dbi -> MDB_val -> Int -> IO MDB_val
- mdb_get' :: MDB_txn -> MDB_dbi' -> MDB_val -> IO (Maybe MDB_val)
- mdb_put' :: MDB_WriteFlags -> MDB_txn -> MDB_dbi' -> MDB_val -> MDB_val -> IO Bool
- mdb_del' :: MDB_txn -> MDB_dbi' -> MDB_val -> Maybe MDB_val -> IO Bool
- mdb_reserve' :: MDB_WriteFlags -> MDB_txn -> MDB_dbi' -> MDB_val -> Int -> IO MDB_val
- mdb_cmp :: MDB_txn -> MDB_dbi -> MDB_val -> MDB_val -> IO Ordering
- mdb_dcmp :: MDB_txn -> MDB_dbi -> MDB_val -> MDB_val -> IO Ordering
- mdb_cmp' :: MDB_txn -> MDB_dbi' -> MDB_val -> MDB_val -> IO Ordering
- mdb_dcmp' :: MDB_txn -> MDB_dbi' -> MDB_val -> MDB_val -> IO Ordering
- mdb_cursor_open :: MDB_txn -> MDB_dbi -> IO MDB_cursor
- mdb_cursor_get :: MDB_cursor_op -> MDB_cursor -> Ptr MDB_val -> Ptr MDB_val -> IO Bool
- mdb_cursor_put :: MDB_WriteFlags -> MDB_cursor -> MDB_val -> MDB_val -> IO Bool
- mdb_cursor_del :: MDB_WriteFlags -> MDB_cursor -> IO ()
- mdb_cursor_close :: MDB_cursor -> IO ()
- mdb_cursor_txn :: MDB_cursor -> MDB_txn
- mdb_cursor_dbi :: MDB_cursor -> MDB_dbi
- mdb_cursor_count :: MDB_cursor -> IO Int
- mdb_cursor_open' :: MDB_txn -> MDB_dbi' -> IO MDB_cursor'
- mdb_cursor_get' :: MDB_cursor_op -> MDB_cursor' -> Ptr MDB_val -> Ptr MDB_val -> IO Bool
- mdb_cursor_put' :: MDB_WriteFlags -> MDB_cursor' -> MDB_val -> MDB_val -> IO Bool
- mdb_cursor_del' :: MDB_WriteFlags -> MDB_cursor' -> IO ()
- mdb_cursor_close' :: MDB_cursor' -> IO ()
- mdb_cursor_txn' :: MDB_cursor' -> MDB_txn
- mdb_cursor_dbi' :: MDB_cursor' -> MDB_dbi'
- mdb_cursor_count' :: MDB_cursor' -> IO Int
- mdb_reader_list :: MDB_env -> IO [String]
- mdb_reader_check :: MDB_env -> IO Int
Documentation
data LMDB_Version Source
Version information for LMDB. Two potentially different versions can be obtained: lmdb_version returns the version at the time of binding (via C preprocessor macros) and lmdb_dyn_version returns a version for the bound library.
These bindings to Haskell will refuse to open the database when the dynamic version of LMDB is different in the major or minor fields.
lmdb_version :: LMDB_Version Source
Version of LMDB when the Haskell-LMDB binding was compiled.
lmdb_dyn_version :: IO LMDB_Version Source
Version of LMDB linked to the current Haskell process.
data LMDB_Error Source
LMDB_Error is the exception type thrown in case a function from the LMDB API does not return successfully. Clients should be prepared to catch exceptions from any LMDB operation.
data MDB_ErrCode Source
Error codes from MDB. Note, however, that this API for MDB will mostly use exceptions for any non-successful return codes. This is mostly included because I feel the binding would be incomplete otherwise.
(The MDB_SUCCESS return value is excluded.)
Opaque structure for LMDB environment.
The environment additionally contains an MVar to enforce at most one lightweight Haskell thread is writing at a time. This is necessary so long as LMDB uses a long-lived mutex for writes, as in v0.9.10.
Handle for a database in the environment.
This variation is associated with unsafe
FFI calls, with reduced
overhead but no user-defined comparisons. I expect most code using
LMDB could use this variation.
data MDB_cursor Source
Opaque structure for LMDB cursor.
data MDB_cursor' Source
Opaque structure for a cursor on an MDB_dbi' object. Cursors
in this case also use the unsafe
FFI calls.
A value stored in the database. Be cautious; committing the
transaction that obtained a value should also invalidate it;
avoid capturing MDB_val in a lazy value. A safe
interface
similar to STRef will be provided in another module.
ms_branch_pages :: MDB_stat -> CSize Source
ms_leaf_pages :: MDB_stat -> CSize Source
ms_overflow_pages :: MDB_stat -> CSize Source
ms_entries :: MDB_stat -> CSize Source
me_mapaddr :: MDB_envinfo -> Ptr () Source
me_mapsize :: MDB_envinfo -> CSize Source
me_last_pgno :: MDB_envinfo -> CSize Source
me_maxreaders :: MDB_envinfo -> CUInt Source
me_numreaders :: MDB_envinfo -> CUInt Source
type MDB_cmp_func = Ptr MDB_val -> Ptr MDB_val -> IO CInt Source
User-defined comparison functions for keys.
wrapCmpFn :: MDB_cmp_func -> IO (FunPtr MDB_cmp_func) Source
data MDB_EnvFlag Source
Environment flags from lmdb.h
Note: MDB_NOTLS is implicit and enforced for this binding.
data MDB_DbFlag Source
data MDB_cursor_op Source
data MDB_WriteFlag Source
data MDB_WriteFlags Source
compiled write flags, corresponding to a [WriteFlag] list. Used because writes are frequent enough that we want to avoid building from a list on a per-write basis.
compileWriteFlags :: [MDB_WriteFlag] -> MDB_WriteFlags Source
compile a list of write flags.
Environment Operations
mdb_env_create :: IO MDB_env Source
Allocate an environment object. This doesn't open the environment.
After creation, but before opening, please use:
mdb_env_set_mapsize mdb_env_set_maxreaders mdb_env_set_maxdbs
Then, just after opening, you should create all the databases your application will use.
In addition to normal LMDB errors, this operation may throw an MDB_VERSION_MISMATCH if the Haskell LMDB bindings doesn't match the dynamic version. If this happens, you'll need to rebuild the lmdb Haskell package, and ensure your lmdb-dev libraries are up to date.
mdb_env_open :: MDB_env -> FilePath -> [MDB_EnvFlag] -> IO () Source
open or build a database in the filesystem. The named directory
must already exist and be writeable. Before opening, be sure to
at least apply mdb_env_set_mapsize
.
After opening the environment, you should open the databases:
Create the environment. Open a transaction. Open all DBI handles the app will need. Commit the transaction. Use those DBI handles in subsequent transactions
mdb_env_copy :: MDB_env -> FilePath -> IO () Source
Copy the environment to an empty (but existing) directory.
Note: the LMDB copy operation temporarily grabs the writer mutex. Unfortunately, this greatly complicates the binding to Haskell. This interface, mdb_env_copy, conservatively blocks all writers in the same process for the entire duration of copy.
Recommendation: Don't use this function in the same process with
writers. Consider use of the mdb_copy
command line utility if
you need hot copies.
mdb_env_stat :: MDB_env -> IO MDB_stat Source
obtain statistics for environment
mdb_env_info :: MDB_env -> IO MDB_envinfo Source
obtain ad-hoc information about the environment.
mdb_env_sync :: MDB_env -> IO () Source
Initiate synchronization of environment with disk. However, if the MDB_NOSYNC or MDB_MAPASYNC flags are active, this won't wait for the operation to finish. Cf. mdb_env_sync_flush.
mdb_env_sync_flush :: MDB_env -> IO () Source
Force buffered writes to disk before returning.
mdb_env_close :: MDB_env -> IO () Source
Close the environment. The MDB_env object should not be used by any operations during or after closing.
mdb_env_set_flags :: MDB_env -> [MDB_EnvFlag] -> IO () Source
Set flags for the environment.
mdb_env_unset_flags :: MDB_env -> [MDB_EnvFlag] -> IO () Source
Unset flags for the environment.
mdb_env_get_flags :: MDB_env -> IO [MDB_EnvFlag] Source
View the current set of flags for the environment.
mdb_env_get_path :: MDB_env -> IO FilePath Source
Obtain filesystem path for this environment.
mdb_env_set_mapsize :: MDB_env -> Int -> IO () Source
Set the memory map size, in bytes, for this environment. This determines the maximum size for the environment and databases, but typically only a small fraction of the database is in memory at any given moment.
It is not a problem to set this to a very large number, hundreds of gigabytes or even terabytes, assuming a sufficiently large address space. It should be set to a multiple of page size.
The default map size is 1MB, intentionally set low to force developers to select something larger.
mdb_env_set_maxreaders :: MDB_env -> Int -> IO () Source
Set the maximum number of concurrent readers.
mdb_env_get_maxreaders :: MDB_env -> IO Int Source
Get the maximum number of concurrent readers.
mdb_env_set_maxdbs :: MDB_env -> Int -> IO () Source
Set the maximum number of named databases. LMDB is designed to support a small handful of databases.
mdb_env_get_maxkeysize :: MDB_env -> IO Int Source
Key sizes in LMDB are determined by a compile-time constant, defaulting to 511 bytes. This function returns the maximum.
Transactions
mdb_txn_begin :: MDB_env -> Maybe MDB_txn -> Bool -> IO MDB_txn Source
Begin a new transaction, possibly read-only, with a possible parent.
mdb_txn_begin env parent bReadOnly
A read-write transaction should be tethered to a specific Haskell thread,
which MUST be a bound
thread (via forkOS or runInBoundThread). A read
only transaction is not so constrained.
The hierarchical transactions are useful for read-write transactions. They allow trying something out then aborting if it doesn't work. But only one child should be active at a time, all in the same OS thread.
An attempt to grab a writer transaction may block, potentially for a very long time. It's the responsibility of the software architects to ensure there is no need for long-running write operations.
mdb_txn_env :: MDB_txn -> MDB_env Source
Access environment for a transaction.
mdb_txn_commit :: MDB_txn -> IO () Source
Commit a transaction. Don't use the transaction after this.
mdb_txn_abort :: MDB_txn -> IO () Source
Abort a transaction. Don't use the transaction after this.
Databases
mdb_dbi_open :: MDB_txn -> String -> [MDB_DbFlag] -> IO MDB_dbi Source
Open a database that supports user-defined comparisons, but has slightly more FFI overhead for reads and writes.
mdb_dbi_flags :: MDB_txn -> MDB_dbi -> IO [MDB_DbFlag] Source
review flags from database
mdb_dbi_close :: MDB_env -> MDB_dbi -> IO () Source
close the database handle.
Note: the normal use-case for LMDB is to open all the database handles up front, then hold onto them until the application is closed or crashed. In that case, you don't need to bother with closing database handles.
mdb_drop :: MDB_txn -> MDB_dbi -> IO () Source
remove the database and close the handle; don't use MDB_dbi after this
mdb_set_compare :: MDB_txn -> MDB_dbi -> FunPtr MDB_cmp_func -> IO () Source
Set a user-defined key comparison function for a database.
mdb_set_dupsort :: MDB_txn -> MDB_dbi -> FunPtr MDB_cmp_func -> IO () Source
Set a user-defined data comparison operator for MDB_DUPSORT databases.
mdb_dbi_open' :: MDB_txn -> String -> [MDB_DbFlag] -> IO MDB_dbi' Source
mdb_dbi_flags' :: MDB_txn -> MDB_dbi' -> IO [MDB_DbFlag] Source
mdb_dbi_close' :: MDB_env -> MDB_dbi' -> IO () Source
mdb_clear' :: MDB_txn -> MDB_dbi' -> IO () Source
Basic Key-Value Access
mdb_get :: MDB_txn -> MDB_dbi -> MDB_val -> IO (Maybe MDB_val) Source
Access a value by key. Returns Nothing if the key is not found.
mdb_put :: MDB_WriteFlags -> MDB_txn -> MDB_dbi -> MDB_val -> MDB_val -> IO Bool Source
Add a (key,value) pair to the database.
Returns False on MDB_KEYEXIST, and True on MDB_SUCCESS. Any other return value results in an exception.
mdb_del :: MDB_txn -> MDB_dbi -> MDB_val -> Maybe MDB_val -> IO Bool Source
Delete a given key, or a specific (key,value) pair in case of MDB_DUPSORT. This function will return False on a MDB_NOTFOUND result.
Note: Ideally, LMDB would match the value even without MDB_DUPSORT. But it doesn't. Under the hood, the data is replaced by a null ptr if MDB_DUPSORT is not enabled (v0.9.10).
mdb_reserve :: MDB_WriteFlags -> MDB_txn -> MDB_dbi -> MDB_val -> Int -> IO MDB_val Source
Allocate space for data under a given key. This space must be filled before the write transaction commits. The idea here is to avoid an extra allocation.
mdb_reserve flags txn dbi key byteCount
Note: not safe to use with MDB_DUPSORT. Note: MDB_KEYEXIST will result in an exception here.
mdb_reserve' :: MDB_WriteFlags -> MDB_txn -> MDB_dbi' -> MDB_val -> Int -> IO MDB_val Source
Database key and value Comparisons
mdb_cmp :: MDB_txn -> MDB_dbi -> MDB_val -> MDB_val -> IO Ordering Source
compare two values as keys in a database
mdb_dcmp :: MDB_txn -> MDB_dbi -> MDB_val -> MDB_val -> IO Ordering Source
compare two values as data in an MDB_DUPSORT database
Cursors
mdb_cursor_open :: MDB_txn -> MDB_dbi -> IO MDB_cursor Source
open a cursor for the database.
mdb_cursor_get :: MDB_cursor_op -> MDB_cursor -> Ptr MDB_val -> Ptr MDB_val -> IO Bool Source
Low-level mdb_cursor_get operation, with direct control of how pointers to values are allocated, whether an argument is a nullPtr, and so on.
In this case, False is returned for MDB_NOTFOUND (in which case the cursor should not be moved), and True is returned for MDB_SUCCESS. Depending on the MDB_cursor_op, additional values may be returned via the pointers.
mdb_cursor_put :: MDB_WriteFlags -> MDB_cursor -> MDB_val -> MDB_val -> IO Bool Source
Low-level mdb_cursor_put
operation.
As with mdb_put, this returns True on MDB_SUCCESS and False for MDB_KEYEXIST, and otherwise throws an exception.
mdb_cursor_del :: MDB_WriteFlags -> MDB_cursor -> IO () Source
Delete the value at the cursor.
mdb_cursor_close :: MDB_cursor -> IO () Source
Close a cursor. don't use after this. In general, cursors should be closed before their associated transaction is commited or aborted.
mdb_cursor_txn :: MDB_cursor -> MDB_txn Source
Access transaction associated with a cursor.
mdb_cursor_dbi :: MDB_cursor -> MDB_dbi Source
Access the database associated with a cursor.
mdb_cursor_count :: MDB_cursor -> IO Int Source
count number of duplicate data items at cursor's current location.
mdb_cursor_open' :: MDB_txn -> MDB_dbi' -> IO MDB_cursor' Source
mdb_cursor_get' :: MDB_cursor_op -> MDB_cursor' -> Ptr MDB_val -> Ptr MDB_val -> IO Bool Source
mdb_cursor_put' :: MDB_WriteFlags -> MDB_cursor' -> MDB_val -> MDB_val -> IO Bool Source
mdb_cursor_del' :: MDB_WriteFlags -> MDB_cursor' -> IO () Source
mdb_cursor_close' :: MDB_cursor' -> IO () Source
mdb_cursor_count' :: MDB_cursor' -> IO Int Source
Misc
mdb_reader_list :: MDB_env -> IO [String] Source
Dump entries from reader lock table.
mdb_reader_check :: MDB_env -> IO Int Source
Check for stale readers, and return number of stale readers cleared.