Difference between revisions of "Category theory/Natural transformation"

From HaskellWiki
Jump to navigation Jump to search
m (<math> environment)
(Make broken link point to Internet Archive. If the page actually has been migrated somewhere else here, that can be patched up.)
 
(29 intermediate revisions by one other user not shown)
Line 1: Line 1:
  +
<haskell>
  +
map even $ maybeToList $ Just 5
  +
</haskell>
  +
yields the same as
  +
<haskell>
  +
maybeToList $ fmap even $ Just 5
  +
</haskell>
  +
yields: both yield
  +
<haskell>
  +
[False]
  +
</haskell>
  +
  +
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 ==
  +
  +
* Let <math>\mathcal C</math>, <math>\mathcal D</math> denote categories.
  +
* Let <math>\Phi, \Psi : \mathcal C \to \mathcal D</math> be functors.
  +
* Let <math>X, Y \in \mathbf{Ob}(\mathcal C)</math>. Let <math>f \in \mathrm{Hom}_{\mathcal C}(X, Y)</math>.
  +
Let us define the <math>\eta : \Phi \to \Psi</math> natural transformation. It associates to each object of <math>\mathcal{C}</math> a morphism of <math>\mathcal{D}</math> in the following way (usually, not sets are discussed here, but proper classes, so I do not use term “function” for this <math>\mathbf{Ob}(\mathcal C) \to \mathbf{Mor}(\mathcal D)</math> mapping):
  +
* <math>\forall A \in \mathbf{Ob}(\mathcal C) \longmapsto \eta_A \in \mathrm{Hom}_{\mathcal D}(\Phi(A), \Psi(A))</math>. We call <math>\eta_A</math> the component of <math>\eta</math> at ''A''.
  +
* <math>\eta_Y \cdot \Phi(f) = \Psi(f) \cdot \eta_X</math>
  +
Thus, the following diagram commutes (in <math>\mathcal D</math>):
  +
  +
[[Image:natural_transformation.png|center]]
  +
 
== Example: <hask>maybeToList</hask> ==
 
== Example: <hask>maybeToList</hask> ==
   
  +
As already mentioned
 
<haskell>
 
<haskell>
 
map even $ maybeToList $ Just 5
 
map even $ maybeToList $ Just 5
Line 6: Line 33:
 
yields the same as
 
yields the same as
 
<haskell>
 
<haskell>
maybeToList $ map even $ Just 5
+
maybeToList $ fmap even $ Just 5
 
</haskell>
 
</haskell>
 
yields: both yield
 
yields: both yield
Line 12: Line 39:
 
[False]
 
[False]
 
</haskell>
 
</haskell>
  +
This example will be shown in the light of the above definition in the followings.
   
 
=== Vertical arrows: sides of objects ===
 
=== Vertical arrows: sides of objects ===
   
… showing the operation of the natural transformation.
+
… showing how the natural transformation works.
   
 
:<math>\eta : \Phi \to \Psi</math>
 
:<math>\eta : \Phi \to \Psi</math>
Line 66: Line 94:
 
|+ <math>\Phi(f) : \Phi(X) \to \Phi(Y)</math>
 
|+ <math>\Phi(f) : \Phi(X) \to \Phi(Y)</math>
 
|
 
|
| <hask>map even:: Maybe Int -> Maybe Bool</hask>
+
| <hask>fmap even:: Maybe Int -> Maybe Bool</hask>
 
|-
 
|-
 
| <hask>Nothing</hask>
 
| <hask>Nothing</hask>
Line 82: Line 110:
 
{| Border=2 CellPadding=2 CellSpacing=2
 
{| Border=2 CellPadding=2 CellSpacing=2
 
|+ <math>\Psi(f) : \Psi(X) \to \Psi(Y)</math>
 
|+ <math>\Psi(f) : \Psi(X) \to \Psi(Y)</math>
  +
|
 
| <hask>map even:: [Int] -> [Bool]</hask>
 
| <hask>map even:: [Int] -> [Bool]</hask>
 
|-
 
|-
Line 88: Line 117:
 
|-
 
|-
 
| <hask>[0]</hask>
 
| <hask>[0]</hask>
| <hask>[T]rue</hask>
+
| <hask>[True]</hask>
 
|-
 
|-
 
| <hask>[1]</hask>
 
| <hask>[1]</hask>
| <hask>[F]alse</hask>
+
| <hask>[False]</hask>
 
|}
 
|}
   
