container-classes-0.0.0.0: Generic classes for interacting with different container types

MaintainerIvan.Miljenovic@gmail.com

Data.Containers

Description

 

Synopsis

Documentation

class Monoid c => Container c v | c -> v whereSource

Containers are data-types that store values. No restriction is placed on how they store these values, though there may be restrictions on some methods if a Container is also an instance of a sub-class of Container.

Minimum required implementation:

Methods

null :: c -> BoolSource

Test whether a Container is empty.

singleton :: v -> cSource

Create a singleton Container; i.e. size (singleton x) == 1).

insert :: v -> c -> cSource

Add a value to the Container. If this is also a Sequence, then it should be a "cons" operation (i.e. insert the value at the beginning of the Sequence).

elem :: Eq v => v -> c -> BoolSource

The container membership predicate, usually written in infix form, e.g., v elem c.

notElem :: Eq v => v -> c -> BoolSource

The negated version of elem.

delete :: Eq v => v -> c -> cSource

Delete the first value of the Container that matches the predicate.

deleteAll :: Eq v => v -> c -> cSource

Delete all values in the Container that match the predicate.

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

When applied to a predicate and a Container, filter returns the Container containing just those elements that satisfy the predicate (preserving order where applicable).

fold :: (v -> a -> a) -> a -> c -> aSource

Applied to a binary operator, a starting value and a Container, reduce the Container using the binary operator. For Sequence instances, this should be a right fold.

fold1 :: (v -> v -> v) -> c -> vSource

A variant of fold with no starting value, and thus must be applied to non-empty Containers.

genericSize :: Num n => c -> nSource

Returns the size of the Container.

size :: c -> IntSource

Returns the size of the Container as an Int. Typically more efficient than genericSize.

partition :: (v -> Bool) -> c -> (c, c)Source

all :: (v -> Bool) -> c -> BoolSource

Applied to a predicate and a Container, all determines if all elements of the Container satisfy the predicate.

and :: v ~ Bool => c -> BoolSource

Returns the conjunction of a Container containing Boolean values. For the result to be True, the Container must be finite; False, however, results from a False value occurring within a finite position within the order utilised by fold.

any :: (v -> Bool) -> c -> BoolSource

Applied to a predicate and a Container, any determines if any element of the Container satisfies the predicate.

or :: v ~ Bool => c -> BoolSource

Returns the disjunction of a Container containing Boolean values. For the result to be False, the Container must be finite; True, however, results from a True value occurring within a finite position within the order utilised by fold.

product :: Num v => c -> vSource

Computes the product of a finite Container of numbers.

sum :: Num v => c -> vSource

Computes the sum of a finite Container of numbers.

rigidMap :: (v -> v) -> c -> cSource

A type-preserving mapping function, where the resulting Container is obtained by applying the provided function on every element of the Container. For instances of CFunctor, rigidMap = map suffices.

splitElem :: c -> Maybe (v, c)Source

