Safe Haskell | None |
---|---|
Language | Haskell2010 |
Provides an analog of Representable
over arity-1 type constructors.
Synopsis
- class Applicative10 f => Representable10 (f :: (k -> Type) -> Type) where
- rep10' :: Representable10 f => (f (Rep10 f) -> Rep10 f a) -> Rep10 f a
- field10' :: Representable10 rec => (rec (Rep10 rec) -> Ap10 a (Rep10 rec)) -> Rep10 rec a
- distributeRep10 :: (Representable10 f, Functor w) => w (f m) -> f (w :.: m)
- collectRep10 :: (Representable10 f, Functor w) => (a -> f m) -> w a -> f (w :.: m)
- class GTabulate10 (rec :: (k -> Type) -> Type) where
- gtabulate10 :: (forall a. Field10 rec a -> r a) -> rec r
- index10C :: forall c f a r m. (Representable10 f, Entails (Rep10 f) c) => f m -> Rep10 f a -> (c a => m a -> r) -> r
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").
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.
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
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
.
gtabulate10 :: (forall a. Field10 rec a -> r a) -> rec r Source #
Instances
GTabulate10 (U1 :: (k -> Type) -> Type) Source # | |
Defined in Data.Ten.Representable | |
Representable10 rec => GTabulate10 (Rec1 rec :: (k -> Type) -> Type) Source # | |
Defined in Data.Ten.Representable | |
(GTabulate10 f, GTabulate10 g) => GTabulate10 (f :*: g :: (k -> Type) -> Type) Source # | |
Defined in Data.Ten.Representable | |
(Representable f, GTabulate10 g) => GTabulate10 (f :.: g :: (k -> Type) -> Type) Source # | |
Defined in Data.Ten.Representable | |
GTabulate10 rec => GTabulate10 (M1 k2 i rec :: (k1 -> Type) -> Type) Source # | |
Defined in Data.Ten.Representable |