deep-transformations
Safe HaskellSafe-Inferred
LanguageHaskell2010

Transformation

Description

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, and the importing module will require at least the FlexibleInstances, MultiParamTypeClasses, and TypeFamilies language extensions to declare the appropriate instances.

Synopsis

Documentation

>>> {-# Language FlexibleInstances, MultiParamTypeClasses, TypeFamilies, TypeOperators #-}
>>> import Transformation (Transformation)
>>> import qualified Transformation

class Transformation t Source #

A Transformation, natural or not, maps one functor to another. For example, here's the declaration for a transformation that maps Maybe to `[]`:

>>> :{
data MaybeToList = MaybeToList
instance Transformation MaybeToList where
   type Domain MaybeToList = Maybe
   type Codomain MaybeToList = []
:}

Associated Types

type Domain t :: Type -> Type Source #

type Codomain t :: Type -> Type Source #

Instances

Instances details
(Transformation t1, Transformation t2, Domain t1 ~ Domain t2) => Transformation (Either t1 t2) Source # 
Instance details

Defined in Transformation

Associated Types

type Domain (Either t1 t2) :: Type -> Type Source #

type Codomain (Either t1 t2) :: Type -> Type Source #

(Transformation t, Transformation u, Domain t ~ Codomain u) => Transformation (Compose t u) Source # 
Instance details

Defined in Transformation

Associated Types

type Domain (Compose t u) :: Type -> Type Source #

type Codomain (Compose t u) :: Type -> Type Source #

Transformation t => Transformation (Folded f t) Source # 
Instance details

Defined in Transformation

Associated Types

type Domain (Folded f t) :: Type -> Type Source #

type Codomain (Folded f t) :: Type -> Type Source #

Transformation t => Transformation (Mapped f t) Source # 
Instance details

Defined in Transformation

Associated Types

type Domain (Mapped f t) :: Type -> Type Source #

type Codomain (Mapped f t) :: Type -> Type Source #

(Transformation t, Codomain t ~ Compose m n) => Transformation (Traversed f t) Source # 
Instance details

Defined in Transformation

Associated Types

type Domain (Traversed f t) :: Type -> Type Source #

type Codomain (Traversed f t) :: Type -> Type Source #

Transformation (Fold p m) Source # 
Instance details

Defined in Transformation.Rank2

Associated Types

type Domain (Fold p m) :: Type -> Type Source #

type Codomain (Fold p m) :: Type -> Type Source #

Transformation (Map p q) Source # 
Instance details

Defined in Transformation.Rank2

Associated Types

type Domain (Map p q) :: Type -> Type Source #

type Codomain (Map p q) :: Type -> Type Source #

(Transformation t1, Transformation t2, Domain t1 ~ Domain t2) => Transformation (t1, t2) Source # 
Instance details

Defined in Transformation

Associated Types

type Domain (t1, t2) :: Type -> Type Source #

type Codomain (t1, t2) :: Type -> Type Source #

Transformation (Feeder a b f) Source # 
Instance details

Defined in Transformation.AG.Dimorphic

Associated Types

type Domain (Feeder a b f) :: Type -> Type Source #

type Codomain (Feeder a b f) :: Type -> Type Source #

Transformation (Traversal p q m) Source # 
Instance details

Defined in Transformation.Rank2

Associated Types

type Domain (Traversal p q m) :: Type -> Type Source #

type Codomain (Traversal p q m) :: Type -> Type Source #

Transformation (Arrow p q x) Source # 
Instance details

Defined in Transformation

Associated Types

type Domain (Arrow p q x) :: Type -> Type Source #

type Codomain (Arrow p q x) :: Type -> Type Source #

class Transformation t => At t x where Source #

Before we can apply a Transformation, we also need to declare At which base types it is applicable and how it works. If the transformation is natural, we'll need only one instance declaration.

>>> :{
instance MaybeToList `Transformation.At` a where
   MaybeToList $ Just x = [x]
   MaybeToList $ Nothing = []
:}
>>> MaybeToList Transformation.$ (Just True)
[True]

An unnatural Transformation can behave differently depending on the base type and even on its value.

>>> :{
instance {-# OVERLAPS #-} MaybeToList `At` Char where
   MaybeToList $ Just '\0' = []
   MaybeToList $ Just c = [c]
   MaybeToList $ Nothing = []
:}

Methods

($) :: t -> Domain t x -> Codomain t x infixr 0 Source #

Apply the transformation t at type x to map Domain to the Codomain functor.

Instances

Instances details
(Transformation (Auto t), p ~ Domain (Auto t), q ~ Codomain (Auto t), q ~ Semantics a b, Foldable (g q), Monoid a, Monoid b, Foldable p, Attribution (Auto t) a b g q p) => At (Auto t) (g (Semantics a b) (Semantics a b)) Source # 
Instance details

Defined in Transformation.AG.Dimorphic

Methods

($) :: Auto t -> Domain (Auto t) (g (Semantics a b) (Semantics a b)) -> Codomain (Auto t) (g (Semantics a b) (Semantics a b)) Source #

(Transformation (Keep t), p ~ Domain (Keep t), q ~ Codomain (Keep t), q ~ PreservingSemantics p a b, Foldable (g q), Monoid a, Monoid b, Foldable p, Functor p, Attribution (Keep t) a b g q p) => At (Keep t) (g (PreservingSemantics p a b) (PreservingSemantics p a b)) Source # 
Instance details

Defined in Transformation.AG.Dimorphic

Methods

($) :: Keep t -> Domain (Keep t) (g (PreservingSemantics p a b) (PreservingSemantics p a b)) -> Codomain (Keep t) (g (PreservingSemantics p a b) (PreservingSemantics p a b)) Source #

(Revelation (Auto t), Domain (Auto t) ~ f, Codomain (Auto t) ~ Semantics (Auto t), Apply (g (Semantics (Auto t))), Attribution (Auto t) g (Semantics (Auto t)) f) => At (Auto t) (g (Semantics (Auto t)) (Semantics (Auto t))) Source # 
Instance details

Defined in Transformation.AG.Generics

Methods

($) :: Auto t -> Domain (Auto t) (g (Semantics (Auto t)) (Semantics (Auto t))) -> Codomain (Auto t) (g (Semantics (Auto t)) (Semantics (Auto t))) Source #

(Revelation (Keep t), p ~ Domain (Keep t), Apply (g q), q ~ Codomain (Keep t), q ~ PreservingSemantics (Keep t) p, s ~ Semantics (Keep t), Atts (Inherited (Keep t)) (g q q) ~ Atts (Inherited (Keep t)) (g s s), Atts (Synthesized (Keep t)) (g q q) ~ Atts (Synthesized (Keep t)) (g s s), g q (Synthesized (Keep t)) ~ g s (Synthesized (Keep t)), g q (Inherited (Keep t)) ~ g s (Inherited (Keep t)), Attribution (Keep t) g q p) => At (Keep t) (g (PreservingSemantics (Keep t) p) (PreservingSemantics (Keep t) p)) Source # 
Instance details

Defined in Transformation.AG.Generics

(Transformation (Auto t), p ~ Domain (Auto t), q ~ Codomain (Auto t), q ~ Semantics a, Foldable (g q), Monoid a, Foldable p, Attribution (Auto t) a g q p) => At (Auto t) (g (Semantics a) (Semantics a)) Source # 
Instance details

Defined in Transformation.AG.Monomorphic

Methods

($) :: Auto t -> Domain (Auto t) (g (Semantics a) (Semantics a)) -> Codomain (Auto t) (g (Semantics a) (Semantics a)) Source #

(Transformation (Keep t), p ~ Domain (Keep t), q ~ Codomain (Keep t), q ~ PreservingSemantics p a, Foldable (g q), Monoid a, Foldable p, Functor p, Attribution (Keep t) a g q p) => At (Keep t) (g (PreservingSemantics p a) (PreservingSemantics p a)) Source # 
Instance details

Defined in Transformation.AG.Monomorphic

(At t x, At u x, Domain t ~ Domain u) => At (Either t u) x Source # 
Instance details

Defined in Transformation

Methods

($) :: Either t u -> Domain (Either t u) x -> Codomain (Either t u) x Source #

(At t x, At u x, Domain t ~ Codomain u) => At (Compose t u) x Source # 
Instance details

Defined in Transformation

Methods

($) :: Compose t u -> Domain (Compose t u) x -> Codomain (Compose t u) x Source #

(At t x, Foldable f, Codomain t ~ (Const m :: Type -> Type), Monoid m) => At (Folded f t) x Source # 
Instance details

Defined in Transformation

Methods

($) :: Folded f t -> Domain (Folded f t) x -> Codomain (Folded f t) x Source #

(At t x, Functor f) => At (Mapped f t) x Source # 
Instance details

Defined in Transformation

Methods

($) :: Mapped f t -> Domain (Mapped f t) x -> Codomain (Mapped f t) x Source #

(At t x, Traversable f, Codomain t ~ Compose m n, Applicative m) => At (Traversed f t) x Source # 
Instance details

Defined in Transformation

Methods

($) :: Traversed f t -> Domain (Traversed f t) x -> Codomain (Traversed f t) x Source #

At (Fold p m) x Source # 
Instance details

Defined in Transformation.Rank2

Methods

($) :: Fold p m -> Domain (Fold p m) x -> Codomain (Fold p m) x Source #

At (Map p q) x Source # 
Instance details

Defined in Transformation.Rank2

Methods

($) :: Map p q -> Domain (Map p q) x -> Codomain (Map p q) x Source #

(At t x, At u x, Domain t ~ Domain u) => At (t, u) x Source # 
Instance details

Defined in Transformation

Methods

($) :: (t, u) -> Domain (t, u) x -> Codomain (t, u) x Source #

At (Feeder a b f) g Source # 
Instance details

Defined in Transformation.AG.Dimorphic

Methods

($) :: Feeder a b f -> Domain (Feeder a b f) g -> Codomain (Feeder a b f) g Source #

At (Traversal p q m) x Source # 
Instance details

Defined in Transformation.Rank2

Methods

($) :: Traversal p q m -> Domain (Traversal p q m) x -> Codomain (Traversal p q m) x Source #

At (Arrow p q x) x Source # 
Instance details

Defined in Transformation

Methods

($) :: Arrow p q x -> Domain (Arrow p q x) x -> Codomain (Arrow p q x) x Source #

apply :: t `At` x => t -> Domain t x -> Codomain t x Source #

Alphabetical synonym for $

data Compose t u Source #

Composition of two transformations

Constructors

Compose t u 

Instances

Instances details
(Transformation t, Transformation u, Domain t ~ Codomain u) => Transformation (Compose t u) Source # 
Instance details

Defined in Transformation

Associated Types

type Domain (Compose t u) :: Type -> Type Source #

type Codomain (Compose t u) :: Type -> Type Source #

(At t x, At u x, Domain t ~ Codomain u) => At (Compose t u) x Source # 
Instance details

Defined in Transformation

Methods

($) :: Compose t u -> Domain (Compose t u) x -> Codomain (Compose t u) x Source #

type Codomain (Compose t u) Source # 
Instance details

Defined in Transformation

type Codomain (Compose t u) = Codomain t
type Domain (Compose t u) Source # 
Instance details

Defined in Transformation

type Domain (Compose t u) = Domain u

newtype Mapped (f :: Type -> Type) t Source #

Transformation under a Functor

Constructors

Mapped t 

Instances

Instances details
Transformation t => Transformation (Mapped f t) Source # 
Instance details

Defined in Transformation

Associated Types

type Domain (Mapped f t) :: Type -> Type Source #

type Codomain (Mapped f t) :: Type -> Type Source #

(At t x, Functor f) => At (Mapped f t) x Source # 
Instance details

Defined in Transformation

Methods

($) :: Mapped f t -> Domain (Mapped f t) x -> Codomain (Mapped f t) x Source #

type Codomain (Mapped f t) Source # 
Instance details

Defined in Transformation

type Codomain (Mapped f t) = Compose f (Codomain t)
type Domain (Mapped f t) Source # 
Instance details

Defined in Transformation

type Domain (Mapped f t) = Compose f (Domain t)

newtype Folded (f :: Type -> Type) t Source #

Transformation under a Foldable

Constructors

Folded t 

Instances

Instances details
Transformation t => Transformation (Folded f t) Source # 
Instance details

Defined in Transformation

Associated Types

type Domain (Folded f t) :: Type -> Type Source #

type Codomain (Folded f t) :: Type -> Type Source #

(At t x, Foldable f, Codomain t ~ (Const m :: Type -> Type), Monoid m) => At (Folded f t) x Source # 
Instance details

Defined in Transformation

Methods

($) :: Folded f t -> Domain (Folded f t) x -> Codomain (Folded f t) x Source #

type Codomain (Folded f t) Source # 
Instance details

Defined in Transformation

type Codomain (Folded f t) = Codomain t
type Domain (Folded f t) Source # 
Instance details

Defined in Transformation

type Domain (Folded f t) = Compose f (Domain t)

newtype Traversed (f :: Type -> Type) t Source #

Transformation under a Traversable

Constructors

Traversed t 

Instances

Instances details
(Transformation t, Codomain t ~ Compose m n) => Transformation (Traversed f t) Source # 
Instance details

Defined in Transformation

Associated Types

type Domain (Traversed f t) :: Type -> Type Source #

type Codomain (Traversed f t) :: Type -> Type Source #

(At t x, Traversable f, Codomain t ~ Compose m n, Applicative m) => At (Traversed f t) x Source # 
Instance details

Defined in Transformation

Methods

($) :: Traversed f t -> Domain (Traversed f t) x -> Codomain (Traversed f t) x Source #

type Codomain (Traversed f t) Source # 
Instance details

Defined in Transformation

type Domain (Traversed f t) Source # 
Instance details

Defined in Transformation

type Domain (Traversed f t) = Compose f (Domain t)

type family ComposeOuter (c :: Type -> Type) :: Type -> Type where ... Source #

Equations

ComposeOuter (Compose p q) = p 

type family ComposeInner (c :: Type -> Type) :: Type -> Type where ... Source #

Equations

ComposeInner (Compose p q) = q