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

Data.Ten.Functor.WithIndex

Description

An extension of Functor10 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 Functor10 f => Functor10WithIndex f where Source #

An extension of Functor10 that provides access to some Index10.

Methods

imap10 :: (forall a. Index10 f a -> m a -> n a) -> f m -> f n Source #

Instances

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

Defined in Data.Ten.Representable

Methods

imap10 :: (forall (a :: k0). Index10 (Wrapped1 Representable10 f) a -> m a -> n a) -> Wrapped1 Representable10 f m -> Wrapped1 Representable10 f n Source #

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

Defined in Data.Ten.Functor.WithIndex

Methods

imap10 :: (forall (a :: k0). Index10 (g :.: f) a -> m a -> n a) -> (g :.: f) m -> (g :.: f) n Source #

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

Defined in Data.Ten.Sigma

Methods

imap10 :: (forall (a :: k0). Index10 ((:**) k) a -> m a -> n a) -> (k :** m) -> k :** n Source #

fmap10C :: forall c f m n. (Entails (Index10 f) c, Functor10WithIndex f) => (forall a. c a => m a -> n a) -> f m -> f n Source #

fmap10 with access to an instance for every element.