Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
A natural transformation is a concept from category theory for a mapping between two functors and their objects
that preserves a naturality condition. In Haskell the naturality condition boils down to parametricity, so a
natural transformation between two functors f
and g
is represented as
type NaturalTransformation f g = ∀a. f a → g a
This type appears in several Haskell libraries, most obviously in
natural-transformations. There are times, however,
when we crave more control. Sometimes what we want to do depends on which type a
is hiding in that f a
we're
given. Sometimes, in other words, we need an unnatural transformation.
This means we have to abandon parametricity for ad-hoc polymorphism, and that means type classes. There are two steps to defining a transformation:
- an instance of the base class
Transformation
declares the two functors being mapped, much like a function type signature, - while the actual mapping of values is performed by an arbitrary number of instances of the method
$
, a bit like multiple equation clauses that make up a single function definition.
The module is meant to be imported qualified.
Synopsis
- class Transformation t where
- class Transformation t => At t x where
- apply :: t `At` x => t -> Domain t x -> Codomain t x
- data Compose t u = Compose t u
- newtype Mapped (f :: Type -> Type) t = Mapped t
- newtype Folded (f :: Type -> Type) t = Folded t
- newtype Traversed (f :: Type -> Type) t = Traversed t
- type family ComposeOuter (c :: Type -> Type) :: Type -> Type where ...
- type family ComposeInner (c :: Type -> Type) :: Type -> Type where ...
Documentation
class Transformation t Source #
A Transformation
, natural or not, maps one functor to another.
Instances
(Transformation t1, Transformation t2, Domain t1 ~ Domain t2) => Transformation (Either t1 t2) Source # | |
(Transformation t, Transformation u, Domain t ~ Codomain u) => Transformation (Compose t u) Source # | |
Transformation t => Transformation (Folded f t) Source # | |
Transformation t => Transformation (Mapped f t) Source # | |
(Transformation t, Codomain t ~ Compose m n) => Transformation (Traversed f t) Source # | |
Transformation (Fold p m) Source # | |
Transformation (Map p q) Source # | |
(Transformation t1, Transformation t2, Domain t1 ~ Domain t2) => Transformation (t1, t2) Source # | |
Transformation (Feeder a b f) Source # | |
Transformation (Traversal p q m) Source # | |
Transformation (Arrow p q x) Source # | |
class Transformation t => At t x where Source #
An unnatural Transformation
can behave differently at different points.
Instances
Composition of two transformations
Compose t u |
Instances
newtype Mapped (f :: Type -> Type) t Source #
Transformation under a Functor
Mapped t |
newtype Folded (f :: Type -> Type) t Source #
Transformation under a Foldable
Folded t |
newtype Traversed (f :: Type -> Type) t Source #
Transformation under a Traversable
Instances
(Transformation t, Codomain t ~ Compose m n) => Transformation (Traversed f t) Source # | |
(At t x, Traversable f, Codomain t ~ Compose m n, Applicative m) => At (Traversed f t) x Source # | |
type Codomain (Traversed f t) Source # | |
Defined in Transformation type Codomain (Traversed f t) = Compose (ComposeOuter (Codomain t)) (Compose f (ComposeInner (Codomain t))) | |
type Domain (Traversed f t) Source # | |
Defined in Transformation |
type family ComposeOuter (c :: Type -> Type) :: Type -> Type where ... Source #
ComposeOuter (Compose p q) = p |
type family ComposeInner (c :: Type -> Type) :: Type -> Type where ... Source #
ComposeInner (Compose p q) = q |