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

Data.Ten.Traversable.WithIndex

Description

An extension of Traversable10 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 (Functor10WithIndex f, Foldable10WithIndex f, Traversable10 f) => Traversable10WithIndex f where Source #

An extension of Traversable10 that provides access to some Index10.

Methods

imapTraverse10 :: Applicative g => (f n -> r) -> (forall a. Index10 f a -> m a -> g (n a)) -> f m -> g r Source #

Instances

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

Defined in Data.Ten.Representable

Methods

imapTraverse10 :: Applicative g => (Wrapped1 Representable10 f n -> r) -> (forall (a :: k0). Index10 (Wrapped1 Representable10 f) a -> m a -> g (n a)) -> Wrapped1 Representable10 f m -> g r Source #

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

Defined in Data.Ten.Traversable.WithIndex

Methods

imapTraverse10 :: Applicative g0 => ((g :.: f) n -> r) -> (forall (a :: k0). Index10 (g :.: f) a -> m a -> g0 (n a)) -> (g :.: f) m -> g0 r Source #

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

Defined in Data.Ten.Sigma

Methods

imapTraverse10 :: Applicative g => ((k :** n) -> r) -> (forall (a :: k0). Index10 ((:**) k) a -> m a -> g (n a)) -> (k :** m) -> g r Source #

itraverse10 :: (Applicative g, Traversable10WithIndex f) => (forall a. Index10 f a -> m a -> g (n a)) -> f m -> g (f n) Source #

traverse10 with an index parameter.

traverse10C :: forall c f g m n. (Entails (Index10 f) c, Applicative g, Traversable10WithIndex f) => (forall a. c a => m a -> g (n a)) -> f m -> g (f n) Source #

traverse10 with an instance for every element.