Portability | not portable |
---|---|
Stability | experimental |
Maintainer | Uwe Schmidt ([email protected]) |
Safe Haskell | Safe-Inferred |
Data.StringMap.Strict
Contents
Description
An efficient implementation of maps from strings to arbitrary values.
Values can associated with an arbitrary byte key. Searching for keys is very fast, but
the prefix tree probably consumes more memory than Data.Map. The main differences are the special
prefixFind
functions, which can be used to perform prefix queries. The interface is
heavily borrowed from Data.Map and Data.IntMap.
Most other function names clash with Prelude names, therefore this module is usually
imported qualified
, e.g.
import Data.StringMap (StringMap) import qualified Data.StringMap as T
Many functions have a worst-case complexity of O(min(n,L)). This means that the operation can become linear with the number of elements with a maximum of L, the length of the key (the number of bytes in the list). The functions for searching a prefix have a worst-case complexity of O(max(L,R)). This means that the operation can become linear with R, the number of elements found for the prefix, with a minimum of L.
The module exports include the internal data types, their constructors and access functions for ultimate flexibility. Derived modules should not export these (as shown in Holumbus.Data.StrMap) to provide only a restricted interface.
- data StringMap v
- type Key = [Sym]
- (!) :: StringMap a -> Key -> a
- value :: Monad m => StringMap a -> m a
- valueWithDefault :: a -> StringMap a -> a
- null :: StringMap a -> Bool
- size :: StringMap a -> Int
- member :: Key -> StringMap a -> Bool
- lookup :: Monad m => Key -> StringMap a -> m a
- findWithDefault :: a -> Key -> StringMap a -> a
- prefixFind :: Key -> StringMap a -> [a]
- prefixFindWithKey :: Key -> StringMap a -> [(Key, a)]
- prefixFindWithKeyBF :: Key -> StringMap a -> [(Key, a)]
- empty :: StringMap v
- singleton :: Key -> a -> StringMap a
- insert :: Key -> a -> StringMap a -> StringMap a
- insertWith :: (a -> a -> a) -> Key -> a -> StringMap a -> StringMap a
- insertWithKey :: (Key -> a -> a -> a) -> Key -> a -> StringMap a -> StringMap a
- delete :: Key -> StringMap a -> StringMap a
- update :: (a -> Maybe a) -> Key -> StringMap a -> StringMap a
- updateWithKey :: (Key -> a -> Maybe a) -> Key -> StringMap a -> StringMap a
- union :: StringMap a -> StringMap a -> StringMap a
- unionWith :: (a -> a -> a) -> StringMap a -> StringMap a -> StringMap a
- unionWithKey :: (Key -> a -> a -> a) -> StringMap a -> StringMap a -> StringMap a
- difference :: StringMap a -> StringMap b -> StringMap a
- differenceWith :: (a -> b -> Maybe a) -> StringMap a -> StringMap b -> StringMap a
- differenceWithKey :: (Key -> a -> b -> Maybe a) -> StringMap a -> StringMap b -> StringMap a
- map :: (a -> b) -> StringMap a -> StringMap b
- mapWithKey :: (Key -> a -> b) -> StringMap a -> StringMap b
- mapM :: Monad m => (a -> m b) -> StringMap a -> m (StringMap b)
- mapWithKeyM :: Monad m => (Key -> a -> m b) -> StringMap a -> m (StringMap b)
- mapMaybe :: (a -> Maybe b) -> StringMap a -> StringMap b
- fold :: (a -> b -> b) -> b -> StringMap a -> b
- foldWithKey :: (Key -> a -> b -> b) -> b -> StringMap a -> b
- keys :: StringMap a -> [Key]
- elems :: StringMap a -> [a]
- fromList :: [(Key, a)] -> StringMap a
- toList :: StringMap a -> [(Key, a)]
- toListBF :: StringMap v -> [(Key, v)]
- fromMap :: Map Key a -> StringMap a
- toMap :: StringMap a -> Map Key a
- space :: StringMap a -> Int
- keyChars :: StringMap a -> Int
- prefixFindCaseWithKey :: Key -> StringMap a -> [(Key, a)]
- prefixFindNoCaseWithKey :: Key -> StringMap a -> [(Key, a)]
- prefixFindNoCase :: Key -> StringMap a -> [a]
- lookupNoCase :: Key -> StringMap a -> [(Key, a)]
- prefixFindCaseWithKeyBF :: Key -> StringMap a -> [(Key, a)]
- prefixFindNoCaseWithKeyBF :: Key -> StringMap a -> [(Key, a)]
- lookupNoCaseBF :: Key -> StringMap a -> [(Key, a)]
Map type
Operators
(!) :: StringMap a -> Key -> aSource
O(min(n,L)) Find the value at a key. Calls error when the element can not be found.
Query
value :: Monad m => StringMap a -> m aSource
O(1) Extract the value of a node (if there is one) TODO: INTERNAL
valueWithDefault :: a -> StringMap a -> aSource
O(1) Extract the value of a node or return a default value if no value exists.
lookup :: Monad m => Key -> StringMap a -> m aSource
O(min(n,L)) Find the value associated with a key. The function will return
the result in
the monad or fail
in it if the key isn't in the map.
findWithDefault :: a -> Key -> StringMap a -> aSource
O(min(n,L)) Find the value associated with a key. The function will return
the result in
the monad or fail
in it if the key isn't in the map.
prefixFind :: Key -> StringMap a -> [a]Source
O(max(L,R)) Find all values where the string is a prefix of the key.
prefixFindWithKey :: Key -> StringMap a -> [(Key, a)]Source
O(max(L,R)) Find all values where the string is a prefix of the key and include the keys in the result.
prefixFindWithKeyBF :: Key -> StringMap a -> [(Key, a)]Source
O(max(L,R)) Find all values where the string is a prefix of the key and include the keys in the result. The result list contains short words first
Construction
Insertion
insert :: Key -> a -> StringMap a -> StringMap aSource
O(min(n,L)) Insert a new key and value into the map. If the key is already present in the map, the associated value will be replaced with the new value.
insertWith :: (a -> a -> a) -> Key -> a -> StringMap a -> StringMap aSource
O(min(n,L)) Insert with a combining function. If the key is already present in the map,
the value of f new_value old_value
will be inserted.
insertWithKey :: (Key -> a -> a -> a) -> Key -> a -> StringMap a -> StringMap aSource
O(min(n,L)) Insert with a combining function. If the key is already present in the map,
the value of f key new_value old_value
will be inserted.
Delete/Update
delete :: Key -> StringMap a -> StringMap aSource
O(min(n,L)) Delete an element from the map. If no element exists for the key, the map remains unchanged.
update :: (a -> Maybe a) -> Key -> StringMap a -> StringMap aSource
O(min(n,L)) Updates a value at a given key (if that key is in the trie) or deletes the
element if the result of the updating function is Nothing
. If the key is not found, the trie
is returned unchanged.
updateWithKey :: (Key -> a -> Maybe a) -> Key -> StringMap a -> StringMap aSource
O(min(n,L)) Updates a value at a given key (if that key is in the trie) or deletes the
element if the result of the updating function is Nothing
. If the key is not found, the trie
is returned unchanged.
Combine
Union
unionWith :: (a -> a -> a) -> StringMap a -> StringMap a -> StringMap aSource
O(n+m) Union with a combining function.
unionWithKey :: (Key -> a -> a -> a) -> StringMap a -> StringMap a -> StringMap aSource
O(n+m) Union with a combining function, including the key.
Difference
difference :: StringMap a -> StringMap b -> StringMap aSource
(O(min(n,m)) Difference between two tries (based on keys).
differenceWith :: (a -> b -> Maybe a) -> StringMap a -> StringMap b -> StringMap aSource
(O(min(n,m)) Difference with a combining function. If the combining function always returns
Nothing
, this is equal to proper set difference.
Traversal
Map
map :: (a -> b) -> StringMap a -> StringMap bSource
O(n) Map a function over all values in the prefix tree.
mapWithKey :: (Key -> a -> b) -> StringMap a -> StringMap bSource
mapWithKeyM :: Monad m => (Key -> a -> m b) -> StringMap a -> m (StringMap b)Source
Monadic mapWithKey
mapMaybe :: (a -> Maybe b) -> StringMap a -> StringMap bSource
O(n) Updates a value or deletes the element if the result of the updating function is Nothing
.
Folds
foldWithKey :: (Key -> a -> b -> b) -> b -> StringMap a -> bSource
O(n) Fold over all key/value pairs in the map.
Conversion
Lists
toListBF :: StringMap v -> [(Key, v)]Source
returns all key-value pairs in breadth first order (short words first)
this enables prefix search with upper bounds on the size of the result set
e.g. search ... >>> toListBF >>> take 1000
will give the 1000 shortest words
found in the result set and will ignore all long words
toList is derived from the following code found in the net when searching haskell breadth first search
Haskell Standard Libraray Implementation
br :: Tree a -> [a] br t = map rootLabel $ concat $ takeWhile (not . null) $ iterate (concatMap subForest) [t]
Maps
Debugging
space :: StringMap a -> IntSource
space required by a prefix tree (logically)
Singletons are counted as 0, all other n-ary constructors are counted as n+1 (1 for the constructor and 1 for every field) cons nodes of char lists are counted 2, 1 for the cons, 1 for the char for values only the ref to the value is counted, not the space for the value itself key chars are assumed to be unboxed
Prefix and Fuzzy Search
prefixFindCaseWithKey :: Key -> StringMap a -> [(Key, a)]Source
O(max(L,R)) Find all values where the string is a prefix of the key.
prefixFindNoCaseWithKey :: Key -> StringMap a -> [(Key, a)]Source
prefixFindNoCase :: Key -> StringMap a -> [a]Source
lookupNoCase :: Key -> StringMap a -> [(Key, a)]Source
prefixFindCaseWithKeyBF :: Key -> StringMap a -> [(Key, a)]Source
O(max(L,R)) Find all values where the string is a prefix of the key. Breadth first variant, short words first in the result list
prefixFindNoCaseWithKeyBF :: Key -> StringMap a -> [(Key, a)]Source
lookupNoCaseBF :: Key -> StringMap a -> [(Key, a)]Source