btree-concurrent-0.1.5: A backend agnostic, concurrent BTree

Safe HaskellNone

Data.BTree.BTree

Contents

Description

Concurrent BTree with relaxed balance.

This module is inspired by the paper B-Trees with Relaxed Balance, Kim S. Larsen and Rolf Fagerberg, 1993 Department of Mathematics and Computer Science, Odense University, Denmark.

This implementation is not full, and has some serious limitations:

  1. The rebalance logic to handle underful leafs has not been implemented.
  2. toList, foldli, foldri, search, findMin and findMax may fail if run in parallel with rebalanceProcess. The current implementations of these operations are therefore considered unsafe.
  3. findMin and findMax may fail in the case where the outer leaf is empty.

It is important to note, that these limitations are limitations of the current implementation and not of the original design. They are solely due to lack of time.

To clarify: Safe operations are those that support rebalancing during the operations, while unsafe operations may fail if run during rebalancing.

Synopsis

Setup and execution:

makeParamSource

Arguments

:: (MonadIO mIO, Cache m p (Ref a) (Node k v)) 
=> Int

Order of tree.

-> Maybe (Ref (Node k1 v1))

Optional root node.

-> p

Cache parameter.

-> mIO (Param p k1 v1)

The result in monadIO

Make a new tree parameter from order, root node and cache parameter. When no root node is given, Ref 0 will be used and a new tree initialised here. This may overwrite an existing tree. Is used together with execTree.

execTreeSource

Arguments

:: Param st k v

Tree parameter (see makeParam)

-> BTreeM m st k v a

Tree instance

-> m a

The result inside the chosen monad

execTree takes a tree parameter and a group of operations in a BTreeM monad and exectures the operations.

Class and type aliases

class (Ord k, Serialize k, Interval k) => Key k Source

Some type-fu. Context (Key k) gives the context (Ord k, Serialize k, ...)

Instances

(Ord k, Serialize k, Interval k) => Key k

Dummy instance.

class (Eq v, Serialize v) => Value v Source

Some type-fu. Context (Value v) gives the context (Eq v, Serialize v, ...)

Instances

(Eq v, Serialize v) => Value v

Dummy instance.

class Interval k whereSource

Needed to generate the split-keys used in branch nodes.

Methods

between :: k -> k -> kSource

Given two keys, a < c, compute a new key b, such that a <= b < c. Default is to choose a, however a smarter instance exist for ByteString.

Instances

Interval ByteString

Instance for Bytestring that yields short keys.

type TreeBackend mc k v = KVBackend mc (Ref (Node k v)) ByteStringSource

Type aliases to shorten cache type.

type TreeResult m mc k v a = BTreeM m (Param mc (Ref (Node k v)) (Node k v)) k v aSource

Type aliases to shorten result types.

Safe operations:

insertSource

Arguments

:: (MonadIO m, TreeBackend mc k v, Key k, Value v) 
=> k

key

-> v

value to associate with the key

-> TreeResult m mc k v () 

O(log n). Insert key-value pair into current tree. After this operation lookup k will yield Just v. If the key already exists it is overridden. If you want the overridden value, or want different behaviour when the key exists see modify.

insert may leave the tree unbalanced, skewed or with underfull nodes. The tree can be re-balanced by starting a rebalanceProcess.

 execTree p $ insert 42 "foobar"

deleteSource

Arguments

:: (MonadIO m, TreeBackend mc k v, Key k, Value v) 
=> k

key

-> TreeResult m mc k v (Maybe v)

The previous value if present

O(log n). Delete a key from the tree. The deleted value is returned as Just v if present, otherwise Nothing is returned.

 execTree p $ delete 42

lookupSource

Arguments

:: (MonadIO m, TreeBackend mc k v, Key k, Value v) 
=> k

key

-> TreeResult m mc k v (Maybe v)

The value if present

O(log n). Lookup key in current tree.

 execTree p $ do insert 42 "foo"      -- ()
                 a <- lookup 42       -- Just "foo"
                 insert 42 "bar"      -- ()
                 b <- lookup 42       -- Just "bar"
                 delete 42            -- Just "bar"
                 c <- lookup 42       -- Nothing
                 return (a, b, c)     -- (Just "foo", Just "bar", Nothing)

modifySource

Arguments

:: (MonadIO m, TreeBackend mc k v, Key k, Value v) 
=> (v -> v -> v)

f computes the new value from old and default.

-> k

key

-> v

Default value is used when no other is present

-> TreeResult m mc k v (Maybe v)

The previous value if present

O(log n). Replace the value of k with f v v', where v' is the current value. The old value v' is returned after the replacement. If no current value exist, v is inserted.

The semantics is the same as insertLookupWithKey . const.

 execTree p $ do delete 42
                 modify subtract 42 1    -- inserts    (42,  1)
                 modify subtract 42 1    -- updates to (42,  0)
                 modify subtract 42 1    -- updates to (42, -1)

saveSource

Arguments

:: (MonadIO m, TreeBackend mc k v, Key k, Value v) 
=> TreeResult m mc k v (Ref (Node k v))

Ref to the root node.

Save the tree by flushing the underlying cache to the permanent store and return a ref to the root node.

Rebalancing:

rebalanceProcessSource

Arguments

:: (MonadIO m, TreeBackend m2 k v, Key k, Value v) 
=> Param (CacheSTMP m2 k v) k v

Tree parameter.

-> m (MVar ThreadId)

ThreadId

A process for background rebalancing. Start inside its own thread, since this will run forever. Stop by killing the thread.

 pid <- forkIO $ rebalanceProcess p
 -- Perform safe tree operations
 killThread pid

Unsafe operations:

toListSource

Arguments

:: (MonadIO m, TreeBackend mc k v, Key k, Value v) 
=> TreeResult m mc k v [(k, v)]

The list of (key, value) pairs.

Convert the tree into a list of key-value pairs. This function may crash if used together with rebalanceProcess.

foldli :: (MonadIO m, TreeBackend mc k v, Key k, Value v) => (a -> k -> v -> a) -> a -> TreeResult m mc k v aSource

Fold with key in left to right order.

foldri :: (MonadIO m, TreeBackend mc k v, Key k, Value v) => (k -> v -> a -> a) -> a -> TreeResult m mc k v aSource

Fold with key in right to left order.

searchSource

Arguments

:: (MonadIO m, TreeBackend mc k v, Key k, Value v) 
=> ((k, k) -> Bool)

f defines interesting intervals

-> TreeResult m mc k v [(k, v)]

A list of chosen (key, value) pairs

A generalised way of querying the tree. Given two keys a <= b the function needs to answer True or False as to whether the interval [a, b] contains interesting keys. No all keys in the interval need be interesting. This function will then return all interesting keys in an efficient way.

search_Source

Arguments

:: (MonadIO m, TreeBackend mc k v, Key k, Value v) 
=> ((k, k) -> Bool)

f defines interesting intervals

-> TreeResult m mc k v ()

A list of chosen (key, value) pairs

findMin :: (Ord k, MonadIO m, Cache mc p (Ref (Node k v)) (Node k v)) => BTreeM m p k v (k, v)Source

Lookup minimum key

findMax :: (Ord k, MonadIO m, Cache mc p (Ref (Node k v)) (Node k v)) => BTreeM m p k v (k, v)Source

Lookup maximum key

height :: (MonadIO m, Cache m1 p (Ref (Node k v)) (Node k v)) => BTreeM m p k v IntSource

Calculate the height of the tree, i.e. the longest node path from root to leaf.