User:Michiexile/MATH198/Lecture 3

From HaskellWiki
< User:Michiexile‎ | MATH198
Revision as of 19:52, 27 September 2009 by Michiexile (talk | contribs)
Jump to navigation Jump to search

IMPORTANT NOTE: THESE NOTES ARE STILL UNDER DEVELOPMENT. PLEASE WAIT UNTIL AFTER THE LECTURE WITH HANDING ANYTHING IN, OR TREATING THE NOTES AS READY TO READ.


Functors

We've spent quite a bit of time talking about categories, and special entities in them - morphisms and objects, and special kinds of them, and properties we can find.

And one of the main messages visible so far is that as soon as we have an algebraic structure, and homomorphisms, this forms a category. More importantly, many algebraic structures, and algebraic theories, can be captured by studying the structure of the category they form.

So obviously, in order to understand Category Theory, one key will be to understand homomorphisms between categories.

Homomorphisms of categories

A category is a graph, so a homomorphism of a category should be a homomorphism of a graph that respect the extra structure. Thus, we are led to the definition:

Definition A functor from a category to a category is a graph homomorphism between the underlying graphs such that for every object :

Note: We shall consistently use in place of and . The context should be able to tell you whether you are mapping an object or a morphism at any given moment.

Examples and non-examples
  • Monoid homomorphisms
  • Monotone functions between posets
  • Pick a basis for every vectorspace, send and to the matrix representing that morphism in the chosen bases.

Interpreting functors in Haskell

One example of particular interest to us is the category Hask. A functor in Hask is something that takes a type, and returns a new type. Not only that, we also require that it takes arrows and return new arrows. So let's pick all this apart for a minute or two.

Taking a type and returning a type means that you are really building a polymorphic type class: you have a family of types parametrized by some type variable. For each type a, the functor will produce a new type, F a. This, really, is all we need to reflect the action of .

The action of in turn is recovered by requiring the parametrized type F a to implement the Functor typeclass. This typeclass requires you to implement a function fmap::(a -> b) -> F a -> F b. This function, as the signature indicates, takes a function f :: a -> b and returns a new function fmap f :: F a -> F b.

The rules we expect a Functor to obey seem obvious: translating from the categorical intuition we arrive at the rules

  • fmap id = id and
  • fmap (g . f) = fmap g . fmap f

Now, the real power of a Functor still isn't obvious with this viewpoint. The real power comes in approaching it less categorically.

A Haskell functor is a polymorphic type. In a way, it is an prototypical polymorphic type. We have some type, and we change it, in a meaningful way. And the existence of the Functor typeclass demands of us that we find a way to translate function applications into the Functor image. We can certainly define a boring Functor, such as

data Boring a = Boring
instance Functor Boring where
  fmap f = const Boring

but this is not particularly useful. Almost all Functor instances will take your type and include it into something different, something useful. And it does this in a way that allows you to lift functions acting on the type it contains, so that they transform them in their container.

And the choice of words here is deliberate. Functors can be thought of as data containers, their parameters declaring what they contain, and the fmap implementation allowing access to the contents. Lists, trees with node values, trees with leaf values, Maybe, Either all are Functors in obvious manners.

data List a = Nil | Cons a (List a) 
instance Functor List where
  fmap f Nil = Nil
  fmap f (Cons x lst) = Cons (f x) (fmap f lst)

data Maybe a = Nothing | Just a
instance Functor Maybe where
  fmap f Nothing = Nothing
  fmap f (Just x) = Just (f x)

data Either b a = Left b | Right a
instance Functor (Either b) where
  fmap f (Left x) = Left x
  fmap f (Right y) = Right (f y)

data LeafTree a = Leaf a | Node [LeafTree a]
instance Functor LeafTree where
  fmap f (Node subtrees) = Node (map (fmap f) subtrees)
  fmap f (Leaf x) = Leaf (f x)

data NodeTree a = Leaf | Node a [NodeTree a]
instance Functor NodeTree where
  fmap f Leaf = Leaf
  fmap f (Node x subtrees) = Node (f x) (map (fmap f) subtrees)

Natural transformations

The category of categories

For now, I wanna introduce functors as morphisms of categories, then introduce the category of categories, and the functor categories, and then talk about functors as containers and the HAskell way of dealing with them.