collections-api-1.0.0.0: API for collection data structures.

Stabilityexperimental
Maintainerjeanphilippe.bernardy; google mail.

Data.Collections

Contents

Description

This module defines a class framework for collection types. It provides:

  • Classes for the most common type of collections
  • View types to change the type of a collection, so it implements other classes. This allows to use types for purposes that they are not originally designed for. (eg. ElemsView)
  • A few generic functions for handling collections.
  • Infix (operator) version of common functions.

Should you need a more precise documentation, Data.Collections.Properties lists laws that implementations are entitled to assume.

The classes defined in this module are intended to give hints about performance. eg. if a function has a Map c k v context, this indicates that the function will perform better if c has an efficitent lookup function.

This class framework is based on ideas found in Simon Peyton Jones, "Bulk types with class". http://research.microsoft.com/Users/simonpj/Papers/collections.ps.gz

Another inspiration source are the examples of MPTC and fuctional dependencies in Oleg Kiselyov's many articles posted to the haskell mailing list.

This module name-clashes with a lot of Prelude functions, subsuming those. The user is encouraged to import Prelude hiding the clashing functions. Alternatively, it can be imported qualified.

Synopsis

Classes

Unfoldable

class Unfoldable c i | c -> i whereSource

Class of collection with unobservable elements. It is the dual of the Foldable class.

Methods

insert :: i -> c -> cSource

'natural' insertion of an element into a collection.

empty :: cSource

The empty collection.

singleton :: i -> cSource

Creates a collection with a single element.

insertMany :: Foldable c' i => c' -> c -> cSource

Insert all the elements of a foldable.

insertManySorted :: Foldable c' i => c' -> c -> cSource

Same as insertMany, but with the unchecked precondition that the input Foldable is sorted.

Instances

Unfoldable m (k, v) => Unfoldable (ElemsView m k v) (k, v) 
Unfoldable m (k, v) => Unfoldable (KeysView m k v) (k, v) 

Collection

class (Foldable c a, Unfoldable c a) => Collection c a | c -> a whereSource

Class of collection types.

Methods

filter :: (a -> Bool) -> c -> cSource

filter f c returns the collection of those elements that satisfy the predicate f.

class Collection c o => SortingCollection c o whereSource

Methods

minView :: c -> Maybe (o, c)Source

Map

class Monoid c => Map c k a | c -> k a whereSource

Class of map-like types. (aka. for sparse associative types).

In opposition of Indexed, Map supports unexisting value for some indices.

Methods

delete :: k -> c -> cSource

Remove a key from the keySet (and therefore the associated value in the Map).

member :: k -> c -> BoolSource

Tells whether an key is member of the keySet.

union :: c -> c -> cSource

Union of two keySets. When duplicates are encountered, the keys may come from any of the two input sets. Values come from the map given as first arguement.

intersection :: c -> c -> cSource

Intersection of two keySets.

When duplicates are encountered, the keys may come from any of the two input sets. Values come from the map given as first arguement.

difference :: c -> c -> cSource

Difference of two keySets. Difference is to be read infix: a difference b returns a set containing the elements of a that are also absent from b.

isSubset :: c -> c -> BoolSource

s1 isSubset s2 returns True iff. the keys in s1 form a subset of the keys in s2.

isProperSubset :: c -> c -> BoolSource

s1 isProperSubset s2 returns True iff. s1 isProperSubset s2 and s1 /= s2

lookup :: k -> c -> Maybe aSource

Lookup the value at a given key.

alter :: (Maybe a -> Maybe a) -> k -> c -> cSource

Change the value associated to a given key. Nothing represents no associated value.

insertWith :: (a -> a -> a) -> k -> a -> c -> cSource

Insert with a combining function.

insertWith f key value m will insert the pair (key, value) into m 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).

fromFoldableWith :: Foldable l (k, a) => (a -> a -> a) -> l -> cSource

Convert a Foldable to a Map, with a combining function. Note the applications of the combining function: fromFoldableWith (+) [(k,x1), (k,x2), ..., (k,xn)] = fromFoldable [(k, xn + (... + (x2 + x1)))] or more generally fromFoldableWith f [(k,x) | x <- l] = fromFoldable [(k,foldl1 (flip f) l)] foldGroups is probably less surprising, so use it.

