User:Michiexile/MATH198/Lecture 3

From HaskellWiki
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

These notes cover material dispersed in several places of Awodey. The definition of a functor is on page 8. More on functors and natural transformations comes in sections 7.1-7.2, 7.4-7.5, 7.7-7.10.

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 frequently use in place of and . The context should suffice to tell you whether you are mapping an object or a morphism at any given moment.

On Wikipedia: [1]

Examples

A homomorphism of monoids is a functor of the corresponding one-object categories . The functor takes the single object to the single object, and acts on morphisms by .

A homomorphism of posets is a functor of the corresponding category. We have if , so if then .

If we pick some basis for every vector space, then this gives us a functor from to the category with objects integers and morphisms matrices by:

  • is the matrix representing in the matrices chosen.

This example relies on the axiom of choice.


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 data F a = ... 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 ::i (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)


The category of categories

We define a category by setting objects to be all small categories, and arrows to be all functors between them. Being graph homomorphisms, functors compose, their composition fulfills all requirements on forming a category. It is sometimes useful to argue about a category of all small and most large categories. The issue here is that allowing opens up for set-theoretical paradoxes.


Isomorphisms in Cat and equivalences of categories

The definition of an isomorphism holds as is in . However, isomorphisms of categories are too restrictive a concept.

To see this, recall the category , where each object is a monoid, and each arrow is a monoid homomorphism. We can form a one-object category out of each monoid, and the method to do this is functorial - i.e. does the right thing to arrows to make the whole process a functor.

Specifically, if is a monoid homomorphism, we create a new functor by setting and . This creates a functor from to . The domain can be further restricted to a full subcategory of , consisting of all the 1-object categories. We can also define a functor by with the monoidal structure on given by the composition in . For an arrow we define .

These functors take a monoid, builds a one-object category, and hits all of them; and takes a one-object category and builds a monoid. Both functors respect the monoidal structures - yet these are not an isomorphism pair. The clou here is that our construction of from requires us to choose something for the one object of the category. And choosing different objects gives us different categories.

Thus, the composition is not the identity; there is no guarantee that we will pick the object we started with in the construction in . Nevertheless, we would be inclined to regard the categories and as essentially the same. The solution is to introduce a different kind of sameness: Definition A functor is an equivalence of categories if there is a functor and:

  • A family of isomorphisms in indexed by the objects of , such that for every arrow .
  • A family of isomorphisms in indexed by the objects of , such that for every arrow .

The functor in the definition is called a pseudo-inverse of .


Natural transformations

The families of morphisms required in the definition of an equivalence show up in more places. Suppose we have two functors and . Definition natural transformation is a family of arrows indexed by the objects of such that for any arrow in (draw diagram)

The commutativity of the corresponding diagram is called the naturality condition on , and the arrow is called the component of the natural transformation at the object .

Given two natural transformations and , we can define a composition componentwise as .

Proposition The composite of two natural transformations is also a natural transformation.

Proposition Given two categories the collection of all functors form a category with objects functors and morphisms natural transformations between these functors.

Note that this allows us to a large degree to use functors to define entities we may otherwise have defined using large and involved definitions. Doing this using the categorical language instead mainly gives us a large number of facts for free: we don't have to verify, say, associativity of composition of functors if we already know them to be functors.

Example Recall our original definition of a graph as two collections and two maps between them. We can define a category GraphS:

A two right arrows B

with the two arrows named and . It is a finite category with 2 objects, and 4 arrows. Now, a small graph can be defined to be just a Functor .

In order to define more intricate structures this way, say Categories, or algebraic structures, we'd need more tools - which we shall find in later lectures. This approach to algebraic definition develops into an area called Sketch theory.

The idea, there, is that theories are modelled by specific categories - such as above, and actual instances of the objects they model appear as functors.

With this definition, since a graph is just a functor , and we get graph homomorphisms for free: a graph homomorphism is just a natural transformation.

And anything we can prove about functors and natural transformations thus immediately gives a corresponding result for graphs and graph homomorphisms.

On Wikipedia, see: [2]. Sketch theory, alas, has a painfully incomplete Wikipedia article.

Properties of functors

The process of forming homsets within a category gives, for any object , two different functors : and . Functoriality for is easy: is the map that takes some and transforms it into .

Functoriality for is more involved. We can view this as a functor either from , or as a different kind of functor. If we just work with , then no additional definitions are needed - but we need an intuition for the dual categories.

Alternatively, we introduce a new concept of a contravariant functor. A contravariant functor is some map of categories, just like a functor is, but such that , as usual, but such that for a , the functor image is some , and the composition is . The usual kind of functors are named covariant.

A functor is faithful if the induced mapping

is injective for all .

A functor is full if the induced mapping

is surjective for all .

Note that a full subcategory is a subcategory so that the embedding functor is both full and faithful.

See also entries in the list of Types of Functors on the Wikipedia page for Functors [3].

