collections-0.3.1: Useful standard collections types and related functions.

Portabilityportable
Stabilityprovisional
Maintainerhttp://homepages.nildram.co.uk/~ahey/em.png

Data.Map.AVL

Contents

Description

This module provides an AVL tree based clone of the base package Data.Map.

There are some differences though..

  • size is O(n), not O(1). Consequently, indexed access is disabled.
  • The showTree and showTreeWith functions are not implemented.
  • Some other functions are not yet implemented.

Synopsis

Map type

data Map k a Source

A Map from keys k to values a.

Instances

Typeable2 Map 
Functor (Map k) 
Foldable (Map k) 
(Eq k, Eq a) => Eq (Map k a) 
(Ord k, Ord a) => Ord (Map k a) 
(Show k, Show a) => Show (Map k a) 
Ord k => Monoid (Map k a) 
Ord k => Map (Map k a) k a 
Ord k => Indexed (Map k a) k a 
Foldable (Map k a) (k, a) 
Ord k => SortingCollection (Map k a) (k, a) 
Ord k => Unfoldable (Map k a) (k, a) 
Ord k => Collection (Map k a) (k, a) 

Operators

(!) :: Ord k => Map k a -> k -> aSource

O(log n). Find the value at a key. Calls error when the element can not be found.

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

O(n+m). See difference.

Query

null :: Map k a -> BoolSource

O(1). Is the map empty?

size :: Map k a -> IntSource

O(n). The number of elements in the map.

member :: Ord k => k -> Map k a -> BoolSource

O(log n). Is the key a member of the map?

lookup :: (Monad m, Ord k) => k -> Map k a -> m aSource

O(log n). Lookup the value at a key in the map.

findWithDefault :: Ord k => a -> k -> Map k a -> aSource

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

Construction

empty :: Map k aSource

O(1). The empty map.

singleton :: k -> a -> Map k aSource

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

Insertion

insert :: Ord k => k -> a -> Map k a -> Map k aSource

O(log n). Insert a new key and value in the map. If the key is already present in the map, the associated value is replaced with the supplied value, i.e. insert is equivalent to insertWith const.

insertWith :: Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k aSource

O(log n). Insert with a combining function.

insertWithKey :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k aSource

O(log n). Insert with a combining function.

insertLookupWithKey :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> (Maybe a, Map k a)Source

O(log n). The expression (insertLookupWithKey f k x map) is a pair where the first element is equal to (lookup k map) and the second element equal to (insertWithKey f k x map).

TODO: only one traversal. This requires fiddling with AVL.Push.

Delete/Update

delete :: Ord k => k -> Map k a -> Map k aSource

O(log n). Delete a key and its value from the map. When the key is not a member of the map, the original map is returned.

adjust :: Ord k => (a -> a) -> k -> Map k a -> Map k aSource

O(log n). Adjust a value at a specific key. When the key is not a member of the map, the original map is returned.

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

O(log n). 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)

adjustWithKey :: Ord k => (k -> a -> a) -> k -> Map k a -> Map k aSource

O(log n). 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) -> k -> Map k a -> Map k aSource

O(log n). 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 => (k -> a -> Maybe a) -> k -> Map k a -> Map k aSource

O(log n). 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 => (k -> a -> Maybe a) -> k -> Map k a -> (Maybe a, Map k a)Source

O(log n). Lookup and update.

TODO: only one traversal. This requires fiddling with AVL.Push.

Combine

Union

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

O(n+m). 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). The implementation uses the efficient hedge-union algorithm. Hedge-union is more efficient on (bigset union smallset)?

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

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

unionWithKey :: Ord k => (k -> a -> a -> a) -> Map k a -> Map k a -> Map k aSource

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

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

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

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

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

Difference

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

O(n+m). Difference of two maps.

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

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

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

Intersection

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

O(n+m). Intersection of two maps. The values in the first map are returned, i.e. (intersection m1 m2 == intersectionWith const m1 m2).

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

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

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

O(n+m). Intersection with a combining function. Intersection is more efficient on (bigset intersection smallset)

Traversal

Map

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

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

mapWithKey :: (k -> a -> b) -> Map k a -> Map k bSource

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

mapAccum :: Ord k => (a -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)Source

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