foldGroups :: Foldable l (k, b) => (b -> a -> a) -> a -> l -> cSource

Convert a Foldable to a Map, with a combining function. foldGroups f a l = let mkGroup g = (fst $ head g, foldr f a (map snd g)) in fromList . map mkGroup . groupBy ((==) on fst)) . toList

mapWithKey :: (k -> a -> a) -> c -> cSource

Apply a function over all values in the map.

unionWith :: (a -> a -> a) -> c -> c -> cSource

Union with a combining function.

intersectionWith :: (a -> a -> a) -> c -> c -> cSource

Intersection with a combining function.

differenceWith :: (a -> a -> Maybe a) -> c -> c -> cSource

Difference with a combining function.

isSubmapBy :: (a -> a -> Bool) -> c -> c -> BoolSource

isSubmapBy

isProperSubmapBy :: (a -> a -> Bool) -> c -> c -> BoolSource

isProperSubmapBy

Instances

Map m k v => Map (KeysView m k v) k v 

lookupWithDefault :: Map c k a => a -> k -> c -> aSource

The expression (lookupWithDefault def k map) returns the value at key k or returns def when the key is not in the map.

unionsWith :: (Unfoldable s i, Map s k a, Foldable cs s) => (a -> a -> a) -> cs -> sSource

Union of many (key) sets, with combining function

intersectionWith' :: (Functor m, Map (m (O a b c)) k (O a b c)) => (a -> b -> c) -> m a -> m b -> m cSource

Same as intersectionWith, but with a more general type.

differenceWith' :: (Functor m, Map (m (O a b c)) k (O a b c)) => (a -> b -> Maybe c) -> m a -> m b -> m cSource

Same as differenceWith, but with a more general type.

mapWithKey' :: (Functor m, Map (m (Either a b)) k (Either a b)) => (k -> a -> b) -> m a -> m bSource

(!) :: Indexed c k v => c -> k -> vSource

Infix version of index, with arguments swapped.

Set

class Map c k () => Set c k | c -> k whereSource

Class for set-like collection types. A set is really a map with no value associated to the keys, so Set just states so.

Methods

haddock_candy :: c -> kSource

Dummy method for haddock to accept the class.

unions :: (Unfoldable s i, Map s k a, Foldable cs s) => cs -> sSource

Union of many (key) sets.

notMember :: Map c k a => k -> c -> BoolSource

Tells whether a key is not a member of the keySet.

(\\) :: Map c k a => c -> c -> cSource

Infix version of difference. Difference of two (key) sets.

Sequence

class (Monoid c, Collection c a) => Sequence c a whereSource

Class of sequential-access types. In addition of the Collection services, it provides deconstruction and concatenation.

Methods

take :: Int -> c -> cSource

The first i elements of a sequence.

drop :: Int -> c -> cSource

Elements of a sequence after the first i.

splitAt :: Int -> c -> (c, c)Source

Split a sequence at a given index.

reverse :: c -> cSource

Reverse a sequence.

front :: c -> Maybe (a, c)Source

Analyse the left end of a sequence.

back :: c -> Maybe (c, a)Source

Analyse the right end of a sequence.

cons :: a -> c -> cSource

Add an element to the left end of a sequence.

snoc :: c -> a -> cSource

Add an element to the right end of a sequence.

isPrefix :: Eq a => c -> c -> BoolSource

The isPrefix function takes two seqences and returns True iff the first is a prefix of the second.

head :: Sequence s a => s -> aSource

tail :: Sequence s a => s -> sSource

append :: Sequence c a => c -> c -> cSource

Concatenate two sequences.

concat :: (Sequence s a, Foldable t s) => t -> sSource

The concatenation of all the elements of a container of sequences.

concatMap :: (Sequence s b, Foldable t a) => (a -> s) -> t -> sSource

Map a function over all the elements of a container and concatenate the resulting sequences.

(<|) :: Sequence c i => i -> c -> cSource

Infix version of cons: add an element to the left end of a sequence. Mnemonic: a triangle with the single element at the pointy end.

