gmap-0.1: Composable maps and generic tries.

Data.GMap

Synopsis

Documentation

class Eq k => Map map k | map -> k whereSource

Type of composable maps. For an example of a composed map see Data.GMap.ListMap

Methods

empty :: map aSource

The empty map.

singleton :: k -> a -> map aSource

Create a map with a single association.

pair :: k -> k -> Maybe (a -> a -> map a)Source

Compare two keys and if they are different return a function that will create a map with two associations (when supplied with the corresponding associated values). If the keys are the same then this function returns Nothing.

fromAssocsWith :: (a -> a -> a) -> [(k, a)] -> map aSource

Create a map from an unordered list of associations Combine repeated keys with the provided function.

fromAssocsMaybe :: (a -> a -> Maybe a) -> [(k, a)] -> map aSource

status :: map a -> Status k aSource

See the Status type. This function provides a way to find out if a map is empty, a singleton, or contains more than one association. It is useful if empty or singleton maps require special treatment.

nonEmpty :: map a -> Maybe (map a)Source

Reject empty maps (return Nothing). Typically used for dealing with nested maps. eg to delete a key from a nested map: 'adjustMaybe (nonEmpty $ delete k2) k1'

addSize :: map a -> Int# -> Int#Source

Add number of key/value pairs in the map to the supplied Int

lookup :: k -> map a -> Maybe aSource

Return the value associated with the supplied key (if any).

lookupCont :: (a -> Maybe b) -> k -> map a -> Maybe bSource

Find the value associated with the supplied key (if any) and return the result of applying the supplied continuation function to that value. Useful for nested lookup.

alter :: (Maybe a -> Maybe a) -> k -> map a -> map aSource

