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

Safe HaskellNone
LanguageHaskell2010

Data.BTree.Impure.NonEmpty

Contents

Description

Non empty wrapper around the impure Tree.

Synopsis

Structures

data NonEmptyTree key val where Source #

A non-empty variant of Tree.

Constructors

NonEmptyTree 

Fields

Instances
(Show key, Show val) => Show (NonEmptyTree key val) Source # 
Instance details

Defined in Data.BTree.Impure.NonEmpty

Methods

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

show :: NonEmptyTree key val -> String #

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

Binary (NonEmptyTree key val) Source # 
Instance details

Defined in Data.BTree.Impure.NonEmpty

Methods

put :: NonEmptyTree key val -> Put #

get :: Get (NonEmptyTree key val) #

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

(Value k, Value v) => Value (NonEmptyTree k v) Source # 
Instance details

Defined in Data.BTree.Impure.NonEmpty

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 

Fields

Leaf 

Fields

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

Defined in Data.BTree.Impure.Internal.Structures

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 # 
Instance details

Defined in Data.BTree.Impure.Internal.Structures

Methods

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

show :: Node height key val -> String #

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

Conversions

fromTree :: Tree key val -> Maybe (NonEmptyTree key val) Source #

Convert a Tree into a NonEmptyTree.

toTree :: NonEmptyTree key val -> Tree key val Source #

Convert a NonEmptyTree into a Tree.

toList :: (AllocReaderM m, Key k, Value v) => NonEmptyTree k v -> m (NonEmpty (k, v)) Source #

Convert a non-empty tree to a list of key-value pairs.

Construction

fromList :: (AllocM m, Key k, Value v) => NonEmpty (k, v) -> m (NonEmptyTree k v) Source #

Create a NonEmptyTree from a NonEmpty list.

Inserting

insert :: (AllocM m, Key k, Value v) => k -> v -> NonEmptyTree k v -> m (NonEmptyTree k v) Source #

Insert an item into a NonEmptyTree

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

Bulk insert a bunch of key-value pairs into a NonEmptyTree.