Safe Haskell | None |
---|---|
Language | Haskell2010 |
An impure B+-tree implementation.
This module contains the implementation of a B+-tree that is backed by a page allocator (see Data.BTree.Alloc).
- data Tree key val where
- data Node height key val where
- empty :: Tree k v
- fromList :: (AllocM m, Key k, Value v) => [(k, v)] -> m (Tree k v)
- fromMap :: (AllocM m, Key k, Value v) => Map k v -> m (Tree k v)
- insertTree :: (AllocM m, Key key, Value val) => key -> val -> Tree key val -> m (Tree key val)
- insertTreeMany :: (AllocM m, Key key, Value val) => Map key val -> Tree key val -> m (Tree key val)
- deleteTree :: (AllocM m, Key key, Value val) => key -> Tree key val -> m (Tree key val)
- lookupTree :: forall m key val. (AllocReaderM m, Key key, Value val) => key -> Tree key val -> m (Maybe val)
- lookupMinTree :: (AllocReaderM m, Key key, Value val) => Tree key val -> m (Maybe (key, val))
- lookupMaxTree :: (AllocReaderM m, Key key, Value val) => Tree key val -> m (Maybe (key, val))
- foldr :: (AllocReaderM m, Key k, Value a) => (a -> b -> b) -> b -> Tree k a -> m b
- foldrM :: (AllocReaderM m, Key k, Value a) => (a -> b -> m b) -> b -> Tree k a -> m b
- foldrWithKey :: (AllocReaderM m, Key k, Value a) => (k -> a -> b -> b) -> b -> Tree k a -> m b
- foldrWithKeyM :: (AllocReaderM m, Key k, Value a) => (k -> a -> b -> m b) -> b -> Tree k a -> m b
- foldMap :: (AllocReaderM m, Key k, Value a, Monoid c) => (a -> c) -> Tree k a -> m c
- toList :: (AllocReaderM m, Key k, Value a) => Tree k a -> m [(k, a)]
Structures
data Tree key val where Source #
A B+-tree.
This is a simple wrapper around a root Node
. The type-level height is
existentially quantified, but a term-level witness is stores.
Tree :: {..} -> Tree key val | |
|
data Node height key val where Source #
A node in a B+-tree.
Nodes are parameterized over the key and value types and are additionally indexed by their height. All paths from the root to the leaves have the same length. The height is the number of edges from the root to the leaves, i.e. leaves are at height zero and index nodes increase the height.
Sub-trees are represented by a NodeId
that are used to resolve the actual
storage location of the sub-tree node.
Construction
fromList :: (AllocM m, Key k, Value v) => [(k, v)] -> m (Tree k v) Source #
Create a tree from a list.
Manipulation
insertTree :: (AllocM m, Key key, Value val) => key -> val -> Tree key val -> m (Tree key val) Source #
Insert a key-value pair in an impure B+-tree.
You are responsible to make sure the key is smaller than maxKeySize
,
otherwise a KeyTooLargeError
can (but not always will) be thrown.
insertTreeMany :: (AllocM m, Key key, Value val) => Map key val -> Tree key val -> m (Tree key val) Source #
Bulk insert a bunch of key-value pairs in an impure B+-tree.
You are responsible to make sure all keys is smaller than maxKeySize
,
otherwise a KeyTooLargeError
can (but not always will) be thrown.
deleteTree :: (AllocM m, Key key, Value val) => key -> Tree key val -> m (Tree key val) Source #
Delete a node from the tree.
Lookup
lookupTree :: forall m key val. (AllocReaderM m, Key key, Value val) => key -> Tree key val -> m (Maybe val) Source #
Lookup a value in an impure B+-tree.
lookupMinTree :: (AllocReaderM m, Key key, Value val) => Tree key val -> m (Maybe (key, val)) Source #
The minimal key of the map, returns Nothing
if the map is empty.
lookupMaxTree :: (AllocReaderM m, Key key, Value val) => Tree key val -> m (Maybe (key, val)) Source #
The maximal key of the map, returns Nothing
if the map is empty.
Folds
foldr :: (AllocReaderM m, Key k, Value a) => (a -> b -> b) -> b -> Tree k a -> m b Source #
Perform a right-associative fold over the tree.
foldrM :: (AllocReaderM m, Key k, Value a) => (a -> b -> m b) -> b -> Tree k a -> m b Source #
Perform a monadic right-associative fold over the tree.
foldrWithKey :: (AllocReaderM m, Key k, Value a) => (k -> a -> b -> b) -> b -> Tree k a -> m b Source #
Perform a right-associative fold over the tree key-value pairs.
foldrWithKeyM :: (AllocReaderM m, Key k, Value a) => (k -> a -> b -> m b) -> b -> Tree k a -> m b Source #
Perform a monadic right-assiciative fold over the tree key-value pairs.