berkeleydb-2008.10.31: Pretty BerkeleyDB v4 binding.

Portabilitynon-portable (requires libDB)
Stabilityexperimental
Maintainerlemmih@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.

Synopsis

Db type

data Db key value Source

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

null :: Db key value -> BoolSource

O(1). Is the map empty?

size :: Db key value -> IntSource

O(1). The number of elements in the map.

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?

lookup :: (Binary key, Binary value, Monad m) => key -> Db key value -> m valueSource

O(log n). Lookup the value at a key in the database.

The function will return the result in the monad or fail in it the key isn't in the database. Often, the monad to use is Maybe, so you get either (Just result) or Nothing.

findWithDefault :: (Binary k, Binary a) => a -> k -> Db k a -> aSource

O(log n). The expression (findWithDefault def k db) returns the value at key k or returns def when the key is not in the database.

Construction

empty :: (Binary key, Binary value) => Db key valueSource

O(1). The empty database.

singleton :: (Binary k, Binary a) => k -> a -> Db k aSource

O(1). A map with a single element.

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. insertWith f key value db will insert the pair (key, value) into db 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. insertWithKey f key value db will insert the pair (key, value) into db 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.

update :: (Binary k, Binary a) => (a -> Maybe a) -> k -> Db k a -> Db k aSource

O(log n). The expression (update f k map) updates the value x at k (if it is in the map). If (f x) is Nothing, the element is deleted. If it is (Just y), the key k is bound to the new value y.

updateWithKey :: (Binary k, Binary a) => (k -> a -> Maybe a) -> k -> Db k a -> Db k aSource

O(log n). The expression (updateWithKey f k db) updates the value x at k (if it is in the database). If (f k x) is Nothing, the element is deleted. If it is (Just y), the key k 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 (updateWithKey f k db) updates the value x at k (if it is in the database). If (f k x) is Nothing, the element is deleted. If it is (Just y), the key k is bound to the new value y.

alter :: (Binary k, Binary a) => (Maybe a -> Maybe a) -> k -> Db k a -> Db k aSource

O(log n). The expression (alter f k db) alters the value x at k, or absence thereof. alter can be used to insert, delete, or update a value in a Db. In short : lookup k (alter f k m) = f (lookup k m)

Combine

Union

union :: (Binary key, Binary value) => Db key value -> Db key value -> Db key valueSource

O(log n*m). The expression (union t1 t2) takes the left-biased union of t1 and t2. It prefers t1 when duplicate keys are encountered, i.e. (union == unionWith const).

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).

unions :: (Binary k, Binary a) => [Db k a] -> Db k aSource

The union of a list of databases: (unions == foldl union empty).

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

fold :: (Binary k, Binary a) => (a -> b -> b) -> b -> Db k a -> bSource

O(n). Fold the values in the map, such that fold f z == foldr f z . elems. For example,

 elems map = fold (:) [] map

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.

Submap

Indexed

Min/Max