Preservation and reflection

We say that a functor preserves a property , if whenever holds in the category , it does so for the image of in .

Thus, the inclusion functor for the category of finite sets into the category of sets preserves both monomorphisms and epimorphisms. Indeed, these properties, in both categories, correspond to injective and surjective functions, respectively; and a surjective (injective) function of finite sets is still surjective (injective) when considered for sets in general.

As another example, consider the category given by , with the single non-identity arrow named . All arrows in this category are both monomorphic and epimorphic. We can define a functor through , and mapping to the set function that takes all elements to the value . The resulting constant map is neither epic nor monic, while the morphism is both.

However, there are properties that functors do preserve:

Proposition Every functor preserves isomorphisms.

Proof Suppose is an isomorphism with inverse . Then has inverse . Indeed, and . QED

We say that a functor reflects a property , if whenever has that property, so does .

A functor is representative if every object in is isomorphic to some for .

Homework

Complete homework is by 4 out of 9 complete solutions. Partial credit will be given.

  1. Show that the category of vectorspaces is equivalent to the category with objects integers and arrows matrices.
  2. Prove the propositions in the section on natural transformations.
  3. Prove that listToMaybe :: [a] -> Maybe a is a natural transformation from the list functor to the maybe functor. Is catMaybes a natural transformation? Between which functors?
  4. Find two more natural transformations defined in the standard Haskell library. Find one polymorphic function that is not a natural transformation.
  5. Write a functor instance for data F a = F (Int -> a)
  6. Write a functor instance for data F a = F ((Int -> a) -> Int)
  7. Write a natural transformation from Maybe a to Either () a. Is this a natural isomorphism? If so, what is its inverse? If not, why not?
  8. Write a natural transformation from [a] to (Maybe a, Maybe a). Is this a natural isomorphism? If so, what is its inverse? If not, why not?
  9. * Recall that a category is called discrete if it has no arrows other than the identities. Show that a small category is discrete if and only if every set function , for every small category , is the object part of a unique functor . Analogously, we define a small category to be indiscrete if for every small category , every set function is the object part of a unique functor . Characterise indiscrete categories by the objects and arrows they have.
  10. * We could write a pretty printer, or XML library, using the following data type as the core data type:
data ML a = Tag a (ML a) | 
            Str String   |
            Seq [ML a]   |
            Nil
With this, we can use a specific string-generating function to generate the tagged marked up text, such as, for instance:
prettyprint (Tag tag ml) = "<" ++ show tag ++ ">" ++ prettyprint ml ++ "</" ++ show tag ++ ">"
prettyprint (Str s) = s
prettyprint (Seq []) = ""
prettyprint (Seq (m:ms)) = prettyprint m ++ "\n" ++ prettyprint (Seq ms)
prettyprint Nil = ""
Write an instance of Functor that allows us to apply changes to the tagging type. Then, using the following tagging types:
data HTMLTag = HTML | BODY | P | H1 | CLASS String deriving (Show)
data XMLTag = DOCUMENT | HEADING | TEXT deriving (Show)
write a function htmlize :: ML XMLTag -> ML HTMLTag and use it to generate a html document out of:
Tag DOCUMENT 
  Seq [
    Tag HEADING
      String "Nobel prize for chromosome find",
    Tag TEXT
      String "STOCKHOLM (Reuters) - Three Americans won the Nobel prize for medicine on Monday for revealing the existence and nature of telomerase, an enzyme which helps prevent the fraying of chromosomes that underlies aging and cancer.",
    Tag TEXT
      String "Australian-born Elizabeth Blackburn, British-born Jack Szostak and Carol Greider won the prize of 10 million Swedish crowns ($1.42 million), Sweden's Karolinska Institute said.",
    Tag TEXT
      String "'The discoveries ... have added a new dimension to our understanding of the cell, shed light on disease mechanisms, and stimulated the development of potential new therapies,' it said.",
    Tag TEXT
      String "The trio's work laid the foundation for studies that have linked telomerase and telomeres -- the small caps on the end of chromosomes -- to cancer and age-related conditions.",
    Tag TEXT
      String "Work on the enzyme has become a hot area of drug research, particularly in cancer, as it is thought to play a key role in allowing tumor cells to reproduce out of control.",
    Tag TEXT
      String "One example, a so-called therapeutic vaccine that targets telomerase, in trials since last year by drug and biotech firms Merck and Geron, could yield a treatment for patients with tumors including lung and prostate cancer.",
    Tag TEXT
      String "The Chief Executive of Britain's Medical Research Council said the discovery of telomerase had spawned research of 'huge importance' to the world of science and medicine.",
    Tag TEXT
      String "'Their research on chromosomes helped lay the foundations of future work on cancer, stem cells and even human aging, areas that continue to be of huge importance,' Sir Leszek Borysiewicz said in a statement."
  ]