An inverse to insert. Should obey the following:

  • isNothing (splitElem c) == null c
  • If splitElem c = Just (v,c'), then c == v `'insert'` c'.
  • If c is an instance of Sequence, then the returned value should be the first one.

maximum :: Ord v => c -> vSource

Returns the maximum value of a non-empty, finite Container.

minimum :: Ord v => c -> vSource

Returns the minimum value of a non-empty, finite Container.

Instances

Container [a] a 

build :: Container c v => ((v -> c -> c) -> c -> c) -> cSource

empty :: Container c v => cSource

An alias for mempty; constructs an empty Container.

(++) :: Container c v => c -> c -> cSource

An alias for mappend; combines two Containers. For instances of Sequence this should be an append operation.

concat :: (Container o i, Container i v) => o -> iSource

Concatenate all the inner Containers together.

concatMap :: (Container f fv, Container t tv) => (fv -> t) -> f -> tSource

Map a function over a Container and concatenate the results. Note that the types of the initial and final Containers do not have to be the same.

convertContainer :: (Container f v, Container t v) => f -> tSource

Convert one Container to another. If they are both Sequences, then ordering is preserved.

convertContainerBy :: (Container f fv, Container t tv) => (fv -> tv) -> f -> tSource

Convert one Container to another by utilising a mapping function. If they are both Sequences, then ordering is preserved.

class Container (c a) a => CFunctor c a whereSource

Denotes Containers that have kind * -> * and can thus have more than one possible type of value stored within them.

Methods

map :: CFunctor c b => (a -> b) -> c a -> c bSource

Apply the provided function on every element of the Container.

Instances

CFunctor [] a 

sequence :: (Monad m, CFunctor c a, CFunctor c (m a)) => c (m a) -> m (c a)Source

Evaluate each action in the Container and collect the results. The order the actions are evaluated in are determined by the corresponding fold definition.

sequence_ :: (Monad m, Container c (m a)) => c -> m ()Source

Evaluate each action in the Container and discard the results. The order the actions are evaluated in are determined by the corresponding fold definition.

mapM :: (Monad m, CFunctor c a, CFunctor c b) => (a -> m b) -> c a -> m (c b)Source

Apply the monadic mapping function to all the elements of the 'Container, and then evaluate the actions and collect the results. The order the actions are evaluated in are determined by the corresponding fold definition.

mapM_ :: (Monad m, CFunctor c a) => (a -> m b) -> c a -> m ()Source

Apply the monadic mapping function to all the elements of the 'Container, and then evaluate the actions and discard the results. The order the actions are evaluated in are determined by the corresponding fold definition.

class Container c v => Sequence c v whereSource

Sequences are linear Containers with explicit left (start) and right (end) ends. As such, it is possible to append/traverse from either end.

All methods have default stand-alone definitions, and thus no explicit method definitions are required for instances.

Methods

snoc :: c -> v -> cSource

Append the value to the end of the Sequence.

foldl :: (b -> v -> b) -> b -> c -> bSource

Applied to a binary operator, a starting value and a Sequence, reduce the Sequence using the binary operator from left to right.

The default definition is modelled after Data.List.foldl' rather than Data.List.foldl.

foldl1 :: (v -> v -> v) -> c -> vSource

A variant of foldl with no starting value, and thus must be applied to non-empty Sequencess.

viewR :: c -> Maybe (v, c)Source

An inverse to snoc (equivalent to (init xs, 'last xs') for non-empty Sequences). Should obey the following:

head :: Sequence c v => c -> vSource

The first element of a non-empty Sequence.

tail :: Sequence c v => c -> cSource

Everything except the first element of a non-empty Sequence. Consider instead using 'drop 1'.

last :: Sequence c v => c -> vSource

The last element of a non-empty Sequence.

init :: Sequence c v => c -> cSource

Everything except the last value of a non-empty Sequence.

genericTake :: Integral n => n -> c -> cSource

Return the first n elements of a Sequence, or the entire Sequence if its length is less than n.

take :: Int -> c -> cSource

A variant of genericTake where n has to be an Int, and is usually more efficient.

takeWhile :: (v -> Bool) -> c -> cSource

When applied to a predicate p and a Sequence xs, returns the longest prefix (possibly empty) of xs of elements that satisfy p.

dropWhile :: (v -> Bool) -> c -> cSource

dropWhile p xs returns the suffix remaining after takeWhile p xs.

genericDrop :: Integral n => n -> c -> cSource

genericDrop n xs returns the suffix of xs after the first n elements, or empty if n > length xs.

drop :: Int -> c -> cSource

A variant of genericDrop where n has to be an Int, and is usually more efficient.

reverse :: c -> cSource

reverse xs returns the elements of xs in reverse order. xs must be finite.

span :: (v -> Bool) -> c -> (c, c)Source

When applied to a predicate p and a Sequence xs, returns a tuple where first element is longest prefix (possibly empty) of xs of elements that satisfy p and second element is the remainder of the Sequence.

break :: (v -> Bool) -> c -> (c, c)Source

When applied to a predicate p and a Sequence xs, returns a tuple where first element is longest prefix (possibly empty) of xs of elements that do not satisfy p and second element is the remainder of the Sequence.

break p is equivalent to span (not . p).

genericSplitAt :: Integral n => n -> c -> (c, c)Source

genericSplitAt n xs returns a tuple where the first element is the prefix of length n of xs and the second element is the rest of the Sequence. It is equivalent to (genericTake n xs, genericDrop n xs).

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

A variant of genericSplitAt where n has to be an Int, and is usually more efficient.

genericReplicate :: Integral n => n -> v -> cSource

genericReplicate n x is a Sequence of length n where every element is x.

replicate :: Int -> v -> cSource

A variant of genericReplicate where n has to be an Int, and is usually more efficient.

lines :: v ~ String => String -> cSource

lines breaks a string up into a Sequence of Strings at newline characters. The resulting Strings do not contain newlines.

unlines :: v ~ String => c -> StringSource

unlines is an inverse operation to lines. It joins lines, after appending a terminating newline to each.

words :: v ~ String => String -> cSource

words breaks a String up into a Sequence of words, which were delimited by white space.

unwords :: v ~ String => c -> StringSource

unwords is an inverse operation to words. It joins words with separating spaces.

Instances

Sequence [a] a 

buildL :: Sequence c v => ((c -> v -> c) -> c -> c) -> cSource

cons :: Sequence c v => v -> c -> cSource

An alias for insert for Sequences.

genericLength :: (Sequence c v, Integral n) => c -> nSource

An alias for genericSize for Sequences.

length :: Sequence c v => c -> IntSource

An alias for size for Sequences.

foldr :: Sequence c v => (v -> a -> a) -> a -> c -> aSource

An alias for fold for Seuquences.

foldr1 :: Sequence c v => (v -> v -> v) -> c -> vSource

An alias for fold1 for Seuquences.

viewL :: Sequence c v => c -> Maybe (v, c)Source

An alias for splitElem for Seuquences.

(!!) :: Sequence c v => c -> Int -> vSource

Sequence index (subscript) operator, starting from 0. Will throw an error if the index is negative or larger than the length of the Sequence.

class (Sequence (c a) a, CFunctor c a) => SFunctor c a whereSource

Represents Sequences that are also instances of CFunctor. All methods have default definitions.

Methods

scanl :: SFunctor c b => (b -> a -> b) -> b -> c a -> c bSource

scanl1 :: (a -> a -> a) -> c a -> c aSource

scanr :: SFunctor c b => (a -> b -> b) -> b -> c a -> c bSource

scanr1 :: (a -> a -> a) -> c a -> c aSource

zipWith :: (SFunctor c b, SFunctor c d) => (a -> b -> d) -> c a -> c b -> c dSource

zip :: (SFunctor c b, SFunctor c (a, b)) => c a -> c b -> c (a, b)Source

unzip :: (SFunctor c b, SFunctor c (a, b)) => c (a, b) -> (c a, c b)Source

zipWith3 :: (SFunctor c b, SFunctor c d, SFunctor c e) => (a -> b -> d -> e) -> c a -> c b -> c d -> c eSource

zip3 :: (SFunctor c b, SFunctor c d, SFunctor c (a, b, d)) => c a -> c b -> c d -> c (a, b, d)Source

unzip3 :: (SFunctor c b, SFunctor c d, SFunctor c (a, b, d)) => c (a, b, d) -> (c a, c b, c d)Source

Instances

SFunctor [] a 

class Sequence c v => Stream c v whereSource

Represents Sequences that may be infinite in length. All methods have default definitions.

Methods

repeat :: v -> cSource

repeat x is an infinite Stream, with x the value of every element.

cycle :: c -> cSource

cycle ties a finite Stream into a circular one, or equivalently, the infinite repetition of the original Stream. It is the identity on infinite Streams.

iterate :: (v -> v) -> v -> cSource

iterate f x returns an infinite Stream of repeated applications of f to x:

 iterate f x = x `cons` f x `cons` f (f x) `cons` ...

enumFrom :: (Enum a, Stream c a) => a -> cSource

A wrapper around enumFrom.

enumFromThen :: (Enum a, Stream c a) => a -> a -> cSource

A wrapper around enumFromThen.

enumFromThenTo :: (Enum a, Sequence c a) => a -> a -> a -> cSource

A wrapper around enumFromThenTo.

enumFromTo :: (Enum a, Sequence c a) => a -> a -> cSource

A wrapper around enumFromTo.