lmdb-simple-0.3.1.0: Simple API for LMDB

Copyright© 2017 Robert Leslie
LicenseBSD3
Maintainerrob@mars.org
Stabilityexperimental
Safe HaskellTrustworthy
LanguageHaskell2010

Database.LMDB.Simple

Contents

Description

This module provides a simple Haskell API for the Lightning Memory-mapped Database (LMDB).

Example usage:

module Main where

import Database.LMDB.Simple
import Control.Monad (forM_)

main = do
  env <- openEnvironment "myenv" defaultLimits
  db <- readOnlyTransaction env $ getDatabase Nothing :: IO (Database String Int)

  transaction env $
    forM_ [("one",1),("two",2),("three",3)] $ \(k,v) -> put db k (Just v)

  print =<< readOnlyTransaction env (get db "two")   -- Just 2
  print =<< readOnlyTransaction env (get db "nine")  -- Nothing

These additional APIs are available:

Synopsis

Environments

data Environment mode Source #

An LMDB environment is a directory or file on disk that contains one or more databases, and has an associated (reader) lock table.

data Limits Source #

LMDB environments have various limits on the size and number of databases and concurrent readers.

Constructors

Limits 

Fields

  • mapSize :: Int

    memory map size, in bytes (also the maximum size of all databases)

  • maxDatabases :: Int

    maximum number of named databases

  • maxReaders :: Int

    maximum number of concurrent ReadOnly transactions (also the number of slots in the lock table)

defaultLimits :: Limits Source #

The default limits are 1 MiB map size, 0 named databases, and 126 concurrent readers. These can be adjusted freely, and in particular the mapSize may be set very large (limited only by available address space). However, LMDB is not optimized for a large number of named databases so maxDatabases should be kept to a minimum.

The default mapSize is intentionally small, and should be changed to something appropriate for your application. It ought to be a multiple of the OS page size, and should be chosen as large as possible to accommodate future growth of the database(s). Once set for an environment, this limit cannot be reduced to a value smaller than the space already consumed by the environment, however it can later be increased.

If you are going to use any named databases then you will need to change maxDatabases to the number of named databases you plan to use. However, you do not need to change this field if you are only going to use the single main (unnamed) database.

openEnvironment :: Mode mode => FilePath -> Limits -> IO (Environment mode) Source #

Open an LMDB environment in either ReadWrite or ReadOnly mode. The FilePath argument may be either a directory or a regular file, but it must already exist. If a regular file, an additional file with "-lock" appended to the name is used for the reader lock table.

Note that an environment must have been opened in ReadWrite mode at least once before it can be opened in ReadOnly mode.

An environment opened in ReadOnly mode may still modify the reader lock table (except when the filesystem is read-only, in which case no locks are used).

openReadWriteEnvironment :: FilePath -> Limits -> IO (Environment ReadWrite) Source #

Convenience function for opening an LMDB environment in ReadWrite mode; see openEnvironment

openReadOnlyEnvironment :: FilePath -> Limits -> IO (Environment ReadOnly) Source #

Convenience function for opening an LMDB environment in ReadOnly mode; see openEnvironment

clearStaleReaders :: Environment mode -> IO Int Source #

Check for stale entries in the reader lock table, and return the number of entries cleared.

Transactions

data Transaction mode a Source #

An LMDB transaction is an atomic unit for reading and/or changing one or more LMDB databases within an environment, during which the transaction has a consistent view of the database(s) and is unaffected by any other transaction. The effects of a transaction can either be committed to the LMDB environment atomically, or they can be rolled back with no observable effect on the environment if the transaction is aborted.

Transactions may be ReadWrite or ReadOnly, however LMDB enforces a strict single-writer policy so only one top-level ReadWrite transaction may be active at any time.

This API models transactions using a Transaction monad. This monad has a MonadIO instance so it is possible to perform arbitrary I/O within a transaction using liftIO. However, such IO actions are not atomic and cannot be rolled back if the transaction is aborted, so use with care.

Instances

Monad (Transaction mode) Source # 

Methods

(>>=) :: Transaction mode a -> (a -> Transaction mode b) -> Transaction mode b #

(>>) :: Transaction mode a -> Transaction mode b -> Transaction mode b #

return :: a -> Transaction mode a #

fail :: String -> Transaction mode a #