=== Commutativity of diagram ===
+
=== Commutativity of the diagram ===
  +
  +
:<math>\Psi(f) \cdot \eta_X = \eta_Y \cdot \Phi(f)</math>
  +
both paths span between
  +
:<math>\Phi(X) \to \Psi(Y)</math>
   
 
{| Border=2 CellPadding=2 CellSpacing=2
 
{| Border=2 CellPadding=2 CellSpacing=2
  +
| RowSpan=2|
|+ <math>\eta_Y \cdot \Phi(f) = \Psi(f) \cdot \eta_X</math>
 
  +
| ColSpan=2|<hask>Maybe Int -> [Bool]</hask>
|
 
  +
|-
 
| <hask>map even . maybeToList</hask>
 
| <hask>map even . maybeToList</hask>
| <hask>maybeToList . map even</hask>
+
| <hask>maybeToList . fmap even</hask>
 
|-
 
|-
 
| <hask>Nothing</hask>
 
| <hask>Nothing</hask>
Line 119: Line 153:
 
* <hask>even</hask> has a more general type (<hask>Integral a => a -> Bool</hask>) than described here
 
* <hask>even</hask> has a more general type (<hask>Integral a => a -> Bool</hask>) 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.
 
* 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 [[#Definition|commutative diagram]], see its [[Media:Natural_transformation.tex|source code]] (in LaTeX using <code>amscd</code>).
  +
  +
== Operations ==
  +
  +
=== Mixed ===
  +
  +
The “mixed” operations described below will be important also in understanding the definition of “monad” concept in category theory.
  +
  +
==== Functor and natural transformation ====
  +
  +
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)
  +
  +
<haskell>
  +
spouse :: Parser (Maybe String)
  +
languages :: Parser [String]
  +
</haskell>
  +
  +
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 <math>\mathrm?\!\!\to\!\!\mathrm*</math>) which converts a “zero-ore-one-occurrence” like parser to a “zero-or-one-or-many-occurrences” like parser.
  +
  +
We can convert <hask>Maybe</hask> to list with <hask>maybeToList</hask>
  +
But if we want to do something similar with a ''parser'' on Maybe's to achieve a ''parser'' on list, then <hask>maybeToList</hask> is not enough alone, we must <hask>fmap</hask> it.
  +
E.g. if we want to convert a parser like <hask>spouse</hask> to be of the same type as <hask>languages</hask>:
  +
<haskell>
  +
fmap maybeToList spouse
  +
</haskell>
  +
Let us see the types:
  +
We start with
  +
<haskell>
  +
spouse :: Parser (Maybe String)
  +
</haskell>
  +
:<math>\Lambda(\Phi(X))</math>
  +
or using notion of composing functors
  +
:<math>(\Lambda \Phi)(X)</math>
  +
We want to achieve
  +
<haskell>
  +
fmap maybeToList spouse :: Parser [String]
  +
</haskell>
  +
:<math>\Lambda(\Psi(X))</math>
  +
:<math>(\Lambda \Psi)(X)</math>
  +
thus we can infer
  +
<haskell>
  +
fmap maybeToList :: Parser (Maybe [String]) -> Parser [String]
  +
</haskell>
  +
:<math>(\Lambda\eta)_X \in \mathrm{Hom}_{\mathcal D}((\Lambda\Phi)(X),\;(\Lambda\Psi)(X))</math>
  +
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 <math>\Lambda\eta</math>:
  +
:To each <math>X \in \mathbf{Ob}(\mathcal C)</math> we associate <math>(\Lambda\eta)_X \in \mathrm{Hom}_{\mathcal D}((\Lambda\Phi)(X),\;(\Lambda\Psi)(X))</math>
  +
:<math>\Lambda\eta : \Lambda\Phi \to \Lambda\Psi</math>
  +
:<math>(\Lambda\eta)_X = \Lambda(\eta_X)</math>
  +
  +
Summary:
  +
  +
:Let <math>\mathcal C, \mathcal D, \mathcal E</math> be categories
  +
:<math>\Phi, \Psi : \mathcal C \to \mathcal D</math> functors
  +
:<math>\Lambda : \mathcal D \to \mathcal E</math> functor
  +
:<math>\eta : \Phi \to \Psi</math> natural transformation
  +
Then let us define a new natural transformation:
  +
:<math>\Lambda\eta : \Lambda\Phi \to \Lambda\Psi</math>
  +
:<math>(\Lambda\eta)_X = \Lambda(\eta_X)</math>
  +
  +
==== Natural transformation and functor ====
  +
  +
:Let <math>\mathcal C, \mathcal D, \mathcal E</math> be categories
  +
:<math>\Delta : \mathcal C \to \mathcal D</math> functor
  +
:<math>\Phi, \Psi : \mathcal D \to \mathcal E</math> functors
  +
:<math>\eta : \Phi \to \Psi</math> natural transformation
  +
Then let us define a new natural transformation:
  +
:<math>\eta\Delta : \Phi\Delta \to \Psi\Delta</math>
  +
:<math>(\eta\Delta)_X = \eta_{\Delta(X)}</math>
  +
  +
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.
  +
  +
<haskell>
  +
convert :: Maybe (Term a) -> [Term a]
  +
</haskell>
  +
  +
Unlike [[#Functor and natural transformation|seen at <math>\mathrm?\!\!\to\!\!\mathrm*</math>]], the definition of this converter will not show much novelty:
  +
  +
<haskell>
  +
convert = maybeToList
  +
</haskell>
  +
  +
the most interesting thing is done automatically by type inference.
  +
  +
== External links ==
  +
* [https://web.archive.org/web/20060925043212/http://www.haskell.org/hawiki/CategoryTheory_2fNaturalTransformation The corresponding HaWiki article] is not migrated here yet, so You can see it for more information.
  +
* Wikipedia's [http://en.wikipedia.org/wiki/Natural_transformation Natural transformation] article
  +
* [http://www.case.edu/artsci/math/wells/pub/ttt.html Toposes, Triples and Theories] written by Michael Barr and Charles Wells.
  +
  +
[[Category:Theoretical foundations]]

Latest revision as of 03:17, 23 September 2014

 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

  • Let , denote categories.
  • Let be functors.
  • Let . Let .

Let us define the natural transformation. It associates to each object of a morphism of in the following way (usually, not sets are discussed here, but proper classes, so I do not use term “function” for this mapping):

  • . We call the component of at A.

Thus, the following diagram commutes (in ):

Natural transformation.png

Example: maybeToList

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

… showing how the natural transformation works.

maybeToList :: Maybe a -> [a]

Left: side of X object

maybeToList :: Maybe Int -> [Int]
Nothing []
Just 0 [0]
Just 1 [1]

Right: side of Y object

maybeToList :: Maybe Bool -> [Bool]
Nothing []
Just True [True]
Just False [False]

Horizontal arrows: sides of functors

 even :: Int -> Bool

Side of functor

fmap even:: Maybe Int -> Maybe Bool
Nothing Nothing
Just 0 Just True
Just 1 Just False

Side of functor

map even:: [Int] -> [Bool]
[] []
[0] [True]
[1] [False]

Commutativity of the diagram

both paths span between

Maybe Int -> [Bool]
map even . maybeToList maybeToList . fmap even
Nothing [] []
Just 0 [True] [True]
Just 1 [False] [False]

Remarks

  • 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

Mixed

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

Functor and natural transformation

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 ) 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)

or using notion of composing functors

We want to achieve

 fmap maybeToList spouse :: Parser [String]

thus we can infer

 fmap maybeToList :: Parser (Maybe [String]) -> Parser [String]

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 :

To each we associate

Summary:

Let be categories
functors
functor
natural transformation

Then let us define a new natural transformation:

Natural transformation and functor

Let be categories
functor
functors
natural transformation

Then let us define a new natural transformation:

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 , the definition of this converter will not show much novelty:

convert = maybeToList

the most interesting thing is done automatically by type inference.

External links