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

Data.Ten.Foldable.WithIndex

Description

An extension of Foldable10 that provides access to some Index10.

Synopsis

Documentation

type family Index10 (f :: (k -> Type) -> Type) :: k -> Type Source #

The index type associated with a given f.

This is often a GADT-like type, in that inspecting Index10 f a can refine a to some more concrete type, provide instances for it via Entails, etc.

Instances

Instances details
type Index10 (Wrapped1 (Representable10 :: ((k -> Type) -> Type) -> Constraint) f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Representable

type Index10 (Wrapped1 (Representable10 :: ((k -> Type) -> Type) -> Constraint) f :: (k -> Type) -> Type) = Rep10 f
type Index10 (g :.: f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Functor.WithIndex

type Index10 (g :.: f :: (k -> Type) -> Type) = Index10 f
type Index10 ((:**) k :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Sigma

type Index10 ((:**) k :: (Type -> Type) -> Type) = k

class Foldable10 f => Foldable10WithIndex f where Source #

An extension of Foldable10 that provides access to some Index10.

Methods

ifoldMap10 :: Monoid w => (forall a. Index10 f a -> m a -> w) -> f m -> w Source #

Instances

Instances details
(Representable10 f, Foldable10 f) => Foldable10WithIndex (Wrapped1 (Representable10 :: ((k -> Type) -> Type) -> Constraint) f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Representable

Methods

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

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

Defined in Data.Ten.Foldable.WithIndex

Methods

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

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

Defined in Data.Ten.Sigma

Methods

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

ifoldl10 :: Foldable10WithIndex f => (forall a. Index10 f a -> b -> m a -> b) -> b -> f m -> b Source #

foldl10 with an index parameter.

ifoldr10 :: Foldable10WithIndex f => (forall a. Index10 f a -> m a -> b -> b) -> b -> f m -> b Source #

foldr10 with an index parameter.

itraverse10_ :: (Foldable10WithIndex f, Applicative g) => (forall a. Index10 f a -> m a -> g ()) -> f m -> g () Source #

traverse10_ with an index parameter.

foldMap10C :: forall c f m w. (Entails (Index10 f) c, Foldable10WithIndex f, Monoid w) => (forall a. c a => m a -> w) -> f m -> w Source #

foldMap10 with an instance for every element.

foldr10C :: forall c f m b. (Entails (Index10 f) c, Foldable10WithIndex f) => (forall a. c a => m a -> b -> b) -> b -> f m -> b Source #

foldr10 with an instance for every element.

foldl10C :: forall c f m b. (Entails (Index10 f) c, Foldable10WithIndex f) => (forall a. c a => b -> m a -> b) -> b -> f m -> b Source #

foldl10 with an instance for every element.

traverse10C_ :: forall c f g m. (Entails (Index10 f) c, Applicative g, Foldable10WithIndex f) => (forall a. c a => m a -> g ()) -> f m -> g () Source #

traverse10_ with an instance for every element.