fixfile-0.2.0.0: File-backed recursive data structures.

Copyright(C) 2016 Rev. Johnny Healey
LicenseLGPL-3
MaintainerRev. Johnny Healey <rev.null@gmail.com>
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Data.FixFile.BTree

Description

This is a BTree data type that can be used with FixFile. It can be used as a key-value store where the same key can correspond to multiple values. It supports logarithmic insert, lookup, and delete operations.

Synopsis

Documentation

data BTree n k v a Source

A Fixed (BTree n k v) stores a BTree of key/value pairs. n should be a Nat and will be the maximum number of elements in each branch of the BTree.

Instances

Functor (BTree n k v) Source 
Foldable (BTree n k v) Source 
Traversable (BTree n k v) Source 
(Read k, Read v, Read a) => Read (BTree n k v a) Source 
(Show k, Show v, Show a) => Show (BTree n k v a) Source 
Generic (BTree n k v a) Source 
(Binary k, Binary v, Binary a) => Binary (BTree n k v a) Source 
type Rep (BTree n k v a) Source 

createBTreeFile :: (Typeable n, Binary k, Typeable k, Binary v, Typeable v) => FilePath -> IO (FixFile (Ref (BTree n k v))) Source

Create a FixFile storing a (BTree k v). The initial value is empty.

openBTreeFile :: (Binary k, Typeable k, Binary v, Typeable v) => FilePath -> IO (FixFile (Ref (BTree n k v))) Source

Open a FixFile storing a (BTree k v).

empty :: Fixed g => g (BTree n k v) Source

An empty BTree

depth :: Fixed g => g (BTree n k v) -> Int Source

Compute the depth of a BTree

insertBTree :: (KnownNat n, Ord k, Fixed g) => k -> v -> g (BTree n k v) -> g (BTree n k v) Source

Insert the value v with the key k into a Fixed (BTree k v).

insertBTreeT :: (KnownNat n, Ord k, Binary k, Binary v) => k -> v -> Transaction (Ref (BTree n k v)) s () Source

lookupBTree :: (Ord k, Fixed g) => k -> g (BTree n k v) -> [v] Source

Lookup the values stored for the key k in a Fixed (BTree k v).

lookupBTreeT :: (Ord k, Binary k, Binary v) => k -> Transaction (Ref (BTree n k v)) s [v] Source

filterBTree :: (Ord k, Fixed g) => k -> (v -> Bool) -> g (BTree n k v) -> g (BTree n k v) Source

Filter items from a Fixed (BTree k v) for a key k that match the predicate.

filterBTreeT :: (Ord k, Binary k, Binary v) => k -> (v -> Bool) -> Transaction (Ref (BTree n k v)) s () Source

deleteBTree :: (Ord k, Fixed g) => k -> g (BTree n k v) -> g (BTree n k v) Source

Delete all items for key k from the Fixed (BTree k v).

deleteBTreeT :: (Ord k, Binary k, Binary v) => k -> Transaction (Ref (BTree n k v)) s () Source

partitionBTree :: (Ord k, Fixed g) => k -> g (BTree n k v) -> (g (BTree n k v), g (BTree n k v)) Source

Split a BTree into two two BTrees with keys and keys k.

toListBTree :: (Ord k, Fixed g) => g (BTree n k v) -> [(k, v)] Source

Turn a Fixed (BTree k v) into a list of key value tuples.

fromListBTree :: (KnownNat n, Ord k, Fixed g) => [(k, v)] -> g (BTree n k v) Source

Turn a list of key value tuples into a Fixed (BTree k v).