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

Safe HaskellNone
LanguageHaskell2010

Data.BTree.Pure

Contents

Description

A pure in-memory B+-tree implementation.

Synopsis

Structures

data Tree key val where Source #

A pure B+-tree.

This is a simple wrapper around a root Node. An empty tree is represented by Nothing. Otherwise it's Just the root. The height is existentially quantified.

Constructors

Tree :: !TreeSetup -> Maybe (Node height key val) -> Tree key val 

Instances

Foldable (Tree key) Source #

Make a tree node foldable over its value.

Methods

fold :: Monoid m => Tree key m -> m #

foldMap :: Monoid m => (a -> m) -> Tree key a -> m #

foldr :: (a -> b -> b) -> b -> Tree key a -> b #

foldr' :: (a -> b -> b) -> b -> Tree key a -> b #

foldl :: (b -> a -> b) -> b -> Tree key a -> b #

foldl' :: (b -> a -> b) -> b -> Tree key a -> b #

foldr1 :: (a -> a -> a) -> Tree key a -> a #

foldl1 :: (a -> a -> a) -> Tree key a -> a #

toList :: Tree key a -> [a] #

null :: Tree key a -> Bool #

length :: Tree key a -> Int #

elem :: Eq a => a -> Tree key a -> Bool #

maximum :: Ord a => Tree key a -> a #

minimum :: Ord a => Tree key a -> a #

sum :: Num a => Tree key a -> a #

product :: Num a => Tree key a -> a #

(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 #

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.

Constructors

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

Fields

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

Fields

Instances

Foldable (Node height key) Source # 

Methods

fold :: Monoid m => Node height key m -> m #

foldMap :: Monoid m => (a -> m) -> Node height key a -> m #

foldr :: (a -> b -> b) -> b -> Node height key a -> b #

foldr' :: (a -> b -> b) -> b -> Node height key a -> b #

foldl :: (b -> a -> b) -> b -> Node height key a -> b #

foldl' :: (b -> a -> b) -> b -> Node height key a -> b #

foldr1 :: (a -> a -> a) -> Node height key a -> a #

foldl1 :: (a -> a -> a) -> Node height key a -> a #

toList :: Node height key a -> [a] #

null :: Node height key a -> Bool #

length :: Node height key a -> Int #

elem :: Eq a => a -> Node height key a -> Bool #

maximum :: Ord a => Node height key a -> a #

minimum :: Ord a => Node height key a -> a #

sum :: Num a => Node height key a -> a #

product :: Num a => Node height key a -> a #

(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 #

Manipulations

empty :: TreeSetup -> Tree key val Source #

The empty tree.

singleton :: Key k => TreeSetup -> k -> v -> Tree k v Source #

Construct a tree containg one element.

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

O(n*log n). Construct a B-tree from a list of key/value pairs.

If the list contains duplicate keys, the last pair for a duplicate key is kept.

insert :: Key k => k -> v -> Tree k v -> Tree k v Source #

Insert a key-value pair into a tree.

When inserting a new entry, the leaf it is inserted to and the index nodes on the path to the leaf potentially need to be split. Instead of returning the outcome, 1 node or 2 nodes (with a discriminating key), we return an Index of these nodes.

If the key already existed in the tree, it is overwritten.

insertMany :: Key k => Map k v -> Tree k v -> Tree k v Source #

Insert a bunch of key-value pairs simultaneously.

delete :: Key k => k -> Tree k v -> Tree k v Source #

Delete a key-value pair from the tree.

Lookup

lookup :: Key k => k -> Tree k v -> Maybe v Source #

Lookup a value in the tree.

findWithDefault :: Key k => v -> k -> Tree k v -> v Source #

Lookup a value in the tree, or return a default.

member :: Key k => k -> Tree k v -> Bool Source #

Check whether a key is present in the tree.

notMember :: Key k => k -> Tree k v -> Bool Source #

Check whether a key is not present in the tree.

Properties

null :: Tree k v -> Bool Source #

Check whether the tree is empty.

size :: Tree k v -> Int Source #

The size of a tree.

Folds

foldrWithKey :: forall k v w. (k -> v -> w -> w) -> w -> Tree k v -> w Source #

O(n). Fold key/value pairs in the B-tree.

toList :: Tree k v -> [(k, v)] Source #

O(n). Convert the B-tree to a sorted list of key/value pairs.