IntervalMap-0.2.0: Maps from Intervals to values, with efficient search.

Portabilityportable
Stabilityexperimental
Maintainerchbreitkopf@googlemail.com

Data.IntervalMap

Contents

Description

An implementation of maps from intervals to values. The key intervals may overlap, and the implementation supports an efficient stabbing query.

Since many function names (but not the type name) clash with Prelude names, this module is usually imported qualified, e.g.

  import Data.IntervalMap (IvMap)
  import qualified Data.IntervalMap as IvMap

It offers most of the functions in Data.Map, but Interval k instead of just k as the key type. Some of the functions need stricter type constraints to maintain the additional information for efficient interval searching, for example fromDistinctAscList needs an Ord k constraint.

Index-based access and some set functions have not been implemented, and many non-core functions, for example the set operations, have not been tuned for efficiency yet.

In addition, there are functions specific to maps of intervals, for example to search for all keys containing a given point or contained in a given interval.

To stay compatible with standard Haskell, this implementation uses a fixed data type for intervals, and not a multi-parameter type class. Thus, it's currently not possible to define e.g. a 2-tuple as an instance of interval and use that map key. Instead you must convert your keys to Data.IntervalMap.Interval.

Closed, open, and half-open intervals can be contained in the same map.

It is an error to insert an empty interval into a map. This precondition is not checked by the various insertion functions.

The implementation is a red-black tree augmented with the maximum upper bound of all keys.

Parts of this implementation are based on code from the Data.Map implementation, (c) Daan Leijen 2002, (c) Andriy Palamarchuk 2008. The red-black tree deletion is based on code from llrbtree by Kazu Yamamoto. Of course, any errors are mine.

Synopsis

re-export

data Interval a Source

Intervals with endpoints of type a.

Read and Show use mathematical notation with square brackets for closed and parens for open intervals. This is better for human readability, but is not a valid Haskell expression. Closed intervals look like a list, open intervals look like a tuple, and half-open intervals look like mismatched parens.

Constructors

IntervalCO !a !a

Including lower bound, excluding upper

ClosedInterval !a !a

Closed at both ends

OpenInterval !a !a

Open at both ends

IntervalOC !a !a

Excluding lower bound, including upper

Instances

Functor Interval 
Eq a => Eq (Interval a) 
Ord a => Ord (Interval a) 
Read a => Read (Interval a) 
Show a => Show (Interval a) 
NFData a => NFData (Interval a) 

Map type

data IntervalMap k v Source

A map from intervals with endpoints of type k to values of type v.

Instances

Functor (IntervalMap k) 
Foldable (IntervalMap k) 
Traversable (IntervalMap k) 
(Eq k, Eq v) => Eq (IntervalMap k v) 
(Ord k, Ord v) => Ord (IntervalMap k v) 
(Ord k, Read k, Read e) => Read (IntervalMap k e) 
(Show k, Show a) => Show (IntervalMap k a) 
Ord k => Monoid (IntervalMap k v) 
(NFData k, NFData a) => NFData (IntervalMap k a) 

Operators

(!) :: Ord k => IntervalMap k v -> Interval k -> vSource

Lookup value for given key. Calls error if the key is not in the map.

(\\) :: Ord k => IntervalMap k a -> IntervalMap k b -> IntervalMap k aSource

Same as difference.

Query

null :: IntervalMap k v -> BoolSource

Is the map empty?

size :: IntervalMap k v -> IntSource

Number of keys in the map.

member :: Ord k => Interval k -> IntervalMap k v -> BoolSource

Does the map contain the given key? See also notMember.

notMember :: Ord k => Interval k -> IntervalMap k v -> BoolSource

Does the map not contain the given key? See also member.

lookup :: Ord k => Interval k -> IntervalMap k v -> Maybe vSource

Look up the given key in the map, returning the value (Just value), or 'Nothing if the key is not in the map.

findWithDefault :: Ord k => a -> Interval k -> IntervalMap k a -> aSource

O(log n). The expression (findWithDefault def k map) returns the value at key k or returns default value def when the key is not in the map.

 findWithDefault 'x' 1 (fromList [(5,'a'), (3,'b')]) == 'x'
 findWithDefault 'x' 5 (fromList [(5,'a'), (3,'b')]) == 'a'

