Portability | non-portable (requires libDB) |
---|---|
Stability | experimental |
Maintainer | lemmih@gmail.com |
Data.BerkeleyDB
Contents
Description
An efficient implementation of maps from keys to values (dictionaries).
Since many function names (but not the type name) clash with
Prelude names, this module is usually imported qualified
, e.g.
import Data.BerkeleyDB (DB) import qualified Data.BerkeleyDB as DB
The implementation of Db
uses the berkeley db library. See
http://en.wikipedia.org/wiki/Berkeley_DB and
http://www.oracle.com/technology/products/berkeley-db/index.html
Note that this implementation behaves exactly like a Data.Map.Map ByteString ByteString
,
with the key and value encoded by Data.Binary.encode/Data.Binary.decode
.
This means that keys aren't sorted according to Ord. Affected functions are:
toList
, assocs
, elems
.
- data Db key value
- (!) :: (Binary k, Binary v) => Db k v -> k -> v
- null :: Db key value -> Bool
- size :: Db key value -> Int
- member :: (Binary key, Binary value) => key -> Db key value -> Bool
- notMember :: (Binary key, Binary value) => key -> Db key value -> Bool
- lookup :: (Binary key, Binary value, Monad m) => key -> Db key value -> m value
- findWithDefault :: (Binary k, Binary a) => a -> k -> Db k a -> a
- empty :: (Binary key, Binary value) => Db key value
- singleton :: (Binary k, Binary a) => k -> a -> Db k a
- insert :: (Binary key, Binary value) => key -> value -> Db key value -> Db key value
- insertWith :: (Binary k, Binary a) => (a -> a -> a) -> k -> a -> Db k a -> Db k a
- insertWithKey :: (Binary k, Binary a) => (k -> a -> a -> a) -> k -> a -> Db k a -> Db k a
- delete :: (Binary key, Binary value) => key -> Db key value -> Db key value
- adjust :: (Binary k, Binary a) => (a -> a) -> k -> Db k a -> Db k a
- adjustWithKey :: (Binary k, Binary a) => (k -> a -> a) -> k -> Db k a -> Db k a
- update :: (Binary k, Binary a) => (a -> Maybe a) -> k -> Db k a -> Db k a
- updateWithKey :: (Binary k, Binary a) => (k -> a -> Maybe a) -> k -> Db k a -> Db k a
- updateLookupWithKey :: (Binary k, Binary a) => (k -> a -> Maybe a) -> k -> Db k a -> (Maybe a, Db k a)
- alter :: (Binary k, Binary a) => (Maybe a -> Maybe a) -> k -> Db k a -> Db k a
- union :: (Binary key, Binary value) => Db key value -> Db key value -> Db key value
- unionWith :: (Binary key, Binary value) => (value -> value -> value) -> Db key value -> Db key value -> Db key value
- unionWithKey :: (Binary key, Binary value) => (key -> value -> value -> value) -> Db key value -> Db key value -> Db key value
- unions :: (Binary k, Binary a) => [Db k a] -> Db k a
- unionsWith :: (Binary k, Binary a) => (a -> a -> a) -> [Db k a] -> Db k a
- map :: (Binary a, Binary b, Binary k) => (a -> b) -> Db k a -> Db k b
- mapWithKey :: (Binary a, Binary b, Binary k) => (k -> a -> b) -> Db k a -> Db k b
- fold :: (Binary k, Binary a) => (a -> b -> b) -> b -> Db k a -> b
- elems :: (Binary key, Binary value) => Db key value -> [value]
- keys :: (Binary key, Binary value) => Db key value -> [key]
- assocs :: (Binary key, Binary value) => Db key value -> [(key, value)]
- toList :: (Binary key, Binary value) => Db key value -> [(key, value)]
- fromList :: (Binary key, Binary value) => [(key, value)] -> Db key value
- fromListWith :: (Binary k, Binary a) => (a -> a -> a) -> [(k, a)] -> Db k a
- fromListWithKey :: (Binary k, Binary a) => (k -> a -> a -> a) -> [(k, a)] -> Db k a
- filter :: (Binary k, Binary a) => (a -> Bool) -> Db k a -> Db k a
- filterWithKey :: (Binary k, Binary a) => (k -> a -> Bool) -> Db k a -> Db k a
Db type
Instances
Typeable2 Db | |
(Binary key, Binary value, Eq key, Eq value) => Eq (Db key value) | |
(Data k, Data a, Binary k, Binary a) => Data (Db k a) | |
(Binary key, Binary value, Ord key, Ord value) => Ord (Db key value) | |
(Binary k, Binary a, Read k, Read a) => Read (Db k a) | |
(Binary key, Binary value, Show key, Show value) => Show (Db key value) | |
(Binary k, Binary a) => Monoid (Db k a) | |
(Show key, Show value, Binary key, Binary value) => Binary (Db key value) |
Operators
(!) :: (Binary k, Binary v) => Db k v -> k -> vSource
O(log n). Find the value at a key.
Calls error
when the element can not be found.
Query
member :: (Binary key, Binary value) => key -> Db key value -> BoolSource
O(log n). Is the key a member of the map?
notMember :: (Binary key, Binary value) => key -> Db key value -> BoolSource
O(log n). Is the key not a member of the map?
findWithDefault :: (Binary k, Binary a) => a -> k -> Db k a -> aSource
O(log n). The expression (
returns
the value at key findWithDefault
def k db)k
or returns def
when the key is not in the database.
Construction
Insertion
insert :: (Binary key, Binary value) => key -> value -> Db key value -> Db key valueSource
O(log n). Insert a new key and value in the database.
If the key is already present in the database, the associated value is
replaced with the supplied value, i.e. insert
is equivalent to
.
insertWith
const
insertWith :: (Binary k, Binary a) => (a -> a -> a) -> k -> a -> Db k a -> Db k aSource
O(log n). Insert with a combining function.
will insert the pair (key, value) into insertWith
f key value dbdb
if key does
not exist in the database. If the key does exist, the function will
insert the pair (key, f new_value old_value)
.
insertWithKey :: (Binary k, Binary a) => (k -> a -> a -> a) -> k -> a -> Db k a -> Db k aSource
O(log n). Insert with a combining function.
will insert the pair (key, value) into insertWithKey
f key value dbdb
if key does
not exist in the database. If the key does exist, the function will
insert the pair (key,f key new_value old_value)
.
Note that the key passed to f is the same key passed to insertWithKey
.
Delete/Update
delete :: (Binary key, Binary value) => key -> Db key value -> Db key valueSource
O(log n). Delete a key and its value from the database. When the key is not a member of the database, the original database is returned.
adjust :: (Binary k, Binary a) => (a -> a) -> k -> Db k a -> Db k aSource
O(log n). Adjust a value at a specific key. When the key is not a member of the map, the original map is returned.
adjustWithKey :: (Binary k, Binary a) => (k -> a -> a) -> k -> Db k a -> Db k aSource
O(log n). Adjust a value at a specific key. When the key is not a member of the map, the original map is returned.
updateWithKey :: (Binary k, Binary a) => (k -> a -> Maybe a) -> k -> Db k a -> Db k aSource
O(log n). The expression (
) updates the
value updateWithKey
f k dbx
at k
(if it is in the database). If (f k x
) is Nothing
,
the element is deleted. If it is (
), the key Just
yk
is bound
to the new value y
.
updateLookupWithKey :: (Binary k, Binary a) => (k -> a -> Maybe a) -> k -> Db k a -> (Maybe a, Db k a)Source
O(log n). The expression (
) updates the
value updateWithKey
f k dbx
at k
(if it is in the database). If (f k x
) is Nothing
,
the element is deleted. If it is (
), the key Just
yk
is bound
to the new value y
.
Combine
Union
unionWith :: (Binary key, Binary value) => (value -> value -> value) -> Db key value -> Db key value -> Db key valueSource
O(log n*m). Union with a combining function.
unionWithKey :: (Binary key, Binary value) => (key -> value -> value -> value) -> Db key value -> Db key value -> Db key valueSource
O(log n*m)).
Union with a combining function. This function is most efficient on (bigset union
smallset).
unionsWith :: (Binary k, Binary a) => (a -> a -> a) -> [Db k a] -> Db k aSource
The union of a list of databases, with a combining operation:
(
).
unionsWith
f == foldl
(unionWith
f) empty
Difference
Traversal
Map
map :: (Binary a, Binary b, Binary k) => (a -> b) -> Db k a -> Db k bSource
O(n). Map a function over all values in the database.
mapWithKey :: (Binary a, Binary b, Binary k) => (k -> a -> b) -> Db k a -> Db k bSource
O(n). Map a function over all values in the database.
Fold
Conversion
elems :: (Binary key, Binary value) => Db key value -> [value]Source
O(n). Return all elements of the database in the ascending order of their keys sorted by their binary representation.
keys :: (Binary key, Binary value) => Db key value -> [key]Source
O(n). Return all keys of the database in ascending order sorted by their binary representation.
assocs :: (Binary key, Binary value) => Db key value -> [(key, value)]Source
O(n). Return all key/value pairs in the map in ascending key order.
Lists
toList :: (Binary key, Binary value) => Db key value -> [(key, value)]Source
O(n). Convert to a list of key/value pairs.
fromList :: (Binary key, Binary value) => [(key, value)] -> Db key valueSource
O(n*log n). Build a database from a list of key/value pairs. See also fromAscList
.
fromListWith :: (Binary k, Binary a) => (a -> a -> a) -> [(k, a)] -> Db k aSource
O(n*log n). Build a database from a list of key/value pairs with a combining function.
fromListWithKey :: (Binary k, Binary a) => (k -> a -> a -> a) -> [(k, a)] -> Db k aSource
O(n*log n). Build a database from a list of key/value pairs with a combining function.
Ordered lists
Filter
filter :: (Binary k, Binary a) => (a -> Bool) -> Db k a -> Db k aSource
O(n). Filter all values that satisfy the predicate.
filterWithKey :: (Binary k, Binary a) => (k -> a -> Bool) -> Db k a -> Db k aSource
O(n). Filter all keys/values that satisfy the predicate.