Functor (Transaction mode) Source # 

Methods

fmap :: (a -> b) -> Transaction mode a -> Transaction mode b #

(<$) :: a -> Transaction mode b -> Transaction mode a #

Applicative (Transaction mode) Source # 

Methods

pure :: a -> Transaction mode a #

(<*>) :: Transaction mode (a -> b) -> Transaction mode a -> Transaction mode b #

(*>) :: Transaction mode a -> Transaction mode b -> Transaction mode b #

(<*) :: Transaction mode a -> Transaction mode b -> Transaction mode a #

MonadIO (Transaction mode) Source # 

Methods

liftIO :: IO a -> Transaction mode a #

transaction :: (Mode tmode, SubMode emode tmode) => Environment emode -> Transaction tmode a -> IO a Source #

Perform a top-level transaction in either ReadWrite or ReadOnly mode. A transaction may only be ReadWrite if the environment is also ReadWrite (enforced by the SubMode constraint).

Once completed, the transaction will be committed and the result returned. An exception will cause the transaction to be implicitly aborted.

Note that there may be several concurrent ReadOnly transactions (limited only by the maxReaders field of the Limits argument given to openEnvironment), but there is at most one active ReadWrite transaction, which is forced to run in a bound thread, and is protected by an internal mutex.

In general, long-lived transactions should be avoided. ReadOnly transactions prevent reuse of database pages freed by newer ReadWrite transactions, and thus the database can grow quickly. ReadWrite transactions prevent other ReadWrite transactions, since writes are serialized.

readWriteTransaction :: Environment ReadWrite -> Transaction ReadWrite a -> IO a Source #

Convenience function for performing a top-level ReadWrite transaction; see transaction

readOnlyTransaction :: Environment mode -> Transaction ReadOnly a -> IO a Source #

Convenience function for performing a top-level ReadOnly transaction; see transaction

nestTransaction :: Transaction ReadWrite a -> Transaction ReadWrite (Maybe a) Source #

Nest a transaction within the current ReadWrite transaction. Transactions may be nested to any level.

If the nested transaction is aborted, Nothing is returned. Otherwise, the nested transaction is committed and the result is returned in a Just value. (The overall effect of a nested transaction depends on whether the parent transaction is ultimately committed.)

An exception will cause the nested transaction to be implicitly aborted.

abort :: Transaction mode a Source #

Explicitly abort the current transaction, nullifying its effects on the LMDB environment. No further actions will be performed within the current transaction.

In a nested transaction, this causes the child transaction to return Nothing to its parent. In a top-level transaction, this throws an AbortedTransaction exception, which can be caught.

Databases

data Database k v Source #

A database maps arbitrary keys to values. This API uses the Serialise class to encode and decode keys and values for LMDB to store on disk. For details on creating your own instances of this class, see Codec.Serialise.Tutorial.

getDatabase :: Mode mode => Maybe String -> Transaction mode (Database k v) Source #

Retrieve a database handle from the LMDB environment. The database may be specified by name, or Nothing can be used to specify the main (unnamed) database for the environment. If a named database is specified, it must already exist, or it will be created if the transaction is ReadWrite.

There are a limited number of named databases you may use in an environment, set by the maxDatabases field of the Limits argument given to openEnvironment. By default (defaultLimits) this number is zero, so you must specify another limit in order to use any named databases.

You should not use both named and unnamed databases in the same environment, because the unnamed database is used internally to store entries for each named database.

You can (and should) retain the database handle returned by this action for use in future transactions.

get :: (Serialise k, Serialise v) => Database k v -> k -> Transaction mode (Maybe v) Source #

Lookup a key in a database and return the corresponding value, or return Nothing if the key does not exist in the database.

put :: (Serialise k, Serialise v) => Database k v -> k -> Maybe v -> Transaction ReadWrite () Source #

Insert the given key/value pair into a database, or delete the key from the database if Nothing is given for the value.

clear :: Database k v -> Transaction ReadWrite () Source #

Delete all key/value pairs from a database, leaving the database empty.

Access modes

class Mode a Source #

Minimal complete definition

isReadOnlyMode

type family SubMode a b :: Constraint where ... Source #

Equations

SubMode a ReadWrite = a ~ ReadWrite 
SubMode a ReadOnly = ()