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

Data.Ten.Functor

Description

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

Synopsis

Documentation

class Functor10 (f :: (k -> Type) -> Type) where Source #

Functor over arity-1 type constructors.

Whereas Functor maps a :: Type values to b :: Type values, Functor10 maps (m :: k -> Type) a values to m b values, parametrically in a. That is, the type parameter of Functor has arity 0, and the type parameter of Functor10 has arity 1.

Methods

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

Map each m a value in f m parametrically to n a to get f m.

Instances

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

Defined in Data.Ten.Functor

Methods

fmap10 :: (forall (a :: k0). m a -> n a) -> U1 m -> U1 n Source #

Functor10 (V1 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Functor

Methods

fmap10 :: (forall (a :: k0). m a -> n a) -> V1 m -> V1 n Source #

Functor10 (Exists :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Exists

Methods

fmap10 :: (forall (a :: k0). m a -> n a) -> Exists m -> Exists n Source #

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

Defined in Data.Ten.Functor

Methods

fmap10 :: (forall (a0 :: k0). m a0 -> n a0) -> Ap10 a m -> Ap10 a n Source #

Functor10 f => Functor10 (Rec1 f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Functor

Methods

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

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

Defined in Data.Ten.Functor

Methods

fmap10 :: (forall (a :: k0). m a -> n a) -> (f :*: g) m -> (f :*: g) n Source #

(Functor10 f, Functor10 g) => Functor10 (f :+: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Functor

Methods

fmap10 :: (forall (a :: k0). m a -> n a) -> (f :+: g) m -> (f :+: g) n Source #

Functor10 (K1 i a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Functor

Methods

fmap10 :: (forall (a0 :: k0). m a0 -> n a0) -> K1 i a m -> K1 i a n Source #

(Generic1 f, Functor10 (Rep1 f)) => Functor10 (Wrapped1 (Generic1 :: ((k -> Type) -> Type) -> Constraint) f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Functor

Methods

fmap10 :: (forall (a :: k0). m a -> n a) -> Wrapped1 Generic1 f m -> Wrapped1 Generic1 f n 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 #

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

Defined in Data.Ten.Functor

Methods

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

Functor10 f => Functor10 (M1 i c f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Functor

Methods

fmap10 :: (forall (a :: k0). m a -> n a) -> M1 i c f m -> M1 i c f n Source #

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

Defined in Data.Ten.Sigma

Methods

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

(<$!) :: Functor10 f => (forall a. n a) -> f m -> f n infixl 4 Source #

(<$) for Functor10.

(<$>!) :: Functor10 f => (forall a. m a -> n a) -> f m -> f n infixl 4 Source #

(<$>) for Functor10.

void10 :: Functor10 f => f m -> f Proxy Source #

void for Functor10.

This returns f Proxy because Proxy :: k -> Type has the right kind and carries no runtime information. It's isomorphic to Const () but easier to spell.