ten-0.1.0.2: Typeclasses like Functor, etc. over arity-1 type constructors.
Safe HaskellNone
LanguageHaskell2010

Data.Ten.Foldable

Description

Provides an analog of Foldable over arity-1 type constructors.

Synopsis

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.

Methods

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

Instances details
Foldable10 (U1 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Foldable

Methods

foldMap10 :: Monoid w => (forall (a :: k0). m a -> w) -> U1 m -> w Source #

Foldable10 (V1 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Foldable

Methods

foldMap10 :: Monoid w => (forall (a :: k0). m a -> w) -> V1 m -> w Source #

Foldable10 (Exists :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Exists

Methods

foldMap10 :: Monoid w => (forall (a :: k0). m a -> w) -> Exists m -> w Source #

Foldable10 (Ap10 a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Foldable

Methods

foldMap10 :: Monoid w => (forall (a0 :: k0). m a0 -> w) -> Ap10 a m -> w Source #

Foldable10 f => Foldable10 (Rec1 f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Foldable

Methods

foldMap10 :: Monoid w => (forall (a :: k0). m a -> w) -> Rec1 f m -> w Source #

(Foldable10 f, Foldable10 g) => Foldable10 (f :*: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Foldable

Methods

foldMap10 :: Monoid w => (forall (a :: k0). m a -> w) -> (f :*: g) m -> w Source #

(Foldable10 f, Foldable10 g) => Foldable10 (f :+: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Foldable

Methods

foldMap10 :: Monoid w => (forall (a :: k0). m a -> w) -> (f :+: g) m -> w Source #

Foldable10 (K1 i a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Foldable

Methods

foldMap10 :: Monoid w => (forall (a0 :: k0). m a0 -> w) -> K1 i a m -> w Source #

(Generic1 f, Foldable10 (Rep1 f)) => Foldable10 (Wrapped1 (Generic1 :: ((k -> Type) -> Type) -> Constraint) f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Foldable

Methods

foldMap10 :: Monoid w => (forall (a :: k0). m a -> w) -> Wrapped1 Generic1 f m -> w Source #

Foldable10 f => Foldable10 (Wrapped1 (Representable10 :: ((k -> Type) -> Type) -> Constraint) f :: (k -> Type) -> Type) Source #

Superclass appeasement; deriving via this will give infinite loops; don't!

Instance details

Defined in Data.Ten.Representable

Methods

foldMap10 :: Monoid w => (forall (a :: k0). m a -> w) -> Wrapped1 Representable10 f m -> w Source #

(Foldable f, Foldable10 g) => Foldable10 (f :.: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Foldable

Methods

foldMap10 :: Monoid w => (forall (a :: k0). m a -> w) -> (f :.: g) m -> w Source #

Foldable10 f => Foldable10 (M1 i c f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Foldable

Methods

foldMap10 :: Monoid w => (forall (a :: k0). m a -> w) -> M1 i c f m -> w Source #

Foldable10 ((:**) k :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Sigma

Methods

foldMap10 :: Monoid w => (forall (a :: k0). m a -> w) -> (k :** m) -> w Source #

fold10 :: (Foldable10 t, Monoid m) => t (Const m) -> m Source #

Given a structure over Const m, return the (<>) of all elements.

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.