Category theory/Natural transformation

From HaskellWiki
 map even $ maybeToList $ Just 5

yields the same as

 maybeToList $ fmap even $ Just 5

yields: both yield

 [False]

In the followings, this example will be used to illustrate the notion of natural transformation. If the examples are exaggerated and/or the definitions are incomprehensible, try #External links.

Definition[edit]

  • Let Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \mathcal C} , Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \mathcal D} denote categories.
  • Let Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \Phi, \Psi : \mathcal C \to \mathcal D} be functors.
  • Let Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle X, Y \in \mathbf{Ob}(\mathcal C)} . Let Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle f \in \mathrm{Hom}_{\mathcal C}(X, Y)} .

Let us define the Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \eta : \Phi \to \Psi} natural transformation. It associates to each object of Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \mathcal{C}} a morphism of Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \mathcal{D}} in the following way (usually, not sets are discussed here, but proper classes, so I do not use term “function” for this Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \mathbf{Ob}(\mathcal C) \to \mathbf{Mor}(\mathcal D)} mapping):

  • Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \forall A \in \mathbf{Ob}(\mathcal C) \longmapsto \eta_A \in \mathrm{Hom}_{\mathcal D}(\Phi(A), \Psi(A))} . We call Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \eta_A} the component of Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \eta} at A.
  • Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \eta_Y \cdot \Phi(f) = \Psi(f) \cdot \eta_X}

Thus, the following diagram commutes (in Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \mathcal D} ):

Example: maybeToList[edit]

As already mentioned

 map even $ maybeToList $ Just 5

yields the same as

 maybeToList $ fmap even $ Just 5

yields: both yield

 [False]

This example will be shown in the light of the above definition in the followings.

Vertical arrows: sides of objects[edit]

… showing how the natural transformation works.

Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \eta : \Phi \to \Psi}
maybeToList :: Maybe a -> [a]

Left: side of X object[edit]

Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \eta_X : \Phi(X) \to \Psi(X)}
maybeToList :: Maybe Int -> [Int]
Nothing []
Just 0 [0]
Just 1 [1]

Right: side of Y object[edit]

Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \eta_Y : \Phi(Y) \to \Psi(Y)}
maybeToList :: Maybe Bool -> [Bool]
Nothing []
Just True [True]
Just False [False]

Horizontal arrows: sides of functors[edit]

Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle f : X \to Y}
 even :: Int -> Bool

Side of Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \Phi} functor[edit]

Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \Phi(f) : \Phi(X) \to \Phi(Y)}
fmap even:: Maybe Int -> Maybe Bool
Nothing Nothing
Just 0 Just True
Just 1 Just False

Side of Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \Psi} functor[edit]

Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \Psi(f) : \Psi(X) \to \Psi(Y)}
map even:: [Int] -> [Bool]
[] []
[0] [True]
[1] [False]

Commutativity of the diagram[edit]

Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \Psi(f) \cdot \eta_X = \eta_Y \cdot \Phi(f)}

both paths span between

Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \Phi(X) \to \Psi(Y)}
Maybe Int -> [Bool]
map even . maybeToList maybeToList . fmap even
Nothing [] []
Just 0 [True] [True]
Just 1 [False] [False]

Remarks[edit]

  • even has a more general type (Integral a => a -> Bool) than described here
  • Words “side”, “horizontal”, “vertical”, “left”, “right” serve here only to point to the discussed parts of a diagram, thus, they are not part of the scientific terminology.
  • If You want to modify the commutative diagram, see its source code (in LaTeX using amscd).

Operations[edit]

Mixed[edit]

The “mixed” operations described below will be important also in understanding the definition of “monad” concept in category theory.

Functor and natural transformation[edit]

Let us imagine a parser library, which contains functions for parsing a form. There are two kinds of cells:

  • containing data which are optional (e.g. name of spouse)
  • containing data which consist of an enumeration of items (e.g. names of acquired languages)
 spouse :: Parser (Maybe String)
 languages :: Parser [String]

Let us imagine we have any processing (storing, archiving etc.) function which processes lists (or any other reason which forces us to convert our results to list format and exclude any Maybe's). (Perhaps, all this example is impractical and exaggerated, because in real life we should solve the whole thing in other ways.)

Thus, we want to build a parser combinator (we could notate it graphically with something like Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \mathrm?\!\!\to\!\!\mathrm*} ) which converts a “zero-ore-one-occurrence” like parser to a “zero-or-one-or-many-occurrences” like parser.

We can convert Maybe to list with maybeToList But if we want to do something similar with a parser on Maybe's to achieve a parser on list, then maybeToList is not enough alone, we must fmap it. E.g. if we want to convert a parser like spouse to be of the same type as languages:

 fmap maybeToList spouse

Let us see the types: We start with

 spouse :: Parser (Maybe String)
Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \Lambda(\Phi(X))}

or using notion of composing functors

Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle (\Lambda \Phi)(X)}

We want to achieve

 fmap maybeToList spouse :: Parser [String]
Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \Lambda(\Psi(X))}
Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle (\Lambda \Psi)(X)}

thus we can infer

 fmap maybeToList :: Parser (Maybe [String]) -> Parser [String]
Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle (\Lambda\eta)_X \in \mathrm{Hom}_{\mathcal D}((\Lambda\Phi)(X),\;(\Lambda\Psi)(X))}

In fact, we have a new “datatype converter”: converting not Maybe's to lists, but parser on Maybe to Parser on list. Let us notate the corresponding natural transformation with Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \Lambda\eta} :

To each Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle X \in \mathbf{Ob}(\mathcal C)} we associate Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle (\Lambda\eta)_X \in \mathrm{Hom}_{\mathcal D}((\Lambda\Phi)(X),\;(\Lambda\Psi)(X))}
Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \Lambda\eta : \Lambda\Phi \to \Lambda\Psi}
Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle (\Lambda\eta)_X = \Lambda(\eta_X)}

Summary:

Let Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \mathcal C, \mathcal D, \mathcal E} be categories
Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \Phi, \Psi : \mathcal C \to \mathcal D} functors
Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \Lambda : \mathcal D \to \mathcal E} functor
Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \eta : \Phi \to \Psi} natural transformation

Then let us define a new natural transformation:

Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \Lambda\eta : \Lambda\Phi \to \Lambda\Psi}
Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle (\Lambda\eta)_X = \Lambda(\eta_X)}

Natural transformation and functor[edit]

Let Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \mathcal C, \mathcal D, \mathcal E} be categories
Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \Delta : \mathcal C \to \mathcal D} functor
Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \Phi, \Psi : \mathcal D \to \mathcal E} functors
Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \eta : \Phi \to \Psi} natural transformation

Then let us define a new natural transformation:

Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \eta\Delta : \Phi\Delta \to \Psi\Delta}
Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle (\eta\Delta)_X = \eta_{\Delta(X)}}

It can be illustrated by Haskell examples, too. Understanding it is made harder (easier?) by the fact that Haskell's type inference “(dis)solves” the main point, thus there is no “materialized” manifestation of it.

convert :: Maybe (Term a) -> [Term a]

Unlike seen at Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \mathrm?\!\!\to\!\!\mathrm*} , the definition of this converter will not show much novelty:

convert = maybeToList

the most interesting thing is done automatically by type inference.

External links[edit]