fixfile-0.5.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.Tree23

Description

This is an implementation of a Two-Three Tree data structure that can be used with FixFile. It has two interfaces that are

Synopsis

Documentation

type Tree23 d = Tree23F (TreeKey d) (TreeValue d) Source #

Fixed (Tree23 d) represents a Two-Three tree. The data type d should have data families for it's key and value. These data families are not exported from the module. As a result, the only valid types for d are (Set k) as defined here or (Map k v), also defined here.

empty :: Fixed g => g (Tree23 d) Source #

An empty Fixed Tree23.

null :: Fixed g => g (Tree23 d) -> Bool Source #

Predicate that returns true if there are no items in the Tree23.

size :: Fixed g => g (Tree23 d) -> Int Source #

Number of entries in (Tree23 g d).

depth :: Fixed g => g (Tree23 d) -> Int Source #

The depth of (Tree23 g d). 0 represents en empty Tree.

  • Set

data Set k Source #

A Set of k represented as a Two-Three Tree.

Instances

FixedFoldable (Tree23 (Set k)) Source # 

Methods

foldMapF :: (Fixed g, Monoid m, (* ~ a) (Alg (Tree23 (Set k)))) => (a -> m) -> g (Tree23 (Set k)) -> m Source #

FixedAlg (Tree23 (Set k)) Source # 

Associated Types

type Alg (Tree23 (Set k) :: * -> *) :: * Source #

type Alg (Tree23 (Set k)) Source # 
type Alg (Tree23 (Set k)) = k

createSetFile :: (Binary k, Typeable k, f ~ Tree23 (Set k)) => FilePath -> IO (FixFile (Ref f)) Source #

Create a FixFile for storing a set of items.

openSetFile :: (Binary k, Typeable k, f ~ Tree23 (Set k)) => FilePath -> IO (FixFile (Ref f)) Source #

Open a FixFile for storing a set of items.

insertSet :: (Fixed g, Ord k, f ~ Tree23 (Set k)) => k -> g f -> g f Source #

Insert an item into a set.

lookupSet :: (Fixed g, Ord k, f ~ Tree23 (Set k)) => k -> g f -> Bool Source #

Lookup an item in a set.

deleteSet :: (Fixed g, Ord k, f ~ Tree23 (Set k)) => k -> g f -> g f Source #

Delete an item from a set.

partitionSet :: (Fixed g, Ord k, f ~ Tree23 (Set k)) => k -> g f -> (g f, g f) Source #

Split a set into sets of items and= k

minSet :: (Fixed g, Ord k, f ~ Tree23 (Set k)) => g f -> Maybe k Source #

return the minimum value

maxSet :: (Fixed g, Ord k, f ~ Tree23 (Set k)) => g f -> Maybe k Source #

return the minimum value

toListSet :: (Fixed g, Ord k, f ~ Tree23 (Set k)) => g f -> [k] Source #

Convert a set into a list of items.

fromListSet :: (Fixed g, Ord k, f ~ Tree23 (Set k)) => [k] -> g f Source #

Convert a list of items into a set.

insertSetT :: (Binary k, Ord k, f ~ Tree23 (Set k)) => k -> Transaction (Ref f) s () Source #

lookupSetT :: (Binary k, Ord k, f ~ Tree23 (Set k)) => k -> Transaction (Ref f) s Bool Source #

FTransaction version of lookupSet.

deleteSetT :: (Binary k, Ord k, f ~ Tree23 (Set k)) => k -> Transaction (Ref f) s () Source #

FTransaction version of deleteSet.

partitionSetT :: (Binary k, Ord k, f ~ Tree23 (Set k)) => k -> Transaction (Ref f) s (Stored s f, Stored s f) Source #

minSetT :: (Binary k, Ord k, f ~ Tree23 (Set k)) => Transaction (Ref f) s (Maybe k) Source #

FTransaction version of minSet.