Fold

fold :: (a -> b -> b) -> b -> Map k a -> bSource

O(n). Fold the values in the map, such that fold f z == Prelude.foldr f z . elems. For example,

 elems map = fold (:) [] map

foldWithKey :: (k -> a -> b -> b) -> b -> Map k a -> bSource

Conversion

elems :: Map k a -> [a]Source

O(n). Convert to a list of values.

keys :: Map k a -> [k]Source

O(n). Convert to a list of keys.

keysSet :: Map k a -> Set kSource

O(n). The set of all keys of the map.

liftKeysSet :: (k -> b) -> Set k -> Map k bSource

O(n). Apply a function to each element of a set and return the resulting map.

assocs :: Map k a -> [(k, a)]Source

O(n). Convert to a list of key/value pairs.

unsafeFromTree :: AVL (k, a) -> Map k aSource

O(1). Convert a sorted AVL tree to an AVL tree based Set (as provided by this module). This function does not check the input AVL tree is sorted.

toTree :: Map k a -> AVL (k, a)Source

O(1). Convert an AVL tree based Set (as provided by this module) to a sorted AVL tree.

toList :: Map k a -> [(k, a)]Source

O(n). Convert to a list of key/value pairs.

fromList :: Ord k => [(k, a)] -> Map k aSource

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

O(n*log n). Build a map from a list of key/value pairs with a combining function. See also fromAscListWith.

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

O(n*log n). Build a map from a list of key/value pairs with a combining function. See also fromAscListWithKey.

Ordered lists

toAscList :: Map k a -> [(k, a)]Source

O(n). Convert to a list of key/value pairs.

fromAscList :: Eq k => [(k, a)] -> Map k aSource

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

fromAscListWith :: Eq k => (a -> a -> a) -> [(k, a)] -> Map k aSource

O(n). 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 :: Eq k => (k -> a -> a -> a) -> [(k, a)] -> Map k aSource

O(n). 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 :: [(k, a)] -> Map k aSource

O(n). Build a map from an ascending list of distinct elements in linear time. The precondition is not checked.

Filter

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

O(n). Filter all values that satisfy the predicate.

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

O(n). Filter all keys/values that satisfy the predicate.

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

O(n). 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.

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

O(n). 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.

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

O(log n). The expression (split x set) is a pair (set1,set2) where all elements in set1 are lower than x and all elements in set2 larger than x. x is not found in neither set1 nor set2.

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

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

Submap

isSubmapOf :: (Ord k, Eq a) => Map k a -> Map k a -> BoolSource

O(n+m). This function is defined as (isSubmapOf = isSubmapOfBy (==)).

isSubmapOfBy :: Ord k => (a -> b -> Bool) -> Map k a -> Map k b -> BoolSource

O(n+m). The expression (isSubmapOfBy f t1 t2) returns True if all keys in t1 are in tree t2, and when f returns True when applied to their respective values. For example, the following expressions are all True:

 isSubmapOfBy (==) (fromList [('a',1)]) (fromList [('a',1),('b',2)])
 isSubmapOfBy (<=) (fromList [('a',1)]) (fromList [('a',1),('b',2)])
 isSubmapOfBy (==) (fromList [('a',1),('b',2)]) (fromList [('a',1),('b',2)])

But the following are all False:

 isSubmapOfBy (==) (fromList [('a',2)]) (fromList [('a',1),('b',2)])
 isSubmapOfBy (<)  (fromList [('a',1)]) (fromList [('a',1),('b',2)])
 isSubmapOfBy (==) (fromList [('a',1),('b',2)]) (fromList [('a',1)])

Indexed

Min/Max

findMin :: Map k a -> (k, a)Source

O(log n). The minimal key of the map.

findMax :: Map k a -> (k, a)Source

O(log n). The minimal key of the map.

deleteMin :: Map k a -> Map k aSource

O(log n). Delete the minimal key.

deleteMax :: Map k a -> Map k aSource

O(log n). Delete the minimal key.

deleteFindMin :: Map k a -> ((k, a), Map k a)Source

O(log n). Delete and find the minimal element.

deleteFindMax :: Map k a -> ((k, a), Map k a)Source

O(log n). Delete and find the maximal element.

Debugging