Interval query

containing :: Ord k => IntervalMap k v -> k -> [(Interval k, v)]Source

Return all key/value pairs where the key intervals contain the given point. The elements are returned in ascending key order.

intersecting :: Ord k => IntervalMap k v -> Interval k -> [(Interval k, v)]Source

Return all key/value pairs where the key intervals overlap (intersect) the given interval. The order in which the elements are returned is undefined.

within :: Ord k => IntervalMap k v -> Interval k -> [(Interval k, v)]Source

Return all key/value pairs where the key intervals are completely inside the given interval. The order in which the elements are returned is undefined.

Construction

empty :: IntervalMap k vSource

The empty map.

singleton :: Interval k -> v -> IntervalMap k vSource

A map with one entry.

Insertion

insert :: Ord k => Interval k -> v -> IntervalMap k v -> IntervalMap k vSource

Insert a new key/value pair. If the map already contains the key, its value is changed to the new value.

insertWith :: Ord k => (v -> v -> v) -> Interval k -> v -> IntervalMap k v -> IntervalMap k vSource

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

insertWith' :: Ord k => (v -> v -> v) -> Interval k -> v -> IntervalMap k v -> IntervalMap k vSource

Same as insertWith, but the combining function is applied strictly. This is often the most desirable behavior.

insertWithKey :: Ord k => (Interval k -> v -> v -> v) -> Interval k -> v -> IntervalMap k v -> IntervalMap k vSource

Insert with a function, combining key, new value and old value. insertWithKey f key value mp will insert the pair (key, value) into mp if key does not exist in the map. If the key does exist, the function will insert the pair (key,f key new_value old_value). Note that the key passed to f is the same key passed to insertWithKey.

insertWithKey' :: Ord k => (Interval k -> v -> v -> v) -> Interval k -> v -> IntervalMap k v -> IntervalMap k vSource

Same as insertWithKey, but the combining function is applied strictly.

insertLookupWithKey :: Ord k => (Interval k -> v -> v -> v) -> Interval k -> v -> IntervalMap k v -> (Maybe v, IntervalMap k v)Source

Combine insert with old values retrieval.

insertLookupWithKey' :: Ord k => (Interval k -> v -> v -> v) -> Interval k -> v -> IntervalMap k v -> (Maybe v, IntervalMap k v)Source

Combine insert with old values retrieval.

Delete/Update

delete :: Ord k => Interval k -> IntervalMap k v -> IntervalMap k vSource

Delete a key from the map. If the map does not contain the key, it is returned unchanged.

adjust :: Ord k => (a -> a) -> Interval k -> IntervalMap k a -> IntervalMap k aSource

Update a value at a specific key with the result of the provided function. When the key is not a member of the map, the original map is returned.

adjustWithKey :: Ord k => (Interval k -> a -> a) -> Interval k -> IntervalMap k a -> IntervalMap k aSource

Adjust a value at a specific key. When the key is not a member of the map, the original map is returned.

update :: Ord k => (a -> Maybe a) -> Interval k -> IntervalMap k a -> IntervalMap k aSource

The expression (update f k map) updates the value x at k (if it is in the map). If (f x) is Nothing, the element is deleted. If it is (Just y), the key k is bound to the new value y.

updateWithKey :: Ord k => (Interval k -> a -> Maybe a) -> Interval k -> IntervalMap k a -> IntervalMap k aSource

The expression (updateWithKey f k map) updates the value x at k (if it is in the map). If (f k x) is Nothing, the element is deleted. If it is (Just y), the key k is bound to the new value y.

updateLookupWithKey :: Ord k => (Interval k -> a -> Maybe a) -> Interval k -> IntervalMap k a -> (Maybe a, IntervalMap k a)Source

Lookup and update. See also updateWithKey. The function returns changed value, if it is updated. Returns the original key value if the map entry is deleted.

alter :: Ord k => (Maybe a -> Maybe a) -> Interval k -> IntervalMap k a -> IntervalMap k aSource

The expression (alter f k map) alters the value x at k, or absence thereof. alter can be used to insert, delete, or update a value in a Map. In short : lookup k (alter f k m) = f (lookup k m).

