Previous Contents

Chapter 7   Associative Collections

The associative-collection abstraction includes finite maps, finite relations, and priority queues where the priority is separate from element. Associative collections are defined in Edison as a set of eight classes, organized in the hierarchy shown in Figure 7.1. Notice that this hierarchy mirrors the hierarchy for collections, but with the addition of Functor as a superclass of every associative collection. Like collections, associative collections depend heavily on multi-parameter type classes.




AssocX OrdAssocX FiniteMapX OrdFiniteMapX
empty,insert minElem insertWith no methods
union,delete deleteMin unionWith  
null,size unsafeInsertMin intersectWith  
lookup foldr,foldl difference  
map,fold filterLT subset  
filter ··· ···  
···      
Assoc OrdAssoc FiniteMap OrdFiniteMap
toSeq minElemWithKey unionWithKey no methods
mapWithKey foldrWithKey intersectWithKey  
foldWithKey toOrdSeq ···  
filterWithKey ···    
···      

Figure 7.1: The associative-collection class hierarchy, with typical methods for each class.


The operations on associative collections are similar to the operations on collections. The differences arise from having a separate key and element, rather than just an element. One significant implication of this separation is that many of the methods move up in the hierarchy, because elements are always observable for associative collections (even though keys may not be).


Associative-Collection Methods

Constructors:

AssocX: empty, single, insert, insertSeq, union, unionSeq, fromSeq
OrdAssocX: unsafeInsertMin, unsafeInsertMax, unsafeFromOrdSeq, unsafeAppend
FiniteMapX: insertWith, insertWithKey, insertSeqWith, insertSeqWithKey,
   unionl, unionr, unionWith, unionSeqWith, fromSeqWith, fromSeqWithKey
FiniteMap: unionWithKey, unionSeqWithKey
Destructors:

OrdAssocX: minView, minElem, maxView, maxElem
OrdAssoc: minViewWithKey, minElemWithKey, maxViewWithKey, maxElemWithKey
Deletions:

AssocX: delete, deleteAll, deleteSeq
OrdAssocX: deleteMin, deleteMax
Observers:

AssocX: null, size, member, count, lookup, lookupM, lookupAll, lookupWithDefault, elements
Assoc: toSeq, keys
OrdAssoc: toOrdSeq
Modifiers:

AssocX: adjust, adjustAll
Maps and folds:

AssocX: map, fold, fold1
OrdAssocX: foldr, foldl, foldr1, foldl1
Assoc: mapWithKey, foldWithKey
OrdAssoc: foldrWithKey, foldlWithKey
Filters and partitions:

AssocX: filter, partition
OrdAssocX: filterLT, filterLE, filterGT, filterGE,
   partitionLT_GE, partitionLE_GT, partitionLT_GT
Assoc: filterWithKey, partitionWithKey
Set-like operations:

FiniteMapX: intersectWith, difference, subset, subsetEq
FiniteMap: intersectWithKey



Figure 7.2: Summary of methods for the associative-collection classes.


Figure 7.2 summarizes all the methods on associative collections. These methods will be described in more detail in the sections on each subclass in the hierarchy.

I will frequently abbreviate ``associative collection'' as ac . I will also refer jointly to a key and element as a binding.

7.1   AssocX

class Eq k => AssocX m k

7.1.1   Constructors

empty :: m k a

The empty ac .

single :: k ® a ® m k a

Create an ac with a single binding.

insert :: k ® a ® m k a ® m k a
insertSeq :: Sequence seq
Þ seq (k,a) ® m k a ® m k a

Add a binding or a sequence of bindings to a collection. For finite maps, insert keeps the new element in the case of duplicate keys, but insertSeq keeps an unspecified element. Which key is kept is also unspecified for both methods.

See also insertWith, insertWithKey, insertSeqWith, and insertSeqWithKey in FiniteMapX.

union :: m k a ® m k a ® m k a
unionSeq :: Sequence seq
Þ seq (m k a) ® m k a

Merge two acs or a sequence of acs . Which element and which key to keep in the case of duplicate keys is unspecified.

See also unionWith and unionSeqWith in FiniteMapX and unionWithKey and unionSeqWithKey in FiniteMap.

fromSeq :: Sequence seq Þ seq (k,a) ® m k a

Convert a list of bindings to an ac . Which element and which key to keep in the case of duplicate keys is unspecified.

7.1.2   Deletions

delete :: k ® m k a ® m k a
deleteAll :: k
® m k a ® m k a

Delete one binding or all bindings with the given key, or leave the ac unchanged if it does not contain the key. For bag-like acs (i.e., those that allow multiple bindings with the same key), it is unspecified which binding will be removed by delete.
deleteSeq :: Sequence seq Þ seq k ® m k a ® m k a

Delete a single occurrence of each of the given keys from an ac , ignoring those keys that do not appear in the ac . For bag-like acs , there may be multiple bindings with a given key, in which case it is unspecified which is deleted.

7.1.3   Observers

null :: m k a ® Bool

Test whether the ac is empty.

Axioms:
  
null m º (size m == 0)
size :: m k a ® Int

Return the number of bindings in the ac .
member :: m k a ® k ® Bool

Test whether the given key is bound in the ac .

Axioms:
  
member m k º (count xs k > 0)
count :: m k a ® k ® Int

Return the number of bindings with the given key.
lookup :: m k a ® k ® a
lookupM :: m k a
® k ® Maybe a
lookupAll :: Sequence seq
Þ m k a ® k ® seq a
lookupWithDefault :: a
® m k a ® k ® a

