lmdb-simple-0.3.1.0: Simple API for LMDB

Safe HaskellTrustworthy
LanguageHaskell2010

Database.LMDB.Simple.View

Contents

Description

This module provides a read-only View that is a snapshot of an LMDB database at a single point in time. Because the view is unchanging, it can be used within pure code. Behind the scenes, data is accessed from the underlying LMDB memory map.

Each View internally keeps open a read-only transaction in the LMDB environment (consuming a slot in the lock table), so their use should be minimized and generally short-lived. The transaction should be closed automatically when the View is garbage collected, but the timing is not guaranteed.

Synopsis

Creating

data View k v Source #

A View behaves much like a Map, except in the way it is created. A View k v maps keys k to values v.

newView :: Database k v -> IO (View k v) Source #

Create and return a read-only View for the given LMDB database. Internally, a read-only transaction is opened and kept alive until the View is garbage collected.

Operators

(!) :: (Serialise k, Serialise v) => View k v -> k -> v infixl 9 Source #

Find the value at a key. Calls error when the element can not be found.

(!?) :: (Serialise k, Serialise v) => View k v -> k -> Maybe v infixl 9 Source #

Find the value at a key. Returns Nothing when the element can not be found.

Query

null :: View k v -> Bool Source #

Is the view empty?

size :: View k v -> Int Source #

The number of elements in the view.

member :: Serialise k => k -> View k v -> Bool Source #

Is the key a member of the view? See also notMember.

notMember :: Serialise k => k -> View k v -> Bool Source #

Is the key not a member of the view? See also member.

lookup :: (Serialise k, Serialise v) => k -> View k v -> Maybe v Source #

Lookup the value at a key in the view.

The function will return the corresponding value as (Just value), or Nothing if the key isn't in the view.

findWithDefault :: (Serialise k, Serialise v) => v -> k -> View k v -> v Source #

The expression (findWithDefault def k view) returns the value at key k or returns default value def when the key is not in the view.

Folds

foldr :: Serialise v => (v -> b -> b) -> b -> View k v -> b Source #

Fold the values in the view using the given right-associative binary operator, such that foldr f z == foldr f z . elems.

foldl :: Serialise v => (a -> v -> a) -> a -> View k v -> a Source #

Fold the values in the view using the given left-associative binary operator, such that foldl f z == foldl f z . elems.

foldrWithKey :: (Serialise k, Serialise v) => (k -> v -> b -> b) -> b -> View k v -> b Source #

Fold the keys and values in the view using the given right-associative binary operator, such that foldrWithKey f z == foldr (uncurry f) z . toList.

foldlWithKey :: (Serialise k, Serialise v) => (a -> k -> v -> a) -> a -> View k v -> a Source #

Fold the keys and values in the view using the given left-associative binary operator, such that foldlWithKey f z == foldl (\z' (kx, x) -> f z' kx x) z . toList.

foldViewWithKey :: (Monoid m, Serialise k, Serialise v) => (k -> v -> m) -> View k v -> m Source #

Fold the keys and values in the view using the given monoid.

Conversion

elems :: Serialise v => View k v -> [v] Source #

Return all elements of the view in the order of their keys.

keys :: Serialise k => View k v -> [k] Source #

Return all keys of the view in the order they are stored in the underlying LMDB database.

toList :: (Serialise k, Serialise v) => View k v -> [(k, v)] Source #

Convert the view to a list of key/value pairs.