Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
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.
- data View k v
- newView :: Database k v -> IO (View k v)
- (!) :: (Serialise k, Serialise v) => View k v -> k -> v
- (!?) :: (Serialise k, Serialise v) => View k v -> k -> Maybe v
- null :: View k v -> Bool
- size :: View k v -> Int
- member :: Serialise k => k -> View k v -> Bool
- notMember :: Serialise k => k -> View k v -> Bool
- lookup :: (Serialise k, Serialise v) => k -> View k v -> Maybe v
- findWithDefault :: (Serialise k, Serialise v) => v -> k -> View k v -> v
- foldr :: Serialise v => (v -> b -> b) -> b -> View k v -> b
- foldl :: Serialise v => (a -> v -> a) -> a -> View k v -> a
- foldrWithKey :: (Serialise k, Serialise v) => (k -> v -> b -> b) -> b -> View k v -> b
- foldlWithKey :: (Serialise k, Serialise v) => (a -> k -> v -> a) -> a -> View k v -> a
- foldViewWithKey :: (Monoid m, Serialise k, Serialise v) => (k -> v -> m) -> View k v -> m
- elems :: Serialise v => View k v -> [v]
- keys :: Serialise k => View k v -> [k]
- toList :: (Serialise k, Serialise v) => View k v -> [(k, v)]
Creating
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
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
.
findWithDefault :: (Serialise k, Serialise v) => v -> k -> View k v -> v Source #
The expression (
returns the value at key
findWithDefault
def k view)k
or returns default value def
when the key is not in the view.
Folds
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.