Copyright | (C) 2016 Rev. Johnny Healey |
---|---|
License | LGPL-3 |
Maintainer | Rev. Johnny Healey <rev.null@gmail.com> |
Stability | experimental |
Portability | unknown |
Safe Haskell | None |
Language | Haskell2010 |
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. This BTree
embeds values in the leaf nodes instead of providing them with distinct
leaf nodes. It is not recommended for use with large values.
- data BTree n k v a
- createBTreeFile :: (Typeable n, Binary k, Typeable k, Binary v, Typeable v) => FilePath -> IO (FixFile (Ref (BTree n k v)))
- openBTreeFile :: (Binary k, Typeable k, Binary v, Typeable v) => FilePath -> IO (FixFile (Ref (BTree n k v)))
- depth :: Fixed g => g (BTree n k v) -> Int
- insertBTree :: (KnownNat n, Ord k, Fixed g) => k -> v -> g (BTree n k v) -> g (BTree n k v)
- insertBTreeT :: (KnownNat n, Ord k, Binary k, Binary v) => k -> v -> Transaction (Ref (BTree n k v)) s ()
- lookupBTree :: (Ord k, Fixed g) => k -> g (BTree n k v) -> [v]
- lookupBTreeT :: (Ord k, Binary k, Binary v) => k -> Transaction (Ref (BTree n k v)) s [v]
- filterBTree :: (Ord k, Fixed g) => k -> (v -> Bool) -> g (BTree n k v) -> g (BTree n k v)
- filterBTreeT :: (Ord k, Binary k, Binary v) => k -> (v -> Bool) -> Transaction (Ref (BTree n k v)) s ()
- deleteBTree :: (Ord k, Fixed g) => k -> g (BTree n k v) -> g (BTree n k v)
- deleteBTreeT :: (Ord k, Binary k, Binary v) => k -> Transaction (Ref (BTree n k v)) s ()
- partitionBTree :: (Ord k, Fixed g) => k -> g (BTree n k v) -> (g (BTree n k v), g (BTree n k v))
- toListBTree :: (Ord k, Fixed g) => g (BTree n k v) -> [(k, v)]
- fromListBTree :: (KnownNat n, Ord k, Fixed g) => [(k, v)] -> g (BTree n k v)
Documentation
A Fixed
(
stores a BTree of key/value pairs.
BTree
n k v)n
should be a Nat
and will be the maximum number of elements in each
branch of the BTree
.
Functor (BTree n k v) Source # | |
Foldable (BTree n k v) Source # | |
Traversable (BTree n k v) Source # | |
FixedTraversable (BTree n k v) Source # | |
FixedFoldable (BTree n k v) Source # | |
FixedFunctor (BTree n k v) Source # | |
FixedSub (BTree n k v) Source # | |
FixedAlg (BTree n k v) Source # | |
Null1 (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 Alg (BTree n k v) Source # | |
type Sub (BTree n k v) v v' 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 #
openBTreeFile :: (Binary k, Typeable k, Binary v, Typeable v) => FilePath -> IO (FixFile (Ref (BTree n k v))) Source #
insertBTree :: (KnownNat n, Ord k, Fixed g) => k -> v -> g (BTree n k v) -> g (BTree n k v) Source #
insertBTreeT :: (KnownNat n, Ord k, Binary k, Binary v) => k -> v -> Transaction (Ref (BTree n k v)) s () Source #
Transaction
version of insertBTree
.
lookupBTreeT :: (Ord k, Binary k, Binary v) => k -> Transaction (Ref (BTree n k v)) s [v] Source #
Transaction
version of lookupBTree
.
filterBTreeT :: (Ord k, Binary k, Binary v) => k -> (v -> Bool) -> Transaction (Ref (BTree n k v)) s () Source #
Transaction
version of filterBTree
.
deleteBTreeT :: (Ord k, Binary k, Binary v) => k -> Transaction (Ref (BTree n k v)) s () Source #
Transaction
version of deleteBTree
.
partitionBTree :: (Ord k, Fixed g) => k -> g (BTree n k v) -> (g (BTree n k v), g (BTree n k v)) Source #