| Maintainer | Ivan.Miljenovic@gmail.com |
|---|
Data.Containers
Description
- class Monoid c => Container c v | c -> v where
- null :: c -> Bool
- singleton :: v -> c
- insert :: v -> c -> c
- elem :: Eq v => v -> c -> Bool
- notElem :: Eq v => v -> c -> Bool
- delete :: Eq v => v -> c -> c
- deleteAll :: Eq v => v -> c -> c
- filter :: (v -> Bool) -> c -> c
- fold :: (v -> a -> a) -> a -> c -> a
- fold1 :: (v -> v -> v) -> c -> v
- genericSize :: Num n => c -> n
- size :: c -> Int
- partition :: (v -> Bool) -> c -> (c, c)
- all :: (v -> Bool) -> c -> Bool
- and :: v ~ Bool => c -> Bool
- any :: (v -> Bool) -> c -> Bool
- or :: v ~ Bool => c -> Bool
- product :: Num v => c -> v
- sum :: Num v => c -> v
- rigidMap :: (v -> v) -> c -> c
- splitElem :: c -> Maybe (v, c)
- maximum :: Ord v => c -> v
- minimum :: Ord v => c -> v
- build :: Container c v => ((v -> c -> c) -> c -> c) -> c
- empty :: Container c v => c
- (++) :: Container c v => c -> c -> c
- concat :: (Container o i, Container i v) => o -> i
- concatMap :: (Container f fv, Container t tv) => (fv -> t) -> f -> t
- convertContainer :: (Container f v, Container t v) => f -> t
- convertContainerBy :: (Container f fv, Container t tv) => (fv -> tv) -> f -> t
- class Container (c a) a => CFunctor c a where
- sequence :: (Monad m, CFunctor c a, CFunctor c (m a)) => c (m a) -> m (c a)
- sequence_ :: (Monad m, Container c (m a)) => c -> m ()
- mapM :: (Monad m, CFunctor c a, CFunctor c b) => (a -> m b) -> c a -> m (c b)
- mapM_ :: (Monad m, CFunctor c a) => (a -> m b) -> c a -> m ()
- class Container c v => Sequence c v where
- snoc :: c -> v -> c
- foldl :: (b -> v -> b) -> b -> c -> b
- foldl1 :: (v -> v -> v) -> c -> v
- viewR :: c -> Maybe (v, c)
- head :: Sequence c v => c -> v
- tail :: Sequence c v => c -> c
- last :: Sequence c v => c -> v
- init :: Sequence c v => c -> c
- genericTake :: Integral n => n -> c -> c
- take :: Int -> c -> c
- takeWhile :: (v -> Bool) -> c -> c
- dropWhile :: (v -> Bool) -> c -> c
- genericDrop :: Integral n => n -> c -> c
- drop :: Int -> c -> c
- reverse :: c -> c
- span :: (v -> Bool) -> c -> (c, c)
- break :: (v -> Bool) -> c -> (c, c)
- genericSplitAt :: Integral n => n -> c -> (c, c)
- splitAt :: Int -> c -> (c, c)
- genericReplicate :: Integral n => n -> v -> c
- replicate :: Int -> v -> c
- lines :: v ~ String => String -> c
- unlines :: v ~ String => c -> String
- words :: v ~ String => String -> c
- unwords :: v ~ String => c -> String
- buildL :: Sequence c v => ((c -> v -> c) -> c -> c) -> c
- cons :: Sequence c v => v -> c -> c
- genericLength :: (Sequence c v, Integral n) => c -> n
- length :: Sequence c v => c -> Int
- foldr :: Sequence c v => (v -> a -> a) -> a -> c -> a
- foldr1 :: Sequence c v => (v -> v -> v) -> c -> v
- viewL :: Sequence c v => c -> Maybe (v, c)
- (!!) :: Sequence c v => c -> Int -> v
- class (Sequence (c a) a, CFunctor c a) => SFunctor c a where
- scanl :: SFunctor c b => (b -> a -> b) -> b -> c a -> c b
- scanl1 :: (a -> a -> a) -> c a -> c a
- scanr :: SFunctor c b => (a -> b -> b) -> b -> c a -> c b
- scanr1 :: (a -> a -> a) -> c a -> c a
- zipWith :: (SFunctor c b, SFunctor c d) => (a -> b -> d) -> c a -> c b -> c d
- zip :: (SFunctor c b, SFunctor c (a, b)) => c a -> c b -> c (a, b)
- unzip :: (SFunctor c b, SFunctor c (a, b)) => c (a, b) -> (c a, c b)
- zipWith3 :: (SFunctor c b, SFunctor c d, SFunctor c e) => (a -> b -> d -> e) -> c a -> c b -> c d -> c e
- zip3 :: (SFunctor c b, SFunctor c d, SFunctor c (a, b, d)) => c a -> c b -> c d -> c (a, b, d)
- unzip3 :: (SFunctor c b, SFunctor c d, SFunctor c (a, b, d)) => c (a, b, d) -> (c a, c b, c d)
- class Sequence c v => Stream c v where
- enumFrom :: (Enum a, Stream c a) => a -> c
- enumFromThen :: (Enum a, Stream c a) => a -> a -> c
- enumFromThenTo :: (Enum a, Sequence c a) => a -> a -> a -> c
- enumFromTo :: (Enum a, Sequence c a) => a -> a -> c
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
Test whether a Container is empty.
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
genericSize :: Num n => c -> nSource
Returns the size of the Container.
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.
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,
suffices.
rigidMap = map
splitElem :: c -> Maybe (v, c)Source
An inverse to insert. Should obey the following:
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 |
concat :: (Container o i, Container i v) => o -> iSource
Concatenate all the inner Containers together.
convertContainer :: (Container f v, Container t v) => f -> tSource
convertContainerBy :: (Container f fv, Container t tv) => (fv -> tv) -> f -> tSource
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 |
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
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 (
for non-empty init xs, 'last xs')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
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
genericDrop :: Integral n => n -> c -> cSource
returns the suffix of genericDrop n xsxs after the first
n elements, or empty if n > .
length xs
A variant of genericDrop where n has to be an Int, and is
usually more efficient.
returns the elements of reverse xsxs 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.
genericSplitAt :: Integral n => n -> c -> (c, c)Source
returns a tuple where the first element
is the prefix of genericSplitAt n xslength 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
is a genericReplicate n xSequence 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.
Instances
| Sequence [a] a |
genericLength :: (Sequence c v, Integral n) => c -> nSource
An alias for genericSize for Sequences.
class (Sequence (c a) a, CFunctor c a) => SFunctor c a whereSource
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.
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.