fixfile-0.6.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 # 

Methods

fmap :: (a -> b) -> BTree n k v a -> BTree n k v b #

(<$) :: a -> BTree n k v b -> BTree n k v a #

Foldable (BTree n k v) Source # 

Methods

fold :: Monoid m => BTree n k v m -> m #

foldMap :: Monoid m => (a -> m) -> BTree n k v a -> m #

foldr :: (a -> b -> b) -> b -> BTree n k v a -> b #

foldr' :: (a -> b -> b) -> b -> BTree n k v a -> b #

foldl :: (b -> a -> b) -> b -> BTree n k v a -> b #

foldl' :: (b -> a -> b) -> b -> BTree n k v a -> b #

foldr1 :: (a -> a -> a) -> BTree n k v a -> a #

foldl1 :: (a -> a -> a) -> BTree n k v a -> a #

toList :: BTree n k v a -> [a] #

null :: BTree n k v a -> Bool #

length :: BTree n k v a -> Int #

elem :: Eq a => a -> BTree n k v a -> Bool #

maximum :: Ord a => BTree n k v a -> a #

minimum :: Ord a => BTree n k v a -> a #

sum :: Num a => BTree n k v a -> a #

product :: Num a => BTree n k v a -> a #

Traversable (BTree n k v) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> BTree n k v a -> f (BTree n k v b) #

sequenceA :: Applicative f => BTree n k v (f a) -> f (BTree n k v a) #

mapM :: Monad m => (a -> m b) -> BTree n k v a -> m (BTree n k v b) #

sequence :: Monad m => BTree n k v (m a) -> m (BTree n k v a) #

FixedTraversable (BTree n k v) Source # 

Methods

traverseF :: (Fixed g, Fixed g', Applicative h, (* ~ a) (Alg (BTree n k v))) => (a -> h b) -> g (BTree n k v) -> h (g' (Sub (BTree n k v) a b)) Source #

FixedFoldable (BTree n k v) Source # 

Methods

foldMapF :: (Fixed g, Monoid m, (* ~ a) (Alg (BTree n k v))) => (a -> m) -> g (BTree n k v) -> m Source #

FixedFunctor (BTree n k v) Source # 

Methods

fmapF :: (Fixed g, Fixed g', (* ~ a) (Alg (BTree n k v))) => (a -> b) -> g (BTree n k v) -> g' (Sub (BTree n k v) a b) Source #

FixedSub (BTree n k v) Source # 

Associated Types

type Sub (BTree n k v :: * -> *) v v' :: * -> * Source #

FixedAlg (BTree n k v) Source # 

Associated Types

type Alg (BTree n k v :: * -> *) :: * Source #

Null1 (BTree n k v) Source # 

Methods

empty1 :: BTree n k v a Source #

null1 :: BTree n k v a -> Bool Source #

(Read k, Read v, Read a) => Read (BTree n k v a) Source # 

Methods

readsPrec :: Int -> ReadS (BTree n k v a) #

readList :: ReadS [BTree n k v a] #

readPrec :: ReadPrec (BTree n k v a) #

readListPrec :: ReadPrec [BTree n k v a] #

(Show k, Show v, Show a) => Show (BTree n k v a) Source # 

Methods

showsPrec :: Int -> BTree n k v a -> ShowS #

show :: BTree n k v a -> String #

showList :: [BTree n k v a] -> ShowS #

Generic (BTree n k v a) Source # 

Associated Types

type Rep (BTree n k v a) :: * -> * #

Methods

from :: BTree n k v a -> Rep (BTree n k v a) x #

to :: Rep (BTree n k v a) x -> BTree n k v a #

(Binary k, Binary v, Binary a) => Binary (BTree n k v a) Source # 

Methods

put :: BTree n k v a -> Put #

get :: Get (BTree n k v a) #

putList :: [BTree n k v a] -> Put #

type Alg (BTree n k v) Source # 
type Alg (BTree n k v) = v
type Sub (BTree n k v) v v' Source # 
type Sub (BTree n k v) v v' = BTree n k v'
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).

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).