(|>) :: Sequence c i => c -> i -> cSource

Infix version of snoc: add an element to the right end of a sequence. Mnemonic: a triangle with the single element at the pointy end.

(><) :: Sequence c a => c -> c -> cSource

Infix verion of append. Concatenate two sequences.

Others

class (Ix k, Foldable c (k, v), Indexed c k v) => Array c k v | c -> k v whereSource

Methods

bounds :: c -> (k, k)Source

if (l,r) = bounds c, then inDomain k c == l <= k <= r

array :: Foldable l (k, v) => (k, k) -> l -> cSource

Construct an array with the specified bounds and containing values for given indices within these bounds.

The array is undefined (i.e. bottom) if any index in the list is out of bounds. The Haskell 98 Report further specifies that if any two associations in the list have the same index, the value at that index is undefined (i.e. bottom). However in GHC's implementation, the value at such an index is the value part of the last association with that index in the list.

Because the indices must be checked for these errors, array is strict in the bounds argument and in the indices of the association list, but nonstrict in the values. Thus, recurrences such as the following are possible:

 a = array (1,100) ((1,1) : [(i, i * a!(i-1)) | i <- [2..100]])

Not every index within the bounds of the array need appear in the association list, but the values associated with indices that do not appear will be undefined (i.e. bottom).

If, in any dimension, the lower bound is greater than the upper bound, then the array is legal, but empty. Indexing an empty array always gives an array-bounds error, but bounds still yields the bounds with which the array was constructed.

class Indexed c k v | c -> k v whereSource

Class of indexed types. The collection is dense: there is no way to remove an element nor for lookup to return not found.

In practice however, most shallow collection types will instanciate this class in addition of Map, and leave the responsibility of failure to the caller.

Methods

index :: k -> c -> vSource

index c k returns element associated to k

adjust :: (v -> v) -> k -> c -> cSource

adjust f k c applies f to element associated to k and returns the resulting collection.

inDomain :: k -> c -> BoolSource

if inDomain k c, then index c k is guaranteed not to fail.

(//) :: Foldable l (k, v) => c -> l -> cSource

Constructs a collection identical to the first argument except that it has been updated by the associations in the right argument. For example, if m is a 1-origin, n by n matrix, then

 m//[((i,i), 0) | i <- [1..n]]

is the same matrix, except with the diagonal zeroed.

accum :: Foldable l (k, v') => (v -> v' -> v) -> c -> l -> cSource

accum f takes an array and an association list and accumulates pairs from the list into the array with the accumulating function f. Thus accumArray can be defined using accum:

Conversions

fromFoldable :: (Foldable f a, Collection c' a) => f -> c'Source

Conversion from a Foldable to a Collection.

fromAscFoldable :: (Foldable f a, Collection c' a) => f -> c'Source

Conversion from a Foldable to a Collection, with the unchecked precondition that the input is sorted

fromList :: Collection c a => [a] -> cSource

Converts a list into a collection.

fromListWith :: Map c k a => (a -> a -> a) -> [(k, a)] -> cSource

Specialized version of fromFoldableWith for lists.

fromAscList :: Collection c a => [a] -> cSource

Converts a list into a collection, with the precondition that the input is sorted.

Views

newtype KeysView m k v Source

View to the keys of a dictionnary

Constructors

KeysView 

Fields

fromKeysView :: m
 

Instances

(Monoid m, Map m k v) => Monoid (KeysView m k v) 
Foldable m (k, v) => Foldable (KeysView m k v) k 
Map m k v => Map (KeysView m k v) k v 
Unfoldable m (k, v) => Unfoldable (KeysView m k v) (k, v) 

newtype ElemsView m k v Source

View to the elements of a dictionnary

Constructors

ElemsView 

Fields

fromElemsView :: m
 

Instances

Foldable m (k, v) => Foldable (ElemsView m k v) v 
Unfoldable m (k, v) => Unfoldable (ElemsView m k v) (k, v) 

withKeys :: Collection m (k, v) => T (KeysView m k v) -> T mSource

withElems :: Collection m (k, v) => T (ElemsView m k v) -> T mSource

Foldable