Safe Haskell | None |
---|---|
Language | Haskell2010 |
Provides an analog of Foldable
over arity-1 type constructors.
Synopsis
- class Foldable10 (t :: (k -> Type) -> Type) where
- fold10 :: (Foldable10 t, Monoid m) => t (Const m) -> m
- foldr10 :: Foldable10 t => (forall a. m a -> b -> b) -> b -> t m -> b
- foldl10 :: Foldable10 t => (forall a. b -> m a -> b) -> b -> t m -> b
- traverse10_ :: (Applicative f, Foldable10 t) => (forall a. m a -> f ()) -> t m -> f ()
- sequenceA10_ :: (Applicative m, Foldable10 f) => f m -> m ()
- fsequenceA10_ :: (Applicative m, Foldable10 f) => f (m :.: n) -> m ()
Documentation
class Foldable10 (t :: (k -> Type) -> Type) where Source #
Foldable
over arity-1 type constructors.
Whereas Foldable
folds a :: Type
values to a monoid, Foldable10
folds
(m :: k -> Type) a
values to a monoid, parametrically in a
. That is,
the type parameter of Foldable
has arity 0, and the type parameter of
Foldable10
has arity 1.
foldMap10 :: Monoid w => (forall a. m a -> w) -> t m -> w Source #
Map each m a
element parametrically to w
and mconcat
the results.
Instances
foldr10 :: Foldable10 t => (forall a. m a -> b -> b) -> b -> t m -> b Source #
Right-associative fold over a Foldable10
.
foldl10 :: Foldable10 t => (forall a. b -> m a -> b) -> b -> t m -> b Source #
Left-associative fold over a Foldable10
.
traverse10_ :: (Applicative f, Foldable10 t) => (forall a. m a -> f ()) -> t m -> f () Source #
Sequence actions given by a function left-to-right in a Foldable10
.
This form discards the final result; see traverse10
for a version that keeps it.
sequenceA10_ :: (Applicative m, Foldable10 f) => f m -> m () Source #
Sequence actions in a Foldable10
left-to-right, discarding the result.
This variant expects just the plain m
actions with no inner type
constructor.
fsequenceA10_ :: (Applicative m, Foldable10 f) => f (m :.: n) -> m () Source #
Sequence actions in a Foldable10
left-to-right, discarding the result.
This variant expects the composition of the Applicative
being sequenced
with some inner type constructor at each field.
See fsequenceA10_
for a version that keeps the result.