deep-transformations-0.1: Deep natural and unnatural tree transformations, including attribute grammars
Safe HaskellNone
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.

Synopsis

Documentation

class Transformation t Source #

A Transformation, natural or not, maps one functor to another.

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 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 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 (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 (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 #

An unnatural Transformation can behave differently at different points.

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
(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 ~ 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 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 (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 (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 Domain (Compose t u) Source # 
Instance details

Defined in Transformation

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

Defined in Transformation

type Codomain (Compose t u) = Codomain t