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 an implementation of a Two-Three Tree data structure that can be
used with FixFile
. It has two interfaces that are
- type Tree23 d = Tree23F (TreeKey d) (TreeValue d)
- empty :: Fixed g => g (Tree23 d)
- null :: Fixed g => g (Tree23 d) -> Bool
- size :: Fixed g => g (Tree23 d) -> Int
- depth :: Fixed g => g (Tree23 d) -> Int
- data Set k
- createSetFile :: (Binary k, Typeable k, f ~ Tree23 (Set k)) => FilePath -> IO (FixFile (Ref f))
- openSetFile :: (Binary k, Typeable k, f ~ Tree23 (Set k)) => FilePath -> IO (FixFile (Ref f))
- insertSet :: (Fixed g, Ord k, f ~ Tree23 (Set k)) => k -> g f -> g f
- lookupSet :: (Fixed g, Ord k, f ~ Tree23 (Set k)) => k -> g f -> Bool
- deleteSet :: (Fixed g, Ord k, f ~ Tree23 (Set k)) => k -> g f -> g f
- partitionSet :: (Fixed g, Ord k, f ~ Tree23 (Set k)) => k -> g f -> (g f, g f)
- minSet :: (Fixed g, Ord k, f ~ Tree23 (Set k)) => g f -> Maybe k
- maxSet :: (Fixed g, Ord k, f ~ Tree23 (Set k)) => g f -> Maybe k
- toListSet :: (Fixed g, Ord k, f ~ Tree23 (Set k)) => g f -> [k]
- fromListSet :: (Fixed g, Ord k, f ~ Tree23 (Set k)) => [k] -> g f
- insertSetT :: (Binary k, Ord k, f ~ Tree23 (Set k)) => k -> Transaction (Ref f) s ()
- lookupSetT :: (Binary k, Ord k, f ~ Tree23 (Set k)) => k -> Transaction (Ref f) s Bool
- deleteSetT :: (Binary k, Ord k, f ~ Tree23 (Set k)) => k -> Transaction (Ref f) s ()
- partitionSetT :: (Binary k, Ord k, f ~ Tree23 (Set k)) => k -> Transaction (Ref f) s (Stored s f, Stored s f)
- minSetT :: (Binary k, Ord k, f ~ Tree23 (Set k)) => Transaction (Ref f) s (Maybe k)
- maxSetT :: (Binary k, Ord k, f ~ Tree23 (Set k)) => Transaction (Ref f) s (Maybe k)
- data Map k v
- createMapFile :: (Binary k, Typeable k, Binary v, Typeable v, f ~ Tree23 (Map k v)) => FilePath -> IO (FixFile (Ref f))
- openMapFile :: (Binary k, Typeable k, Binary v, Typeable v, f ~ Tree23 (Map k v)) => FilePath -> IO (FixFile (Ref f))
- insertMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => k -> v -> g f -> g f
- lookupMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => k -> g f -> Maybe v
- deleteMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => k -> g f -> g f
- partitionMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => k -> g f -> (g f, g f)
- alterMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => k -> (Maybe v -> Maybe v) -> g f -> g f
- minMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => g f -> Maybe (k, v)
- maxMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => g f -> Maybe (k, v)
- toListMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => g f -> [(k, v)]
- fromListMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => [(k, v)] -> g f
- insertMapT :: (Binary k, Binary v, Ord k, f ~ Tree23 (Map k v)) => k -> v -> Transaction (Ref f) s ()
- lookupMapT :: (Binary k, Binary v, Ord k, f ~ Tree23 (Map k v)) => k -> Transaction (Ref f) s (Maybe v)
- deleteMapT :: (Binary k, Binary v, Ord k, f ~ Tree23 (Map k v)) => k -> Transaction (Ref f) s ()
- partitionMapT :: (Binary k, Ord k, Binary v, f ~ Tree23 (Map k v)) => k -> Transaction (Ref f) s (Stored s f, Stored s f)
- alterMapT :: (Binary k, Binary v, Ord k, f ~ Tree23 (Map k v)) => k -> (Maybe v -> Maybe v) -> Transaction (Ref f) s ()
- minMapT :: (Binary k, Binary v, Ord k, f ~ Tree23 (Map k v)) => Transaction (Ref f) s (Maybe (k, v))
- maxMapT :: (Binary k, Binary v, Ord k, f ~ Tree23 (Map k v)) => Transaction (Ref f) s (Maybe (k, v))
- keysMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => g f -> [k]
- valuesMap :: (Fixed g, Ord k, f ~ Tree23 (Map k v)) => g f -> [v]
Documentation
null :: Fixed g => g (Tree23 d) -> Bool Source #
Predicate that returns true if there are no items in the Tree23
.
depth :: Fixed g => g (Tree23 d) -> Int Source #
The depth of (
. Tree23
g d)0
represents en empty Tree.
- Set
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 #
Transaction
version of insertSet
.
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 #
Transaction
version of partitionSet
.
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
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
(
as an argument for any possible exiting value and returns
Maybe
v)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 #
Transaction
version of insertMap
.
lookupMapT :: (Binary k, Binary v, Ord k, f ~ Tree23 (Map k v)) => k -> Transaction (Ref f) s (Maybe v) Source #
Transaction
version of lookupMap
.
deleteMapT :: (Binary k, Binary v, Ord k, f ~ Tree23 (Map k v)) => k -> Transaction (Ref f) s () Source #
Transaction
version of deleteMap
.
partitionMapT :: (Binary k, Ord k, Binary v, f ~ Tree23 (Map k v)) => k -> Transaction (Ref f) s (Stored s f, Stored s f) Source #
Transaction
version of partitionMap
.
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
.