maxSetT :: (Binary k, Ord k, f ~ Tree23 (Set k)) => Transaction (Ref f) s (Maybe k) Source #

FTransaction version of minSet.

  • Map

data Map k v Source #

A Map of keys k to values v represented as a Two-Three Tree.

Instances

FixedTraversable (Tree23 (Map k v)) Source # 

Methods

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

FixedFoldable (Tree23 (Map k v)) Source # 

Methods

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

FixedFunctor (Tree23 (Map k v)) Source # 

Methods

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

FixedSub (Tree23 (Map k v)) Source # 

Associated Types

type Sub (Tree23 (Map k v) :: * -> *) v v' :: * -> * Source #

FixedAlg (Tree23 (Map k v)) Source # 

Associated Types

type Alg (Tree23 (Map k v) :: * -> *) :: * Source #

type Alg (Tree23 (Map k v)) Source # 
type Alg (Tree23 (Map k v)) = v
type Sub (Tree23 (Map k v)) v v' Source # 
type Sub (Tree23 (Map k v)) v v' = Tree23 (Map k v')

createMapFile :: (Binary k, Typeable k, Binary v, Typeable v, f ~ Tree23 (Map k v)) => FilePath -> IO (FixFile (Ref f)) Source #

Create a FixFile of a Map.

openMapFile :: (Binary k, Typeable k, Binary v, Typeable v, f ~ Tree23 (Map k v)) => FilePath -> IO (FixFile (Ref f)) Source #

Open a FixFile of a Map.

insertMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => k -> v -> g f -> g f Source #

Insert value v into a map for key k. Any existing value is replaced.

lookupMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => k -> g f -> Maybe v Source #

Lookup an item in a map corresponding to key k.

deleteMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => k -> g f -> g f Source #

Delete an item from a map at key k.

partitionMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => k -> g f -> (g f, g f) Source #

Split a set into maps for keys and= k

alterMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => k -> (Maybe v -> Maybe v) -> g f -> g f Source #

Apply a function to alter a Map at key k. The function takes (Maybe v) as an argument for any possible exiting value and returns Nothing to delete a value or Just v to set a new value.

minMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => g f -> Maybe (k, v) Source #

return the minimum key and value

maxMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => g f -> Maybe (k, v) Source #

return the maximum key and value

toListMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => g f -> [(k, v)] Source #

Convert a map into a list of key-value tuples.

fromListMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => [(k, v)] -> g f Source #

Convert a lst of key-value tuples into a map.

insertMapT :: (Binary k, Binary v, Ord k, f ~ Tree23 (Map k v)) => k -> v -> Transaction (Ref f) s () Source #

lookupMapT :: (Binary k, Binary v, Ord k, f ~ Tree23 (Map k v)) => k -> Transaction (Ref f) s (Maybe v) Source #

deleteMapT :: (Binary k, Binary v, Ord k, f ~ Tree23 (Map k v)) => k -> Transaction (Ref f) s () Source #

partitionMapT :: (Binary k, Ord k, Binary v, f ~ Tree23 (Map k v)) => k -> Transaction (Ref f) s (Stored s f, Stored s f) Source #

alterMapT :: (Binary k, Binary v, Ord k, f ~ Tree23 (Map k v)) => k -> (Maybe v -> Maybe v) -> Transaction (Ref f) s () Source #

FTransaction version of alterMap.

minMapT :: (Binary k, Binary v, Ord k, f ~ Tree23 (Map k v)) => Transaction (Ref f) s (Maybe (k, v)) Source #

FTransaction version of minMap.

maxMapT :: (Binary k, Binary v, Ord k, f ~ Tree23 (Map k v)) => Transaction (Ref f) s (Maybe (k, v)) Source #

FTransaction version of minMap.

keysMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => g f -> [k] Source #

Return the list of keys in a map.

valuesMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => g f -> [v] Source #

Return a list of values in a map.