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

Safe HaskellNone
LanguageHaskell2010

Data.BTree.Impure.Structures

Contents

Description

Basic structures of an impure B+-tree.

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 #

type LeafItems k v = Map k (LeafValue v) Source #

data LeafValue v Source #

Instances

Eq v => Eq (LeafValue v) Source # 

Methods

(==) :: LeafValue v -> LeafValue v -> Bool #

(/=) :: LeafValue v -> LeafValue v -> Bool #

Show v => Show (LeafValue v) Source # 
Binary v => Binary (LeafValue v) Source # 

Methods

put :: LeafValue v -> Put #

get :: Get (LeafValue v) #

putList :: [LeafValue v] -> Put #

Binary encoding

putLeafNode :: (Binary key, Binary val) => Node Z key val -> Put Source #

Encode a Leaf Node.

getLeafNode :: (Ord key, Binary key, Binary val) => Height Z -> Get (Node Z key val) Source #

Decode a Leaf Node.

putIndexNode :: (Binary key, Binary val) => Node (S n) key val -> Put Source #

Encode an Idx Node.

getIndexNode :: (Binary key, Binary val) => Height (S n) -> Get (Node (S n) key val) Source #

Decode an Idx Node.

Casting

castNode Source #

Arguments

:: (Typeable key1, Typeable val1, Typeable key2, Typeable val2) 
=> Height height1

Term-level witness for the source height.

-> Height height2

Term-level witness for the target height.

-> n height1 key1 val1

Node to cast.

-> Maybe (n height2 key2 val2) 

Cast a node to a different type.

Essentially this is just a drop-in replacement for cast.

castNode' Source #

Arguments

:: (Typeable k, Typeable v) 
=> Height h

Term-level witness for the source height

-> n h k v

Node to cast.

-> Either (n Z k v) (n (S h) k v) 

Cast a node to one of the available types.

castValue :: (Typeable v1, Typeable v2) => v1 -> Maybe v2 Source #

Cast a value to a different type.

Essentially this is just a drop-in replacement for cast.