generics-sop-0.2.0.0: Generic Programming using True Sums of Products

Safe HaskellSafe
LanguageHaskell2010

Generics.SOP.BasicFunctors

Description

Basic functors.

Definitions of the type-level equivalents of const, id, and (.), and a definition of the lifted function space.

These datatypes are generally useful, but in this library, they're primarily used as parameters for the NP, NS, POP, and SOP types.

Synopsis

Documentation

newtype K a b Source

The constant type functor.

Like Constant, but kind-polymorphic in its second argument and with a shorter name.

Constructors

K a 

Instances

Functor (K * a) Source 
Monoid a => Applicative (K * a) Source 
Foldable (K * a) Source 
Traversable (K * a) Source 
Show a => Show (K k a b) Source 
Generic (K k a b) Source 
type Rep (K k a b) Source 
type Code (K * a0 b0) = (:) [*] ((:) * a0 ([] *)) ([] [*]) Source 

unK :: K a b -> a Source

Extract the contents of a K value.

newtype I a Source

The identity type functor.

Like Identity, but with a shorter name.

Constructors

I a 

Instances

Monad I Source 
Functor I Source 
Applicative I Source 
Foldable I Source 
Traversable I Source 
Show a => Show (I a) Source 
Generic (I a) Source 
type Rep (I a) Source 
type Code (I a0) = (:) [*] ((:) * a0 ([] *)) ([] [*]) Source 

unI :: I a -> a Source

Extract the contents of an I value.

newtype (f :.: g) p infixr 7 Source

Composition of functors.

Like Compose, but kind-polymorphic and with a shorter name.

Constructors

Comp (f (g p)) 

Instances

(Functor f, Functor g) => Functor ((:.:) * * f g) Source 
Show (f (g p)) => Show ((:.:) l k f g p) Source 
Generic ((:.:) l k f g p) Source 
type Rep ((:.:) l k f g p) Source 
type Code ((:.:) * * f0 g0 p0) = (:) [*] ((:) * (f0 (g0 p0)) ([] *)) ([] [*]) Source 

unComp :: (f :.: g) p -> f (g p) Source

Extract the contents of a Comp value.