data-stringmap-1.0.1.1: An efficient implementation of maps from strings to arbitrary values

Portabilitynot portable
Stabilityexperimental
MaintainerUwe Schmidt (uwe@fh-wedel.de), Sebastian Philipp (sebastian@spawnhost.de)
Safe HaskellSafe-Inferred

Data.StringMap.Strict

Contents

Description

An efficient implementation of maps from strings to arbitrary values.

Values can be associated with an arbitrary [Char] key. Searching for keys is very fast. The main differences to Data.Map and Data.IntMap 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.Strict (StringMap)
 import qualified Data.StringMap.Strict as M

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.

This module has versions of the "modifying" operations, like insert, update, delete and map, that force evaluating the attribute values before doing the operation. All "reading" operations and the data types are reexported from Data.StringMap.Base.

Synopsis

Map type

type Key = [Sym]Source

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)

valueWithDefault :: a -> StringMap a -> aSource

O(1) Extract the value of a node or return a default value if no value exists.

null :: StringMap a -> BoolSource

O(1) Is the map empty?

size :: StringMap a -> IntSource

O(n) The number of elements.

member :: Key -> StringMap a -> BoolSource

O(min(n,L)) Is the key a member of the map?

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

Deprecated: use toList . prefixFilter instead

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

Deprecated: use toListShortestFirst . prefixFilter instead

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

lookupRange :: Key -> Key -> StringMap a -> StringMap aSource

Combination of lookupLE and lookupGE

 keys $ lookupRange "a" "b" $ fromList $ zip ["", "a", "ab", "b", "ba", "c"] [1..] = ["a","ab","b"]

For all keys in k = keys $ lookupRange lb ub m, this property holts true: k >= ub && k <= lb

Construction

empty :: StringMap vSource

Creates an empty string map

 null $ empty == True

singleton :: Key -> a -> StringMap aSource

O(1) Create a map with a single element.

the attribute value is evaluated to WHNF

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

adjust :: (a -> a) -> Key -> StringMap a -> StringMap aSource

adjustWithKey :: (Key -> a -> a) -> Key -> StringMap a -> StringMap aSource

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. The updated value is evaluated to WHNF before insertion.

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. The updated value is evaluated to WHNF before insertion.

Combine

Union

union :: StringMap a -> StringMap a -> StringMap aSource

O(n+m) Left-biased union of two maps. It prefers the first map when duplicate keys are encountered, i.e. (union == unionWith const).

unionWith :: (a -> a -> a) -> StringMap a -> StringMap a -> StringMap aSource

O(n+m) union with a combining function.

unionMapWith :: (b -> a) -> (a -> b -> a) -> StringMap a -> StringMap b -> StringMap aSource

Generalisation of unionWith. The second map may have another attribute type than the first one. Conversion and merging of the maps is done in a single step. This is much more efficient than mapping the second map and then call unionWith

unionWithConf to ( x y -> x op to y) m1 m2 = unionWith op m1 (fmap to m2)

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 string maps (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.

differenceWithKey :: (Key -> a -> b -> Maybe a) -> StringMap a -> StringMap b -> StringMap aSource

O(min(n,m)) difference with a combining function, including the key. If two equal keys are encountered, the combining function is applied to the key and both values. If it returns Nothing, the element is discarded, if it returns Just a value, the element is updated with the new value.

Interset

intersection :: StringMap a -> StringMap a -> StringMap aSource

O(min(n,m)) intersection is required to allow all major set operations: AND = intersection OR = union AND NOT = difference

intersectionWith :: (a -> b -> c) -> StringMap a -> StringMap b -> StringMap cSource

O(min(n,m)) intersection with a modification function

Traversal

Map

map :: (a -> b) -> StringMap a -> StringMap bSource

O(n) Map a function over all values in the string map.

mapWithKey :: (Key -> a -> b) -> StringMap a -> StringMap bSource

O(n) Same as map, but with an additional paramter

mapM :: Monad m => (a -> m b) -> StringMap a -> m (StringMap b)Source

Monadic map

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

fold :: (a -> b -> b) -> b -> StringMap a -> bSource

Deprecated: use foldr instead

O(n) Fold over all values in the map.

foldWithKey :: (Key -> a -> b -> b) -> b -> StringMap a -> bSource

Deprecated: use foldrWithKey instead

O(n) Fold over all key/value pairs in the map.

foldr :: (a -> b -> b) -> b -> StringMap a -> bSource

O(n) Right fold over all values in the map.

foldrWithKey :: (Key -> a -> b -> b) -> b -> StringMap a -> bSource

O(n) Right fold over all keys and values in the map.

foldl :: (b -> a -> b) -> b -> StringMap a -> bSource

O(n) Left fold over all values in the map.

foldlWithKey :: (b -> Key -> a -> b) -> b -> StringMap a -> bSource

O(n) Left fold over all keys and values in the map.

Conversion

keys :: StringMap a -> [Key]Source

O(n) Returns all keys.

elems :: StringMap a -> [a]Source

O(n) Returns all values.

Lists

fromList :: [(Key, a)] -> StringMap aSource

O(n) Creates a string map from a list of key/value pairs.

toList :: StringMap a -> [(Key, a)]Source

O(n) Returns all elements as list of key value pairs,

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

fromMap :: Map Key a -> StringMap aSource

O(n) Convert an ordinary map into a string map

toMap :: StringMap a -> Map Key aSource

O(n) Convert into an ordinary map.

Prefix and Fuzzy Search

prefixFilter :: Key -> StringMap a -> StringMap aSource

O(max(L,R)) Find all values where the string is a prefix of the key.

prefixFilterNoCase :: Key -> StringMap a -> StringMap aSource

Same as prefixFilterNoCase, bur case insensitive

lookupNoCase :: Key -> StringMap a -> StringMap aSource

Same as lookup, but case insensitive