Combine

Union

union :: Ord k => IntervalMap k a -> IntervalMap k a -> IntervalMap k aSource

The expression (union t1 t2) takes the left-biased union of t1 and t2. It prefers t1 when duplicate keys are encountered, i.e. (union == unionWith const).

unionWith :: Ord k => (a -> a -> a) -> IntervalMap k a -> IntervalMap k a -> IntervalMap k aSource

Union with a combining function.

unionWithKey :: Ord k => (Interval k -> a -> a -> a) -> IntervalMap k a -> IntervalMap k a -> IntervalMap k aSource

Union with a combining function.

unions :: Ord k => [IntervalMap k a] -> IntervalMap k aSource

The union of a list of maps: (unions == Prelude.foldl union empty).

unionsWith :: Ord k => (a -> a -> a) -> [IntervalMap k a] -> IntervalMap k aSource

The union of a list of maps, with a combining operation: (unionsWith f == Prelude.foldl (unionWith f) empty).

Difference

difference :: Ord k => IntervalMap k a -> IntervalMap k b -> IntervalMap k aSource

Difference of two maps. Return elements of the first map not existing in the second map.

differenceWith :: Ord k => (a -> b -> Maybe a) -> IntervalMap k a -> IntervalMap k b -> IntervalMap k aSource

Difference with a combining function. When two equal keys are encountered, the combining function is applied to the values of these keys. If it returns Nothing, the element is discarded (proper set difference). If it returns (Just y), the element is updated with a new value y.

differenceWithKey :: Ord k => (Interval k -> a -> b -> Maybe a) -> IntervalMap k a -> IntervalMap k b -> IntervalMap k aSource

Difference with a combining function. When two equal keys are encountered, the combining function is applied to the key and both values. If it returns Nothing, the element is discarded (proper set difference). If it returns (Just y), the element is updated with a new value y.

Intersection

intersection :: Ord k => IntervalMap k a -> IntervalMap k b -> IntervalMap k aSource

Intersection of two maps. Return data in the first map for the keys existing in both maps. (intersection m1 m2 == intersectionWith const m1 m2).

intersectionWith :: Ord k => (a -> b -> c) -> IntervalMap k a -> IntervalMap k b -> IntervalMap k cSource

Intersection with a combining function.

intersectionWithKey :: Ord k => (Interval k -> a -> b -> c) -> IntervalMap k a -> IntervalMap k b -> IntervalMap k cSource

Intersection with a combining function.

Traversal

Map

map :: (a -> b) -> IntervalMap k a -> IntervalMap k bSource

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

mapWithKey :: (Interval k -> a -> b) -> IntervalMap k a -> IntervalMap k bSource

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

mapAccum :: (a -> b -> (a, c)) -> a -> IntervalMap k b -> (a, IntervalMap k c)Source

O(n). The function mapAccum threads an accumulating argument through the map in ascending order of keys.

 let f a b = (a ++ b, b ++ "X")
 mapAccum f "Everything: " (fromList [(5,"a"), (3,"b")]) == ("Everything: ba", fromList [(3, "bX"), (5, "aX")])

mapAccumWithKey :: (a -> Interval k -> b -> (a, c)) -> a -> IntervalMap k b -> (a, IntervalMap k c)Source

O(n). The function mapAccumWithKey threads an accumulating argument through the map in ascending order of keys.

 let f a k b = (a ++ " " ++ (show k) ++ "-" ++ b, b ++ "X")
 mapAccumWithKey f "Everything:" (fromList [(5,"a"), (3,"b")]) == ("Everything: 3-b 5-a", fromList [(3, "bX"), (5, "aX")])

mapAccumRWithKey :: (a -> Interval k -> b -> (a, c)) -> a -> IntervalMap k b -> (a, IntervalMap k c)Source

O(n). The function mapAccumR threads an accumulating argument through the map in descending order of keys.

mapKeys :: Ord k2 => (Interval k1 -> Interval k2) -> IntervalMap k1 a -> IntervalMap k2 aSource

mapKeys f s is the map obtained by applying f to each key of s.