Find the element associated with the given given. lookup signals an error if the key is not bound, while lookupWithDefault returns a default value (provided as its first argument). If there is more than one binding with the given key, it is unspecified which element is chosen by lookup, lookupM, or lookupWithDefault. lookupAll returns all elements bound to the given key, but in an unspecified order.
elements :: Sequence seq Þ m k a ® seq a

Return all elements in the given ac , in an unspecified order.

7.1.4   Modifiers

adjust :: (a ® a) ® k ® m k a ® m k a
adjustAll :: (a
® a) ® k ® m k a ® m k a

Change a single binding or all bindings for the given key by applying a function to its element(s). If more than one binding has the same key, it is unspecified which is modified by adjust.

7.1.5   Maps and folds

map :: (a ® b) ® m k a ® m k b

Apply a function to the elements of every binding in an ac . This method appears both in AssocX and in Functor.
fold :: (a ® b ® b) ® b ® m k a ® b

Combine all the elements in an ac , given a combining function and an initial value. The elements are processed in an unspecified order. Note that fold ignores the keys.
fold1 :: (a ® a ® a) ® m k a ® a

Combine all the elements in a non-empty ac using the given combining function. Signals an error if the ac is empty. The elements are processed in an unspecified order. An implementation may choose to process the elements linearly or in a balanced fashion (like reduce1 on sequences). Note that fold1 ignores the keys.

7.1.6   Filters and partitions

filter :: (a ® Bool) ® m k a ® m k a

Extract all the bindings whose elements satisfy the given predicate.
partition :: (a ® Bool) ® m k a ® (m k a, m k a)

Split an ac into those bindings whose elements satisfy the given predicate, and those bindings whose elements do not satisfy the predicate.

7.2   OrdAssocX

class (AssocX m k, Ord k) => OrdAssocX m k

7.2.1   Constructors

unsafeInsertMin :: k ® a ® m k a ® m k a
unsafeInsertMax :: m k a
® k ® a ® m k a

Insert a binding into an ac with the precondition that the given key is £ or ³ any exisiting keys. For finite maps, this precondition is strengthened to < or >.
unsafeFromOrdSeq :: Sequence seq ® seq (k,a) ® m k a

Convert a sequence of bindings into an ac with the precondition that the sequence is sorted into non-decreasing order by key. For finite maps, this precondition is strengthened to increasing order.
unsafeAppend :: m k a ® m k a ® m k a

Merge two acs with the precondition that every key in the first ac is £ every key in the second ac . For finite maps, this precondition is strengthened to <.

7.2.2   Destructors

minView :: m k a ® Maybe2 a (m k a)
maxView :: m k a
® Maybe2 (m k a) a

Remove the binding with the minimum or maximum key, and return its element together with the remaining ac . Return Nothing2 if the ac is empty. Which binding is removed if there is more than one minimum or maximum is unspecified.

See also minViewWithKey and maxViewWithKey in OrdAssoc.

minElem :: m k a ® a
maxElem :: m k a
® a

Return the element associated with the minimum or maximum key, or signal an error if the ac is empty. Which element is chosen if there is more than one minimum or maximum is unspecified.

See also minElemWithKey and maxElemWithKey in OrdAssoc.

7.2.3   Deletions

deleteMin :: m k a ® m k a
deleteMax :: m k a
® m k a

Delete the binding with the minimum or maximum key, or return empty if the ac is already empty. Which binding is chosen if there is more than one minimum or maximum is unspecified.

7.2.4   Maps and Folds

foldr :: (a ® b ® b) ® b ® m k a ® b
foldl :: (b
® a ® b) ® b ® m k a ® b

Fold across the elements in non-decreasing order by key.
foldr1 :: (a ® a ® a) ® m k a ® a
foldl1 :: (a
® a ® a) ® m k a ® a

Fold across the elements in non-decreasing order by key, or signal an error if the ac is empty.

7.2.5   Filters and partitions

filterLT
filterLE
filterGT
filterGE

partitionLT_GE
partitionLE_GT
partitionLT_GT

7.3   FiniteMapX

class AssocX m k => FiniteMapX m k

7.3.1   Constructors

insertWith
insertSeqWith

insertWithKey
insertSeqWithKey

unionl
unionr

unionWith
unionSeqWith

fromSeqWith
fromSeqWithKey

7.3.2   Set-like operations

intersectWith

difference

subset

subsetEq

7.4   OrdFiniteMapX

class (OrdAssocX m k, FiniteMapX m k) => OrdFiniteMapX m k
This class contains no methods. It exists only as an abbreviation for the context
(OrdAssocX m k, FiniteMapX m k)

7.5   Assoc

class AssocX m k => Assoc m k

7.5.1   Observers

toSeq

keys

7.5.2   Maps and folds

mapWithKey

foldWithKey

7.5.3   Filters and partitions

filterWithKey

partitionWithKey

7.6   OrdAssoc

class (Assoc m k, OrdAssocX m k) => OrdAssoc m k

7.6.1   Destructors

minViewWithKey

minElemWithKey

maxViewWithKey

maxElemWithKey

7.6.2   Observers

toOrdSeq

7.6.3   Maps and folds

foldrWithKey
foldlWithKey

7.7   FiniteMap

class (Assoc m k, FiniteMapX m k) => FiniteMap m k

7.7.1   Constructors

unionWithKey
unionSeqWithKey

7.7.2   Set-like operations

intersectWithKey

7.8   OrdFiniteMap

class (OrdAssoc m k, FiniteMap m k) => OrdFiniteMap m k
This class contains no methods. It exists only as an abbreviation for the context
(OrdAssoc m k, FiniteMap m k)


Previous Contents