Data.Map.TernaryMap
- data TernaryMap k v
 - insert :: Ord k => [k] -> v -> TernaryMap k v -> TernaryMap k v
 - singleton :: Ord k => [k] -> v -> TernaryMap k v
 - member :: Ord k => [k] -> TernaryMap k v -> Bool
 - size :: TernaryMap k v -> Int
 - fromList :: Ord k => [([k], v)] -> TernaryMap k v
 - lookup :: Ord k => [k] -> TernaryMap k v -> Maybe v
 - (!) :: Ord k => TernaryMap k v -> [k] -> Maybe v
 - findWithDefault :: Ord k => v -> [k] -> TernaryMap k v -> v
 - insertWith :: Ord k => (v -> v -> v) -> [k] -> v -> TernaryMap k v -> TernaryMap k v
 - insertWithKey :: Ord k => ([k] -> v -> v -> v) -> [k] -> v -> TernaryMap k v -> TernaryMap k v
 - keys :: TernaryMap k v -> [[k]]
 - assocs :: TernaryMap k v -> [([k], v)]
 - elems :: TernaryMap k v -> [v]
 - null :: TernaryMap k v -> Bool
 
Documentation
data TernaryMap k v Source
TernaryMap k v is ternary tree. It is commonly used for storing word lists like dictionaries.
Instances
| Functor (TernaryMap k) | |
| (Eq k, Eq v) => Eq (TernaryMap k v) | |
| (Show k, Show v) => Show (TernaryMap k v) | |
| (Binary k, Binary v) => Binary (TernaryMap k v) | A rather long Binary instance, that uses binary numbers to indicate where Ends are efficiently.  | 
insert :: Ord k => [k] -> v -> TernaryMap k v -> TernaryMap k vSource
Inserts an entrie into a tree. Values with the same key will be replaced with the newer value.
singleton :: Ord k => [k] -> v -> TernaryMap k vSource
Quickly build a tree without an initial tree. This should be used to create an initial tree, using insert there after.
member :: Ord k => [k] -> TernaryMap k v -> BoolSource
Returns true if the `[k]` is a key in the TernaryMap.
size :: TernaryMap k v -> IntSource
Counts how many entries there are in the tree.
fromList :: Ord k => [([k], v)] -> TernaryMap k vSource
Creates a new tree from a list of strings
lookup :: Ord k => [k] -> TernaryMap k v -> Maybe vSource
(!) :: Ord k => TernaryMap k v -> [k] -> Maybe vSource
findWithDefault :: Ord k => v -> [k] -> TernaryMap k v -> vSource
insertWith :: Ord k => (v -> v -> v) -> [k] -> v -> TernaryMap k v -> TernaryMap k vSource
Inserts a new value into the tree with a given function that combines the new value and the old value together to for a new entry.
insertWith f key newval (fromList [(notkey,val1),(key,oldval)]) == fromList [(notkey,val1),(key,f newval oldval)]
insertWithKey :: Ord k => ([k] -> v -> v -> v) -> [k] -> v -> TernaryMap k v -> TernaryMap k vSource
Inserts a new value into the tree with a given function that combines the new value and the old value together to for a new entry.
insertWithKey f key newval (fromList [(notkey,val1),(key,oldval)]) == fromList [(notkey,val1),(key,f key newval oldval)]
keys :: TernaryMap k v -> [[k]]Source
Returns a (sorted) list of all keys in the map.
assocs :: TernaryMap k v -> [([k], v)]Source
Returns a (sorted) list of all keys in the map.
elems :: TernaryMap k v -> [v]Source
Makes a list of all the values in the map.
null :: TernaryMap k v -> BoolSource
Returns true if the map is empty.