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

Data.Ten.Representable

Description

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

Synopsis

Documentation

class Applicative10 f => Representable10 (f :: (k -> Type) -> Type) where Source #

Analog of Representable over arity-1 type constructors.

If f is Representable10, then a value of type f m is isomorphic to a function forall a. Rep10 f a -> m a. This essentially means it can be thought of as a fixed-shape record with a wrapper type applied to all of its fields.

This is also equivalent to a total dependent map from Rep10 f to m ("total" meaning that every "key" has a "value").

Associated Types

type Rep10 f :: k -> Type Source #

The "index" type of an f "container".

This is a type that behaves like a GADT, with a value for each possible "position" of an m a in f m and the parameter type(s) a it can have.

Methods

index10 :: f m -> Rep10 f a -> m a Source #

Given an f m and a Rep10 f a "index" into it, extract the m a.

tabulate10 :: (forall a. Rep10 f a -> m a) -> f m Source #

Build an f m by applying a parametric function to each "index".

Instances

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

Defined in Data.Ten.Representable

Associated Types

type Rep10 (Ap10 a) :: k -> Type Source #

Methods

index10 :: forall m (a0 :: k0). Ap10 a m -> Rep10 (Ap10 a) a0 -> m a0 Source #

tabulate10 :: (forall (a0 :: k0). Rep10 (Ap10 a) a0 -> m a0) -> Ap10 a m 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 #

Functor10 f => Functor10 (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

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

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 #

(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 #

Traversable10 f => Traversable10 (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

mapTraverse10 :: forall f0 m n r. Applicative f0 => (Wrapped1 Representable10 f n -> r) -> (forall (a :: k0). m a -> f0 (n a)) -> Wrapped1 Representable10 f m -> f0 r Source #

(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 #

(Generic1 rec, Applicative10 (Rep1 rec), GTabulate10 (Rep1 rec)) => Representable10 (Wrapped1 (Generic1 :: ((k -> Type) -> Type) -> Constraint) rec :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Representable

Associated Types

type Rep10 (Wrapped1 Generic1 rec) :: k -> Type Source #

Methods

index10 :: forall m (a :: k0). Wrapped1 Generic1 rec m -> Rep10 (Wrapped1 Generic1 rec) a -> m a Source #

tabulate10 :: (forall (a :: k0). Rep10 (Wrapped1 Generic1 rec) a -> m a) -> Wrapped1 Generic1 rec m Source #

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

rep10' :: Representable10 f => (f (Rep10 f) -> Rep10 f a) -> Rep10 f a Source #

Turn a record field selector into a Rep10.

See also rep10.

field10' :: Representable10 rec => (rec (Rep10 rec) -> Ap10 a (Rep10 rec)) -> Rep10 rec a Source #

Turn a record field selector targeting Ap10 into a Rep10.

See also rep10.

distributeRep10 :: (Representable10 f, Functor w) => w (f m) -> f (w :.: m) Source #

Analog of distributeRep for Representable10.

Pulls a fixed record shape to the outside of any functor.

collectRep10 :: (Representable10 f, Functor w) => (a -> f m) -> w a -> f (w :.: m) Source #

Analog of collectRep for Representable10.

Gathers a fixed record shape mapped over the elements of any functor.

class GTabulate10 (rec :: (k -> Type) -> Type) where Source #

The Generic1 implementation of tabulate10 based on Field10.

Methods

gtabulate10 :: (forall a. Field10 rec a -> r a) -> rec r Source #

Instances

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

Defined in Data.Ten.Representable

Methods

gtabulate10 :: (forall (a :: k0). Field10 U1 a -> r a) -> U1 r Source #

Representable10 rec => GTabulate10 (Rec1 rec :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Representable

Methods

gtabulate10 :: (forall (a :: k0). Field10 (Rec1 rec) a -> r a) -> Rec1 rec r Source #

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

Defined in Data.Ten.Representable

Methods

gtabulate10 :: (forall (a :: k0). Field10 (f :*: g) a -> r a) -> (f :*: g) r Source #

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

Defined in Data.Ten.Representable

Methods

gtabulate10 :: (forall (a :: k0). Field10 (f :.: g) a -> r a) -> (f :.: g) r Source #

GTabulate10 rec => GTabulate10 (M1 k2 i rec :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Representable

Methods

gtabulate10 :: (forall (a :: k). Field10 (M1 k2 i rec) a -> r a) -> M1 k2 i rec r Source #

index10C :: forall c f a r m. (Representable10 f, Entails (Rep10 f) c) => f m -> Rep10 f a -> (c a => m a -> r) -> r Source #

Access an element along with an instance for its type parameter.