| 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 |
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
- type Tree23 g d = g (TreeD d)
- type TreeD d = Tree23F (TreeKey d) (TreeValue d)
- empty :: Fixed g => Tree23 g d
- null :: Fixed g => Tree23 g d -> Bool
- size :: Fixed g => Tree23 g d -> Int
- data Set k
- createSetFile :: (Binary k, Typeable k) => FilePath -> IO (FixFile (Ref (TreeD (Set k))))
- openSetFile :: (Binary k, Typeable k) => FilePath -> IO (FixFile (Ref (TreeD (Set k))))
- insertSet :: (Fixed g, Ord k) => k -> Tree23 g (Set k) -> Tree23 g (Set k)
- lookupSet :: (Fixed g, Ord k) => k -> Tree23 g (Set k) -> Bool
- deleteSet :: (Fixed g, Ord k) => k -> Tree23 g (Set k) -> Tree23 g (Set k)
- toListSet :: (Fixed g, Ord k) => Tree23 g (Set k) -> [k]
- fromListSet :: (Fixed g, Ord k) => [k] -> Tree23 g (Set k)
- insertSetT :: (Binary k, Ord k) => k -> Transaction (Ref (TreeD (Set k))) s ()
- lookupSetT :: (Binary k, Ord k) => k -> Transaction (Ref (TreeD (Set k))) s Bool
- deleteSetT :: (Binary k, Ord k) => k -> Transaction (Ref (TreeD (Set k))) s ()
- data Map k v
- createMapFile :: (Binary k, Typeable k, Binary v, Typeable v) => FilePath -> IO (FixFile (Ref (TreeD (Map k v))))
- openMapFile :: (Binary k, Typeable k, Binary v, Typeable v) => FilePath -> IO (FixFile (Ref (TreeD (Map k v))))
- insertMap :: (Fixed g, Ord k) => k -> v -> Tree23 g (Map k v) -> Tree23 g (Map k v)
- lookupMap :: (Fixed g, Ord k) => k -> Tree23 g (Map k v) -> Maybe v
- deleteMap :: (Fixed g, Ord k) => k -> Tree23 g (Map k v) -> Tree23 g (Map k v)
- alterMap :: (Fixed g, Ord k) => k -> (Maybe v -> Maybe v) -> Tree23 g (Map k v) -> Tree23 g (Map k v)
- mapMap :: (Fixed g, Fixed h, Ord k) => (a -> b) -> Tree23 g (Map k a) -> Tree23 h (Map k b)
- toListMap :: (Fixed g, Ord k) => Tree23 g (Map k v) -> [(k, v)]
- fromListMap :: (Fixed g, Ord k) => [(k, v)] -> Tree23 g (Map k v)
- insertMapT :: (Binary k, Binary v, Ord k) => k -> v -> Transaction (Ref (TreeD (Map k v))) s ()
- lookupMapT :: (Binary k, Binary v, Ord k) => k -> Transaction (Ref (TreeD (Map k v))) s (Maybe v)
- deleteMapT :: (Binary k, Binary v, Ord k) => k -> Transaction (Ref (TreeD (Map k v))) s ()
- alterMapT :: (Binary k, Binary v, Ord k) => k -> (Maybe v -> Maybe v) -> Transaction (Ref (TreeD (Map k v))) s ()
- keysMap :: (Fixed g, Ord k) => Tree23 g (Map k v) -> [k]
- valuesMap :: (Fixed g, Ord k) => Tree23 g (Map k v) -> [v]
Documentation
null :: Fixed g => Tree23 g d -> Bool Source
Predicate that returns true if there are no items in the Tree23.
- Set
createSetFile :: (Binary k, Typeable k) => FilePath -> IO (FixFile (Ref (TreeD (Set k)))) Source
Create a FixFile for storing a set of items.
openSetFile :: (Binary k, Typeable k) => FilePath -> IO (FixFile (Ref (TreeD (Set k)))) Source
Open a FixFile for storing a set of items.
insertSet :: (Fixed g, Ord k) => k -> Tree23 g (Set k) -> Tree23 g (Set k) Source
Insert an item into a set.
deleteSet :: (Fixed g, Ord k) => k -> Tree23 g (Set k) -> Tree23 g (Set k) Source
Delete an item from a set.
fromListSet :: (Fixed g, Ord k) => [k] -> Tree23 g (Set k) Source
Convert a list of items into a set.
insertSetT :: (Binary k, Ord k) => k -> Transaction (Ref (TreeD (Set k))) s () Source
Transaction version of insertSet.
lookupSetT :: (Binary k, Ord k) => k -> Transaction (Ref (TreeD (Set k))) s Bool Source
FTransaction version of lookupSet.
deleteSetT :: (Binary k, Ord k) => k -> Transaction (Ref (TreeD (Set k))) s () Source
FTransaction version of deleteSet.
- Map
createMapFile :: (Binary k, Typeable k, Binary v, Typeable v) => FilePath -> IO (FixFile (Ref (TreeD (Map k v)))) Source
Create a FixFile of a Map.
openMapFile :: (Binary k, Typeable k, Binary v, Typeable v) => FilePath -> IO (FixFile (Ref (TreeD (Map k v)))) Source
Open a FixFile of a Map.
insertMap :: (Fixed g, Ord k) => k -> v -> Tree23 g (Map k v) -> Tree23 g (Map k v) Source
Insert value v into a map for key k. Any existing value is replaced.
lookupMap :: (Fixed g, Ord k) => k -> Tree23 g (Map k v) -> Maybe v Source
Lookup an item in a map corresponding to key k.
deleteMap :: (Fixed g, Ord k) => k -> Tree23 g (Map k v) -> Tree23 g (Map k v) Source
Delete an item from a map at key k.
alterMap :: (Fixed g, Ord k) => k -> (Maybe v -> Maybe v) -> Tree23 g (Map k v) -> Tree23 g (Map k v) 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.
mapMap :: (Fixed g, Fixed h, Ord k) => (a -> b) -> Tree23 g (Map k a) -> Tree23 h (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) => Tree23 g (Map k v) -> [(k, v)] Source
Convert a map into a list of key-value tuples.
fromListMap :: (Fixed g, Ord k) => [(k, v)] -> Tree23 g (Map k v) Source
Convert a lst of key-value tuples into a map.
insertMapT :: (Binary k, Binary v, Ord k) => k -> v -> Transaction (Ref (TreeD (Map k v))) s () Source
Transaction version of insertMap.
lookupMapT :: (Binary k, Binary v, Ord k) => k -> Transaction (Ref (TreeD (Map k v))) s (Maybe v) Source
Transaction version of lookupMap.
deleteMapT :: (Binary k, Binary v, Ord k) => k -> Transaction (Ref (TreeD (Map k v))) s () Source
Transaction version of deleteMap.