The size of the result may be smaller if f maps two or more distinct keys to the same new key. In this case the value at the smallest of these keys is retained.

mapKeysWith :: Ord k2 => (a -> a -> a) -> (Interval k1 -> Interval k2) -> IntervalMap k1 a -> IntervalMap k2 aSource

mapKeysWith c f s is the map obtained by applying f to each key of s.

The size of the result may be smaller if f maps two or more distinct keys to the same new key. In this case the associated values will be combined using c.

mapKeysMonotonic :: Ord k2 => (Interval k1 -> Interval k2) -> IntervalMap k1 a -> IntervalMap k2 aSource

mapKeysMonotonic f s == mapKeys f s, but works only when f is strictly monotonic. That is, for any values x and y, if x < y then f x < f y. The precondition is not checked.

Fold

foldr :: (a -> b -> b) -> b -> IntervalMap k a -> bSource

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

foldl :: (b -> a -> b) -> b -> IntervalMap k a -> bSource

Fold the values in the map using the given left-associative binary operator, such that foldl f z == Prelude.foldl f z . elems.

foldrWithKey :: (Interval k -> v -> a -> a) -> a -> IntervalMap k v -> aSource

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

foldlWithKey :: (a -> Interval k -> v -> a) -> a -> IntervalMap k v -> aSource

Fold the keys and values in the map using the given left-associative binary operator, such that foldlWithKey f z == Prelude.foldl (\z' (kx, x) -> f z' kx x) z . toAscList.

foldl' :: (b -> a -> b) -> b -> IntervalMap k a -> bSource

A strict version of foldl. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

foldr' :: (a -> b -> b) -> b -> IntervalMap k a -> bSource

A strict version of foldr. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

foldrWithKey' :: (Interval k -> v -> a -> a) -> a -> IntervalMap k v -> aSource

A strict version of foldrWithKey. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

foldlWithKey' :: (a -> Interval k -> v -> a) -> a -> IntervalMap k v -> aSource

A strict version of foldlWithKey. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

Conversion

elems :: IntervalMap k v -> [v]Source

List of all values in the map, in no particular order.

keys :: IntervalMap k v -> [Interval k]Source

List of all keys in the map, in no particular order.

keysSet :: Ord k => IntervalMap k v -> Set (Interval k)Source

Set of the keys.

assocs :: IntervalMap k v -> [(Interval k, v)]Source

Same as toList.

Lists

toList :: IntervalMap k v -> [(Interval k, v)]Source

The list of all key/value pairs contained in the map, in no particular order.

fromList :: Ord k => [(Interval k, v)] -> IntervalMap k vSource

Build a map from a list of key/value pairs. See also fromAscList. If the list contains more than one value for the same key, the last value for the key is retained.

fromListWith :: Ord k => (a -> a -> a) -> [(Interval k, a)] -> IntervalMap k aSource

Build a map from a list of key/value pairs with a combining function. See also fromAscListWith.

fromListWithKey :: Ord k => (Interval k -> a -> a -> a) -> [(Interval k, a)] -> IntervalMap k aSource

Build a map from a list of key/value pairs with a combining function. See also fromAscListWith.

Ordered lists

toAscList :: IntervalMap k v -> [(Interval k, v)]Source

The list of all key/value pairs contained in the map, in ascending order of keys.

toDescList :: IntervalMap k v -> [(Interval k, v)]Source

The list of all key/value pairs contained in the map, in descending order of keys.

fromAscList :: Ord k => [(Interval k, v)] -> IntervalMap k vSource

Build a map from an ascending list in linear time. The precondition (input list is ascending) is not checked.

fromAscListWith :: Ord k => (a -> a -> a) -> [(Interval k, a)] -> IntervalMap k aSource

Build a map from an ascending list in linear time with a combining function for equal keys. The precondition (input list is ascending) is not checked.

fromAscListWithKey :: Ord k => (Interval k -> a -> a -> a) -> [(Interval k, a)] -> IntervalMap k aSource

Build a map from an ascending list in linear time with a combining function for equal keys. The precondition (input list is ascending) is not checked.

fromDistinctAscList :: Ord k => [(Interval k, v)] -> IntervalMap k vSource

Build a map from an ascending list of elements with distinct keys in linear time. The precondition is not checked.