This is a combined insert/modify/delete operation. The argument to the supplied function is (Just a) if there is a value (a) associated with the supplied key, otherwise Nothing. If the return value is (Just a'), a' becomes the new value associated with the supplied key. If the return value is Nothing, the association for the supplied key (if any) is deleted.

insertWith :: (a -> a) -> k -> a -> map a -> map aSource

Insert a new association in the map if there is currently no value associated with the key. If there is a value associated with the key then replace it with the result of applying the supplied function to that value.

insertWith' :: (a -> a) -> k -> a -> map a -> map aSource

Same as insertWith, but applies the supplied function strictly if the search succeeds. Note that the third argument is not strictly evaluated either way (TODO change this)

insertMaybe :: (a -> Maybe a) -> k -> a -> map a -> map aSource

Similar to insert, but the association is deleted if the supplied function returns Nothing. (The supplied function is always applied strictly.)

delete :: k -> map a -> map aSource

Delete the association for the supplied key (if any).

adjustWith :: (a -> a) -> k -> map a -> map aSource

Find the value associated with the supplied key (if any) and apply the supplied function to that value.

adjustWith' :: (a -> a) -> k -> map a -> map aSource

Same as adjust but applies the supplied function strictly.

adjustMaybe :: (a -> Maybe a) -> k -> map a -> map aSource

Find the value associated with the supplied key (if any) and apply the supplied function to that value. Delete the association if the result is Nothing. Replace the old value with the new value if the result is (Just something).

venn :: (a -> b -> c) -> map a -> map b -> (map a, map c, map b)Source

Returns the left difference, intersection and right difference of the supplied maps

venn' :: (a -> b -> c) -> map a -> map b -> (map a, map c, map b)Source

Same as venn, but the new values in the intersection are evaluated strictly

vennMaybe :: (a -> b -> Maybe c) -> map a -> map b -> (map a, map c, map b)Source

Same as venn, except that values for which the argument function returns nothing are dropped from the intersection

union :: (a -> a -> a) -> map a -> map a -> map aSource

Evaluate the union of two maps. If the maps contain common keys then combine the values associated with those keys using the supplied function. The value arguments to this function are supplied in the same order as the map arguments.

union' :: (a -> a -> a) -> map a -> map a -> map aSource

Same as unionWith, but the new associated values are evaluated strictly.

unionMaybe :: (a -> a -> Maybe a) -> map a -> map a -> map aSource

Evaluate the union of two maps, but delete combined associations from the result map if the combining function returns Nothing.

disjointUnion :: map a -> map a -> map aSource

Evaluate the union of two key-disjoint maps. If the arguments are not disjoint the behaviour is undefined. This is potentially faster than union.

intersection :: (a -> b -> c) -> map a -> map b -> map cSource

Evaluate the intersection of two maps, combining common associations using the supplied function.

intersection' :: (a -> b -> c) -> map a -> map b -> map cSource

Same as intersection, but the new associated values are evaluated strictly.

intersectionMaybe :: (a -> b -> Maybe c) -> map a -> map b -> map cSource

Evaluate the intersection of two maps, but delete combined associations from the result map if the combining function returns Nothing.

difference :: map a -> map b -> map aSource

Evaluate the difference between two maps. For any key occuring in the second map, the corresponding association (if any) is deleted from the first map. The associated values in the second map are irrelevant.

differenceMaybe :: (a -> b -> Maybe a) -> map a -> map b -> map aSource

Difference with a combining function. If the combining function returns Just a then the corresponding association is not deleted from the result map (it is retained with a as the associated value).

isSubsetOf :: map a -> map b -> BoolSource

Returns true if the keys in the first map are a subset of the keys in the second map. (This includes the case where the key sets are identical). Note that this function does not examine the associated values (which are irrelevant). See isSubmapOf if you do want associated values examined.

isSubmapOf :: (a -> b -> Bool) -> map a -> map b -> BoolSource

Returns true if the keys in the first map are a subset of the keys in the second map and the corresponding function always returns true when applied to the values associated with matching keys.

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

Apply the supplied function to every associated value in the map.

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

Same as map, but the function is applied strictly.

mapMaybe :: (a -> Maybe b) -> map a -> map bSource

Apply the supplied function to every associated value in the map. If the result is Nothing then the delete the corresponding association.

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

Apply the supplied function to every association in the map, and use the result as the new associated value for the corresponding key.

mapWithKey' :: (k -> a -> b) -> map a -> map bSource

Same as mapWithKey, but the function is applied strictly.

filter :: (a -> Bool) -> map a -> map aSource

Delete associations for which the supplied predicate returns False when applied to the associated value.

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

Fold right over the list of elements in an unspecified order.

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

Fold right over the list of keys in an unspecified order.

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

Fold right over the list of associations in an unspecified order.

foldElems' :: (a -> b -> b) -> b -> map a -> bSource

A strict version of foldElems which should be used for accumulating functions which are strict in their second argument.

foldKeys' :: (k -> b -> b) -> b -> map a -> bSource

A strict version of foldKeys which should be used for accumulating functions which are strict in their second argument.

foldAssocs' :: (k -> a -> b -> b) -> b -> map a -> bSource

A strict version of foldAssocs which should be used for accumulating functions which are strict in their third argument.

foldElemsUInt :: (a -> Int# -> Int#) -> Int# -> map a -> Int#Source

Fold over elements in un-specified order using unboxed Int accumulator (with GHC). Defaults to boxed Int for other Haskells. Typically used for counting functions. Implementations are free to traverse the map in any order. The folded function is always applied strictly.

valid :: map a -> Maybe StringSource

Test whatever underlying data structure is used to implement an instance of this class is valid. Used for debugging. Nothing indicates the data structure is valid.

Instances

Map IntMap Int 
Map UnitMap () 
Eq k => Map (ImaginaryOrdMap k) k 
Eq k => Map (AList k) k 
Ord k => Map (OrdMap k) k 
(Eq k, Ord k, OrderedMap mp k) => Map (SList mp k) k 
Map mp k => Map (CacheKeys mp k) k 
Map map k => Map (ListMap map k) [k]

ListMap is an instance of Map.

(Eq k1, Injection t k1 k2, Map map k2) => Map (InjectKeys t k1 k2 map) k1

InjectKeys is an instance of Map.

(Map mapL kL, Map mapR kR) => Map (Choice2Map mapL mapR kL kR) (Choice2 kL kR) 
(Map map1 k1, Map map2 k2) => Map (Tuple2Map map1 map2 k1 k2) (k1, k2)

Tuple2Map is an instance of Map.

data Status k a Source

Raised by disjointUnion if the arguments are not disjoint. Note that instances of Map are *not* required to test that arguments are disjoint.

This is the return type for the status method of the Map class

Constructors

None 
One k a 
Many 

Instances

(Eq k, Eq a) => Eq (Status k a) 

vennMaybe' :: Map map k => (a -> b -> Maybe c) -> map a -> map b -> (map a, map c, map b)Source

Same as vennMaybe except that the new associated values are strictly evaluated.

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

Like alter except that the new associated value is strictly evaluated

adjustMaybe' :: Map map k => (a -> Maybe a) -> k -> map a -> map aSource

Like adjustMaybe except that the new associated value is strictly evaluated

insertMaybe' :: Map map k => (a -> Maybe a) -> k -> a -> map a -> map aSource

Like insertMaybe except that if the key is already present the new associated value is evaluated strictly. If the key is not present then the supplied value is *not* evaluated strictly. (TODO Change this)

unionMaybe' :: Map map k => (a -> a -> Maybe a) -> map a -> map a -> map aSource

Like unionMaybe except that the new associated values are strictly evaluated

intersectionMaybe' :: Map map k => (a -> b -> Maybe c) -> map a -> map b -> map cSource

Like intersectionMaybe except that the new associated values are strictly evaluated

differenceMaybe' :: Map map k => (a -> b -> Maybe a) -> map a -> map b -> map aSource

Like differenceMaybe except that the new associated values are strictly evaluated

mapMaybe' :: Map map k => (a -> Maybe b) -> map a -> map bSource

Like mapMaybe except that the new associated values are strictly evaluated

isEmpty :: Map map l => map a -> BoolSource

isSingleton :: Map map l => map a -> BoolSource

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

Write a new association in the map, overwriting any value currently associated with the key.

insert' :: Map map k => k -> a -> map a -> map aSource

Write a new association in the map, overwriting any value currently associated with the key. The new value is evaluated strictly.

size :: Map map k => map a -> IntSource

Count the number of associations in a map.

insertAssocs :: Map map k => [(k, a)] -> map a -> map aSource

Insert an unordered list of key/value pairs into a map. Repeated keys will be overwritten by the last occurence of the key.

insertAssocsWith :: Map map k => (a -> a -> a) -> [(k, a)] -> map a -> map aSource

insertAssocsMaybe :: Map map k => (a -> a -> Maybe a) -> [(k, a)] -> map a -> map aSource

fromAssocs :: Map map k => [(k, a)] -> map aSource

lookupM :: (Map map k, Monad m) => k -> map a -> m aSource

Monadic lookup.

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

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

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

class Map map k => OrderedMap map k whereSource

Maps which maintain some order on their keys, determined by compareKey.

Methods

compareKey :: map a -> k -> k -> OrderingSource

Every function in this class must respect the ordering given by compareKey. The first argument is required for its type only and should not be evaluated.

fromAssocsAscWith :: (a -> a -> a) -> [(k, a)] -> map aSource

Create a map from an ascending list of key/value pairs Combine repeated keys with the provided function.

fromAssocsAscMaybe :: (a -> a -> Maybe a) -> [(k, a)] -> map aSource

fromAssocsDescWith :: (a -> a -> a) -> [(k, a)] -> map aSource

Create a map from a descending list of key/value pairs Combine repeated keys with the provided function.

fromAssocsDescMaybe :: (a -> a -> Maybe a) -> [(k, a)] -> map aSource

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

Right associative fold over the list of elements in ascending order of keys. See foldElemsAsc' for a strict version of this function.

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

Right associative fold over the list of elements in descending order of keys. See foldElemsDesc' for a strict version of this function.

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

Right associative fold over the list of keys in ascending order. See foldKeysAsc' for a strict version of this function.

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

Right associative fold over the list of keys in descending order. See foldKeysDesc' for a strict version of this function.

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

Right associative fold over the list of associations in ascending order of keys. See foldAssocsAsc' for a strict version of this function.

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

Right associative fold over the list of associations in descending order of keys. See foldAssocsDesc' for a strict version of this function.

foldElemsAsc' :: (a -> b -> b) -> b -> map a -> bSource

A strict version of foldElemsAsc which should be used for accumulating functions which are strict in their second argument.

foldElemsDesc' :: (a -> b -> b) -> b -> map a -> bSource

A strict version of foldElemsDesc which should be used for accumulating functions which are strict in their second argument.

foldKeysAsc' :: (k -> b -> b) -> b -> map a -> bSource

A strict version of foldKeysAsc which should be used for accumulating functions which are strict in their second argument.

foldKeysDesc' :: (k -> b -> b) -> b -> map a -> bSource

A strict version of foldKeysDesc which should be used for accumulating functions which are strict in their second argument.

foldAssocsAsc' :: (k -> a -> b -> b) -> b -> map a -> bSource

A strict version of foldAssocsAsc which should be used for accumulating functions which are strict in their third argument.

foldAssocsDesc' :: (k -> a -> b -> b) -> b -> map a -> bSource

A strict version of foldAssocsDesc which should be used for accumulating functions which are strict in their third argument.

Instances

OrderedMap IntMap Int 
OrderedMap UnitMap () 
(Eq k, Ord k) => OrderedMap (ImaginaryOrdMap k) k 
Ord k => OrderedMap (OrdMap k) k 
(Eq k, Ord k, OrderedMap mp k) => OrderedMap (SList mp k) k 
OrderedMap mp k => OrderedMap (CacheKeys mp k) k 
OrderedMap map k => OrderedMap (ListMap map k) [k] 
(Eq k1, Injection t k1 k2, OrderedMap map k2) => OrderedMap (InjectKeys t k1 k2 map) k1 
(OrderedMap mapL kL, OrderedMap mapR kR) => OrderedMap (Choice2Map mapL mapR kL kR) (Choice2 kL kR) 
(OrderedMap map1 k1, OrderedMap map2 k2) => OrderedMap (Tuple2Map map1 map2 k1 k2) (k1, k2) 

fromAssocsAsc :: OrderedMap map k => [(k, a)] -> map aSource

fromAssocsDesc :: OrderedMap map k => [(k, a)] -> map aSource

insertAssocsAsc :: OrderedMap map k => [(k, a)] -> map a -> map aSource

Insert an ascending list of associations into a map Duplicate keys are replaced by the rightmost value

insertAssocsDesc :: OrderedMap map k => [(k, a)] -> map a -> map aSource

Insert a descending list of associations into a map Duplicate keys are replaced by the rightmost value

insertAssocsAscWith :: OrderedMap map k => (a -> a -> a) -> [(k, a)] -> map a -> map aSource

Insert an ascending list of associations into a map Duplicate keys are combined with the supplied function

insertAssocsDescWith :: OrderedMap map k => (a -> a -> a) -> [(k, a)] -> map a -> map aSource

Insert a descending list of associations into a map Duplicate keys are combined with the supplied function

insertAssocsAscMaybe :: OrderedMap map k => (a -> a -> Maybe a) -> [(k, a)] -> map a -> map aSource

Same as insertAssocsAscWith except that if Nothing is returned then the key is discarded

insertAssocsDescMaybe :: OrderedMap map k => (a -> a -> Maybe a) -> [(k, a)] -> map a -> map aSource

Same as insertAssocsDescWith except that if Nothing is returned then the key is discarded

elemsAsc :: OrderedMap map k => map a -> [a]Source

List the elements in the map in ascending order of keys.

elemsDesc :: OrderedMap map k => map a -> [a]Source

List the elements in the map in descending order of keys.

assocsAsc :: OrderedMap map k => map a -> [(k, a)]Source

List all associations in the map in ascending order of keys.

assocsDesc :: OrderedMap map k => map a -> [(k, a)]Source

List all associations in the map in descending order of keys.

keysAsc :: OrderedMap map k => map a -> [k]Source

List all keys in the map in ascending order.

keysDesc :: OrderedMap map k => map a -> [k]Source

List all keys in the map in descending order.

isProperSubsetOf :: Map map k => map a -> map b -> BoolSource

Similar to isSubsetOf, but also requires that the size of the second map is greater than the first (so does not include the case where the key sets are identical).

isProperSubmapOfBy :: Map map k => (a -> b -> Bool) -> map a -> map b -> BoolSource

Similar to isSubmapOf, but also requires that the size of the second map is greater than the first (so does not include the case where the key sets are identical).

sortAscWith :: OrderedMap map k => map Int -> [k] -> [k]Source

Use a map of the supplied type to sort a list of keys into ascending order Slower than nubAscWith, but retains duplicate keys

sortDescWith :: OrderedMap map k => map Int -> [k] -> [k]Source

Use a map of the supplied type to sort a list of keys into descending order Slower than nubDescWith, but retains duplicate keys

nubAscWith :: OrderedMap map k => map () -> [k] -> [k]Source

Use a map of the supplied type to sort a list of keys into ascending order (eliminating duplicates).

nubDescWith :: OrderedMap map k => map () -> [k] -> [k]Source

Use a map of the supplied type to sort a list of keys into descending order (eliminating duplicates).