hunt-searchengine-0.3.0.1: A search and indexing engine.

CopyrightCopyright (C) 2012 Sebastian M. Schlatt, Timo B. Huebel, Uwe Schmidt
LicenseMIT
MaintainerUwe Schmidt
Safe HaskellNone
LanguageHaskell98

Hunt.Common.DocIdMap

Description

Efficient Map implementation for DocIds.

Synopsis

Documentation

newtype DocIdMap v Source

An efficient Map implementation for DocIds.

Constructors

DIM 

Fields

unDIM :: IntMap v
 

empty :: DocIdMap v Source

The empty map.

singleton :: DocId -> v -> DocIdMap v Source

A map with a single element.

null :: DocIdMap v -> Bool Source

Is the map empty?

member :: DocId -> DocIdMap v -> Bool Source

Is the DocId member of the map?

lookup :: DocId -> DocIdMap v -> Maybe v Source

Lookup the value at a DocId in the map.

insert :: DocId -> v -> DocIdMap v -> DocIdMap v Source

Insert a DocId and value in the map. If the DocId is already present in the map, the associated value is replaced with the supplied value. insert is equivalent to insertWith const.

delete :: DocId -> DocIdMap v -> DocIdMap v Source

Delete a DocId and its value from the map. When the DocId is not a member of the map, the original map is returned.

insertWith :: (v -> v -> v) -> DocId -> v -> DocIdMap v -> DocIdMap v Source

Insert with a function, combining new value and old value. insertWith f docId value mp will insert the pair (docId, value) into mp if docId does not exist in the map. If the DocId does exist, the function will insert the pair (docId, f new_value old_value).

size :: DocIdMap v -> Int Source

The number of elements in the map.

sizeWithLimit :: Int -> DocIdMap v -> Maybe Int Source

The number of elements limited up to a maximum

union :: DocIdMap v -> DocIdMap v -> DocIdMap v Source

The (left-biased) union of two maps. It prefers the first map when duplicate DocId are encountered, i.e. (union == unionWith const).

intersection :: DocIdMap v -> DocIdMap v -> DocIdMap v Source

The (left-biased) intersection of two maps (based on DocIds).

difference :: DocIdMap v -> DocIdMap w -> DocIdMap v Source

Difference between two maps (based on DocIds).

diffWithSet :: DocIdMap v -> DocIdSet -> DocIdMap v Source

Difference between the map and a set of DocIds.

unionWith :: (v -> v -> v) -> DocIdMap v -> DocIdMap v -> DocIdMap v Source

The union with a combining function.

intersectionWith :: (v -> v -> v) -> DocIdMap v -> DocIdMap v -> DocIdMap v Source

The intersection with a combining function.

differenceWith :: (v -> v -> Maybe v) -> DocIdMap v -> DocIdMap v -> DocIdMap v Source

Difference with a combining function.

unionsWith :: (v -> v -> v) -> [DocIdMap v] -> DocIdMap v Source

The union of a list of maps, with a combining operation.

map :: (v -> r) -> DocIdMap v -> DocIdMap r Source

Map a function over all values in the map.

filter :: (v -> Bool) -> DocIdMap v -> DocIdMap v Source

Filter all values that satisfy some predicate.

filterWithKey :: (DocId -> v -> Bool) -> DocIdMap v -> DocIdMap v Source

Filter all DocIds/values that satisfy some predicate.

mapWithKey :: (DocId -> v -> r) -> DocIdMap v -> DocIdMap r Source

Map a function over all values in the map.

traverseWithKey :: Applicative t => (DocId -> a -> t b) -> DocIdMap a -> t (DocIdMap b) Source

traverseWithKey f s == fromList $ traverse ((k, v) -> (,) k $ f k v) (toList m) That is, behaves exactly like a regular traverse except that the traversing function also has access to the DocId associated with a value.

traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(1, 'a'), (5, 'e')]) == Just (fromList [(1, 'b'), (5, 'f')])
traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(2, 'c')])           == Nothing

foldr :: (v -> b -> b) -> b -> DocIdMap v -> b Source

Fold the values in the map using the given right-associative binary operator, such that foldr f z == foldr f z . elems.

For example,

elems map = foldr (:) [] map
let f a len = len + (length a)
foldr f 0 (fromList [(5,"a"), (3,"bbb")]) == 4

foldrWithKey :: (DocId -> v -> b -> b) -> b -> DocIdMap v -> b Source

Fold the DocIds and values in the map using the given right-associative binary operator, such that foldrWithKey f z == foldr (uncurry f) z . toAscList.

For example,

keys map = foldrWithKey (\k x ks -> k:ks) [] map
let f k a result = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
foldrWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (5:a)(3:b)"

foldl :: (b -> v -> b) -> b -> DocIdMap v -> b Source

fromList :: [(DocId, v)] -> DocIdMap v Source

Create a map from a list of DocId/value pairs.

fromDocIdSet :: (Int -> v) -> DocIdSet -> DocIdMap v Source

Create a map from a set of DocId values

fromAscList :: [(DocId, v)] -> DocIdMap v Source

Build a map from a list of DocId/value pairs where the DocIds are in ascending order.

toList :: DocIdMap v -> [(DocId, v)] Source

Convert the map to a list of DocId/value pairs. Subject to list fusion.

keys :: DocIdMap v -> [DocId] Source

Return all DocIds of the map in ascending order. Subject to list fusion.

elems :: DocIdMap v -> [v] Source

Return all elements of the map in the ascending order of their DocIds. Subject to list fusion.