haskey-btree-0.2.0.0: B+-tree implementation in Haskell.

Safe HaskellNone
LanguageHaskell2010

Data.BTree.Impure

Contents

Description

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

Synopsis

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.

Constructors

Tree :: {..} -> Tree key val 

Fields

Instances

(Show key, Show val) => Show (Tree key val) Source # 

Methods

showsPrec :: Int -> Tree key val -> ShowS #

show :: Tree key val -> String #

showList :: [Tree key val] -> ShowS #

Binary (Tree key val) Source # 

Methods

put :: Tree key val -> Put #

get :: Get (Tree key val) #

putList :: [Tree key val] -> Put #

(Value k, Value v) => Value (Tree k v) Source # 

Methods

fixedSize :: Proxy * (Tree k v) -> Maybe Int Source #

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.

Constructors

Idx :: {..} -> Node (S height) key val 

Fields

Leaf :: {..} -> Node Z key val 

Fields

Instances

(Eq key, Eq val) => Eq (Node height key val) Source # 

Methods

(==) :: Node height key val -> Node height key val -> Bool #

(/=) :: Node height key val -> Node height key val -> Bool #

(Show key, Show val) => Show (Node height key val) Source # 

Methods

showsPrec :: Int -> Node height key val -> ShowS #

show :: Node height key val -> String #

showList :: [Node height key val] -> ShowS #

Construction

empty :: Tree k v Source #

Create an empty tree.

fromList :: (AllocM m, Key k, Value v) => [(k, v)] -> m (Tree k v) Source #

Create a tree from a list.

fromMap :: (AllocM m, Key k, Value v) => Map k v -> m (Tree k v) Source #

Create a tree from a map.

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.

foldMap :: (AllocReaderM m, Key k, Value a, Monoid c) => (a -> c) -> Tree k a -> m c Source #

Map each value of the tree to a monoid, and combine the results.

toList :: (AllocReaderM m, Key k, Value a) => Tree k a -> m [(k, a)] Source #

Convert an impure B+-tree to a list of key-value pairs.