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

Safe HaskellNone
LanguageHaskell2010

Data.BTree.Primitives.Index

Synopsis

Documentation

data Index key node Source #

The Index encodes the internal structure of an index node.

The index is abstracted over the type node of sub-trees. The keys and nodes are stored in separate Vectors and the keys are sorted in strictly increasing order. There should always be one more sub-tree than there are keys. Hence structurally the smallest Index has one sub-tree and no keys, but a valid B+-tree index node will have at least two sub-trees and one key.

Constructors

Index !(Vector key) !(Vector node) 

Instances

Functor (Index key) Source # 

Methods

fmap :: (a -> b) -> Index key a -> Index key b #

(<$) :: a -> Index key b -> Index key a #

Foldable (Index key) Source # 

Methods

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

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

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

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

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

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

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

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

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

null :: Index key a -> Bool #

length :: Index key a -> Int #

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

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

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

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

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

Traversable (Index key) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Index key a -> f (Index key b) #

sequenceA :: Applicative f => Index key (f a) -> f (Index key a) #

mapM :: Monad m => (a -> m b) -> Index key a -> m (Index key b) #

sequence :: Monad m => Index key (m a) -> m (Index key a) #

(Eq node, Eq key) => Eq (Index key node) Source # 

Methods

(==) :: Index key node -> Index key node -> Bool #

(/=) :: Index key node -> Index key node -> Bool #

(Show node, Show key) => Show (Index key node) Source # 

Methods

showsPrec :: Int -> Index key node -> ShowS #

show :: Index key node -> String #

showList :: [Index key node] -> ShowS #

(Binary k, Binary n) => Binary (Index k n) Source # 

Methods

put :: Index k n -> Put #

get :: Get (Index k n) #

putList :: [Index k n] -> Put #

indexNumKeys :: Index key val -> Int Source #

Return the number of keys in this Index.

indexNumVals :: Index key val -> Int Source #

Return the number of values stored in this Index.

validIndex :: Ord key => Index key node -> Bool Source #

Validate the key/node count invariant of an Index.

validIndexSize :: Ord key => Int -> Int -> Index key node -> Bool Source #

Validate the size of an Index.

splitIndexAt :: Int -> Index key val -> (Index key val, key, Index key val) Source #

Split an index node.

This function splits an index node into two new nodes at the given key position numLeftKeys and returns the resulting indices and the key separating them. Eventually this should take the binary size of serialized keys and sub-tree pointers into account. See also splitLeaf in Data.BTree.Primitives.Leaf.

extendedIndex :: Int -> (Index k b -> a) -> Index k b -> Index k a Source #

Split an index many times.

This function splits an Index node into smaller pieces. Each resulting sub-Index has between maxIdxKeys/2 and maxIdxKeys inclusive values and is additionally applied to the function f.

This is the dual of a monadic bind and is also known as the extended function of extendable functors. See Data.Functor.Extend in the "semigroupoids" package.

bindIndex (extendedIndex n id idx) id == idx

extendIndexPred :: (a -> Bool) -> (Index k b -> a) -> Index k b -> Maybe (Index k a) Source #

mergeIndex :: Index key val -> key -> Index key val -> Index key val Source #

Merge two indices.

Merge two indices leftIndex, rightIndex given a discriminating key middleKey, i.e. such that '∀ (k,v) ∈ leftIndex. k < middleKey' and '∀ (k,v) ∈ rightIndex. middleKey <= k'.

mergeIndex is a partial inverse of splitIndex, i.e. prop> splitIndex is == (left,mid,right) => mergeIndex left mid right == is

indexFromList :: [key] -> [val] -> Index key val Source #

Create an index from key-value lists.

The internal invariants of the Index data structure apply. That means there is one more value than there are keys and keys are ordered in strictly increasing order.

singletonIndex :: val -> Index key val Source #

Create an index with a single value.

fromSingletonIndex :: Index key val -> Maybe val Source #

Test if the index consists of a single value.

Returns the element if the index is a singleton. Otherwise fails.

fromSingletonIndex (singletonIndex val) == Just val

bindIndex :: Index k a -> (a -> Index k b) -> Index k b Source #

Bind an index

bindIndex idx singletonIndex == idx

bindIndexM :: (Functor m, Monad m) => Index k a -> (a -> m (Index k b)) -> m (Index k b) Source #

data IndexCtx key val Source #

Representation of one-hole contexts of Index.

Just one val removes. All keys are present.

V.length leftVals  == V.length lefyKeys
V.length rightVals == V.length rightKeys

Constructors

IndexCtx 

Instances

Functor (IndexCtx key) Source # 

Methods

fmap :: (a -> b) -> IndexCtx key a -> IndexCtx key b #

(<$) :: a -> IndexCtx key b -> IndexCtx key a #

Foldable (IndexCtx key) Source # 

Methods

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

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

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

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

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

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

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

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

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

null :: IndexCtx key a -> Bool #

length :: IndexCtx key a -> Int #

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

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

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

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

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

Traversable (IndexCtx key) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> IndexCtx key a -> f (IndexCtx key b) #

sequenceA :: Applicative f => IndexCtx key (f a) -> f (IndexCtx key a) #

mapM :: Monad m => (a -> m b) -> IndexCtx key a -> m (IndexCtx key b) #

sequence :: Monad m => IndexCtx key (m a) -> m (IndexCtx key a) #

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

Methods

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

show :: IndexCtx key val -> String #

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

putVal :: IndexCtx key val -> val -> Index key val Source #

putIdx :: IndexCtx key val -> Index key val -> Index key val Source #

valView :: Ord key => key -> Index key val -> (IndexCtx key val, val) Source #

valViewMin :: Index key val -> (IndexCtx key val, val) Source #

valViewMax :: Index key val -> (IndexCtx key val, val) Source #

distribute :: Ord k => Map k v -> Index k node -> Index k (Map k v, node) Source #

Distribute a map of key-value pairs over an index.

leftView :: IndexCtx key val -> Maybe (IndexCtx key val, val, key) Source #

rightView :: IndexCtx key val -> Maybe (key, val, IndexCtx key val) Source #