Filter

filter :: Ord k => (a -> Bool) -> IntervalMap k a -> IntervalMap k aSource

Filter values satisfying a predicate.

filterWithKey :: Ord k => (Interval k -> a -> Bool) -> IntervalMap k a -> IntervalMap k aSource

Filter keys/values satisfying a predicate.

partition :: Ord k => (a -> Bool) -> IntervalMap k a -> (IntervalMap k a, IntervalMap k a)Source

Partition the map according to a predicate. The first map contains all elements that satisfy the predicate, the second all elements that fail the predicate. See also split.

partitionWithKey :: Ord k => (Interval k -> a -> Bool) -> IntervalMap k a -> (IntervalMap k a, IntervalMap k a)Source

Partition the map according to a predicate. The first map contains all elements that satisfy the predicate, the second all elements that fail the predicate. See also split.

mapMaybe :: Ord k => (a -> Maybe b) -> IntervalMap k a -> IntervalMap k bSource

Map values and collect the Just results.

mapMaybeWithKey :: Ord k => (Interval k -> a -> Maybe b) -> IntervalMap k a -> IntervalMap k bSource

Map keys/values and collect the Just results.

mapEither :: Ord k => (a -> Either b c) -> IntervalMap k a -> (IntervalMap k b, IntervalMap k c)Source

Map values and separate the Left and Right results.

mapEitherWithKey :: Ord k => (Interval k -> a -> Either b c) -> IntervalMap k a -> (IntervalMap k b, IntervalMap k c)Source

Map keys/values and separate the Left and Right results.

split :: Ord k => Interval k -> IntervalMap k a -> (IntervalMap k a, IntervalMap k a)Source

The expression (split k map) is a pair (map1,map2) where the keys in map1 are smaller than k and the keys in map2 larger than k. Any key equal to k is found in neither map1 nor map2.

splitLookup :: Ord k => Interval k -> IntervalMap k a -> (IntervalMap k a, Maybe a, IntervalMap k a)Source

The expression (splitLookup k map) splits a map just like split but also returns lookup k map.

Min/Max

findMin :: IntervalMap k v -> (Interval k, v)Source

Returns the smallest key and its associated value. Calls error if the map is empty.

findMax :: IntervalMap k v -> (Interval k, v)Source

Returns the largest key and its associated value. Calls error if the map is empty.

findLast :: Eq k => IntervalMap k v -> (Interval k, v)Source

Returns the interval with the largest endpoint. If there is more than one interval with that endpoint, return the rightmost.

deleteMin :: Ord k => IntervalMap k v -> IntervalMap k vSource

Remove the smallest key from the map. Return the empty map if the map is empty.

deleteMax :: Ord k => IntervalMap k v -> IntervalMap k vSource

Remove the largest key from the map. Return the empty map if the map is empty.

deleteFindMin :: Ord k => IntervalMap k v -> ((Interval k, v), IntervalMap k v)Source

Delete and return the smallest key.

deleteFindMax :: Ord k => IntervalMap k v -> ((Interval k, v), IntervalMap k v)Source

Delete and return the largest key.

updateMin :: Ord k => (v -> Maybe v) -> IntervalMap k v -> IntervalMap k vSource

Update or delete value at minimum key.

updateMax :: Ord k => (v -> Maybe v) -> IntervalMap k v -> IntervalMap k vSource

Update or delete value at maximum key.

updateMinWithKey :: Ord k => (Interval k -> v -> Maybe v) -> IntervalMap k v -> IntervalMap k vSource

Update or delete value at minimum key.

updateMaxWithKey :: Ord k => (Interval k -> v -> Maybe v) -> IntervalMap k v -> IntervalMap k vSource

Update or delete value at maximum key.

Debugging

valid :: Ord k => IntervalMap k v -> BoolSource

Check red-black-tree and interval search augmentation invariants.

Testing

height :: IntervalMap k v -> IntSource

The height of the tree. For testing/debugging only.

maxHeight :: Int -> IntSource

The maximum height of a red-black tree with the given number of nodes.

showStats :: IntervalMap k a -> (Int, Int, Int)Source

Tree statistics (size, height, maxHeight size)