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

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

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

  • Map

data Map k v Source

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

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.

mapMap :: (Fixed g, Fixed h, Ord k) => (a -> b) -> g (Tree23 (Map k a)) -> h (Tree23 (Map k b)) Source

Map a function over a map. Because of the way Tree23 is implemented, it is not possible to create a Functor instance to achieve this.

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.

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.

partitionTree23 :: (Fixed g, Ord (TreeKey d)) => TreeKey d -> g (Tree23 d) -> (g (Tree23 d), g (Tree23 d)) Source