Copyright | (c) Sergey Vinokurov 2019 |
---|---|
License | BSD-2 (see LICENSE) |
Maintainer | sergey@debian |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- class Constrained f => CFoldable f where
- cfold :: (Monoid m, Constraints f m) => f m -> m
- cfoldMap :: (Monoid m, Constraints f a) => (a -> m) -> f a -> m
- cfoldr :: Constraints f a => (a -> b -> b) -> b -> f a -> b
- cfoldr' :: Constraints f a => (a -> b -> b) -> b -> f a -> b
- cfoldl :: Constraints f a => (b -> a -> b) -> b -> f a -> b
- cfoldl' :: Constraints f a => (b -> a -> b) -> b -> f a -> b
- cfoldr1 :: Constraints f a => (a -> a -> a) -> f a -> a
- cfoldl1 :: Constraints f a => (a -> a -> a) -> f a -> a
- ctoList :: Constraints f a => f a -> [a]
- cnull :: Constraints f a => f a -> Bool
- clength :: Constraints f a => f a -> Int
- celem :: (Eq a, Constraints f a) => a -> f a -> Bool
- cmaximum :: forall a. (Ord a, Constraints f a) => f a -> a
- cminimum :: forall a. (Ord a, Constraints f a) => f a -> a
- csum :: (Num a, Constraints f a) => f a -> a
- cproduct :: (Num a, Constraints f a) => f a -> a
- cfoldrM :: (CFoldable f, Monad m, Constraints f a) => (a -> b -> m b) -> b -> f a -> m b
- cfoldlM :: (CFoldable f, Monad m, Constraints f a) => (b -> a -> m b) -> b -> f a -> m b
- ctraverse_ :: (CFoldable f, Applicative f, Constraints f a) => (a -> f b) -> f a -> f ()
- cfor_ :: (CFoldable f, Applicative f, Constraints f a) => f a -> (a -> f b) -> f ()
- cmapM_ :: (CFoldable f, Monad m, Constraints f a) => (a -> m b) -> f a -> m ()
- cforM_ :: (CFoldable f, Monad m, Constraints f a) => f a -> (a -> m b) -> m ()
- csequenceA_ :: (CFoldable f, Applicative m, Constraints f (m a)) => f (m a) -> m ()
- csequence_ :: (CFoldable f, Monad m, Constraints f a, Constraints f (m a)) => f (m a) -> m ()
- casum :: (CFoldable f, Alternative m, Constraints f (m a)) => f (m a) -> m a
- cmsum :: (CFoldable f, MonadPlus m, Constraints f (m a)) => f (m a) -> m a
- cconcat :: (CFoldable f, Constraints f [a]) => f [a] -> [a]
- cconcatMap :: (CFoldable f, Constraints f a) => (a -> [b]) -> f a -> [b]
- cand :: (CFoldable f, Constraints f Bool) => f Bool -> Bool
- cor :: (CFoldable f, Constraints f Bool) => f Bool -> Bool
- cany :: (CFoldable f, Constraints f a) => (a -> Bool) -> f a -> Bool
- call :: (CFoldable f, Constraints f a) => (a -> Bool) -> f a -> Bool
- cmaximumBy :: (CFoldable f, Constraints f a) => (a -> a -> Ordering) -> f a -> a
- cminimumBy :: (CFoldable f, Constraints f a) => (a -> a -> Ordering) -> f a -> a
- cnotElem :: (CFoldable f, Eq a, Constraints f a) => a -> f a -> Bool
- cfind :: (CFoldable f, Constraints f a) => (a -> Bool) -> f a -> Maybe a
- class Constrained (f :: k2 -> k1) where
- type Constraints (f :: k2 -> k1) :: k2 -> Constraint
Documentation
class Constrained f => CFoldable f where Source #
Like Foldable
but allows elements to have constraints on them.
Laws are the same.
cfold :: (Monoid m, Constraints f m) => f m -> m Source #
Combine the elements of a structure using a monoid.
cfoldMap :: (Monoid m, Constraints f a) => (a -> m) -> f a -> m Source #
Map each element of the structure to a monoid, and combine the results.
cfoldr :: Constraints f a => (a -> b -> b) -> b -> f a -> b Source #
Right-associative fold of a structure.
In the case of lists, cfoldr
, when applied to a binary operator, a
starting value (typically the right-identity of the operator), and a
list, reduces the list using the binary operator, from right to left:
cfoldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)
Note that, since the head of the resulting expression is produced by
an application of the operator to the first element of the list,
cfoldr
can produce a terminating expression from an infinite list.
For a general CFoldable
structure this should be semantically identical
to,
cfoldr f z =foldr
f z .ctoList
cfoldr' :: Constraints f a => (a -> b -> b) -> b -> f a -> b Source #
Right-associative fold of a structure, but with strict application of the operator.
cfoldl :: Constraints f a => (b -> a -> b) -> b -> f a -> b Source #
Left-associative fold of a structure.
In the case of lists, cfoldl
, when applied to a binary
operator, a starting value (typically the left-identity of the operator),
and a list, reduces the list using the binary operator, from left to
right:
cfoldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn
Note that to produce the outermost application of the operator the
entire input list must be traversed. This means that cfoldl'
will
diverge if given an infinite list.
Also note that if you want an efficient left-fold, you probably want to
use cfoldl'
instead of cfoldl
. The reason for this is that latter does
not force the "inner" results (e.g. z
in the above example)
before applying them to the operator (e.g. to f
x1(
). This results
in a thunk chain f
x2)O(n)
elements long, which then must be evaluated from
the outside-in.
For a general CFoldable
structure this should be semantically identical
to,
cfoldl f z =foldl
f z .ctoList
cfoldl' :: Constraints f a => (b -> a -> b) -> b -> f a -> b Source #
Left-associative fold of a structure but with strict application of the operator.
This ensures that each step of the fold is forced to weak head normal
form before being applied, avoiding the collection of thunks that would
otherwise occur. This is often what you want to strictly reduce a finite
list to a single, monolithic result (e.g. clength
).
For a general CFoldable
structure this should be semantically identical
to,
cfoldl f z =foldl'
f z .ctoList
cfoldr1 :: Constraints f a => (a -> a -> a) -> f a -> a Source #
A variant of cfoldr
that has no base case,
and thus may only be applied to non-empty structures.
cfoldr1
f =foldr1
f .ctoList
cfoldl1 :: Constraints f a => (a -> a -> a) -> f a -> a Source #
A variant of cfoldl
that has no base case,
and thus may only be applied to non-empty structures.
cfoldl1
f =foldl1
f .ctoList
ctoList :: Constraints f a => f a -> [a] Source #
List of elements of a structure, from left to right.
cnull :: Constraints f a => f a -> Bool Source #
Test whether the structure is empty. The default implementation is optimized for structures that are similar to cons-lists, because there is no general way to do better.
clength :: Constraints f a => f a -> Int Source #
Returns the size/length of a finite structure as an Int
. The
default implementation is optimized for structures that are similar to
cons-lists, because there is no general way to do better.
celem :: (Eq a, Constraints f a) => a -> f a -> Bool Source #
Does the element occur in the structure?
cmaximum :: forall a. (Ord a, Constraints f a) => f a -> a Source #
The largest element of a non-empty structure.
cminimum :: forall a. (Ord a, Constraints f a) => f a -> a Source #
The least element of a non-empty structure.
csum :: (Num a, Constraints f a) => f a -> a Source #
The csum
function computes the sum of the numbers of a structure.
cproduct :: (Num a, Constraints f a) => f a -> a Source #
The cproduct
function computes the product of the numbers of a
structure.
Instances
cfoldrM :: (CFoldable f, Monad m, Constraints f a) => (a -> b -> m b) -> b -> f a -> m b Source #
Monadic fold over the elements of a structure, associating to the right, i.e. from right to left.
cfoldlM :: (CFoldable f, Monad m, Constraints f a) => (b -> a -> m b) -> b -> f a -> m b Source #
Monadic fold over the elements of a structure, associating to the left, i.e. from left to right.
ctraverse_ :: (CFoldable f, Applicative f, Constraints f a) => (a -> f b) -> f a -> f () Source #
Map each element of a structure to an action, evaluate these
actions from left to right, and ignore the results. For a version
that doesn't ignore the results see traverse
.
cfor_ :: (CFoldable f, Applicative f, Constraints f a) => f a -> (a -> f b) -> f () Source #
cfor_
is ctraverse_
with its arguments flipped. For a version
that doesn't ignore the results see cfor
.
>>>
for_ [1..4] print
1 2 3 4
cmapM_ :: (CFoldable f, Monad m, Constraints f a) => (a -> m b) -> f a -> m () Source #
Map each element of a structure to a monadic action, evaluate
these actions from left to right, and ignore the results. For a
version that doesn't ignore the results see
mapM
.
csequenceA_ :: (CFoldable f, Applicative m, Constraints f (m a)) => f (m a) -> m () Source #
Evaluate each action in the structure from left to right, and
ignore the results. For a version that doesn't ignore the results
see sequenceA
.
csequence_ :: (CFoldable f, Monad m, Constraints f a, Constraints f (m a)) => f (m a) -> m () Source #
Evaluate each monadic action in the structure from left to right,
and ignore the results. For a version that doesn't ignore the
results see sequence
.
casum :: (CFoldable f, Alternative m, Constraints f (m a)) => f (m a) -> m a Source #
cmsum :: (CFoldable f, MonadPlus m, Constraints f (m a)) => f (m a) -> m a Source #
The sum of a collection of actions, generalizing concat
.
cconcat :: (CFoldable f, Constraints f [a]) => f [a] -> [a] Source #
The concatenation of all the elements of a container of lists.
cconcatMap :: (CFoldable f, Constraints f a) => (a -> [b]) -> f a -> [b] Source #
Map a function over all the elements of a container and concatenate the resulting lists.
cany :: (CFoldable f, Constraints f a) => (a -> Bool) -> f a -> Bool Source #
Determines whether any element of the structure satisfies the predicate.
call :: (CFoldable f, Constraints f a) => (a -> Bool) -> f a -> Bool Source #
Determines whether all elements of the structure satisfy the predicate.
cmaximumBy :: (CFoldable f, Constraints f a) => (a -> a -> Ordering) -> f a -> a Source #
The largest element of a non-empty structure with respect to the given comparison function.
cminimumBy :: (CFoldable f, Constraints f a) => (a -> a -> Ordering) -> f a -> a Source #
The least element of a non-empty structure with respect to the given comparison function.
class Constrained (f :: k2 -> k1) Source #
Specification of constrains that a functor might impose on its elements. For example, sets typically require that their elements are ordered and unboxed vectors require elements to have an instance of special class that allows them to be packed in memory.
NB The Constraints
type family is associated with a typeclass in
order to improve type inference. Whenever a typeclass constraint
will be present, instance is guaranteed to exist and typechecker is
going to take advantage of that.
type Constraints (f :: k2 -> k1) :: k2 -> Constraint Source #