<<

{-# LANGUAGE RankNTypes #-}

AbstractNonsense where import Control.

1 theory

Definition 1. A category consists of • a collection of objects • and a collection of between those objects. We write f : A → B for the f connecting the object A to B. • Morphisms are closed under composition, i.e. for morphisms f : A → B and g : B → C there exists the composed morphism h = f ◦ g : A → C1. Furthermore we require that • Composition is associative, i.e.

f ◦ (g ◦ h) = (f ◦ g) ◦ h

• and for each object A there exists an identity morphism idA such that for all morphisms f : A → B:

f ◦ idB = idA ◦ f = f

Many mathematical structures form catgeories and thus the theorems and con- structions of apply to them. As an example consider the cate- gories • whose objects are sets and morphisms are functions between those sets. • Grp whose objects are groups and morphisms are homomorphisms, i.e. structure preserving functions, between those groups.

1.1 Category theory is mainly interested in relationships between different kinds of mathematical structures. Therefore the fundamental notion of a is introduced: 1The order of the composition is to be read from left to right in contrast to standard mathematical notation.

1 Definition 2. A functor F : C → D is a transformation between categories C and D. It is defined by its action on objects F (A) and morphisms F (f) and has to preserve the categorical structure, i.e. for any morphism f : A → B:

F (f(A)) = F (f)(F (A)) which can also be stated graphically as the commutativity of the following dia- gram: F (f) F (A) F (B)

f A B Alternatively we can state that functors preserve the categorical structure by the requirement to respect the composition of morphisms:

F (idC) = idD F (f) ◦ F (g) = F (f ◦ g)

1.2 Natural transformations Taking the construction a step further we can ask for transformations between functors. This idea is captured by the notion of a . Definition 3. A natural transformation η : F → G between functors F : C → D and G : C → D associates to each object A of C a morphism ηA such that for each morphism f : A → B the following diagram commutes: F (f) F (A) F (B)

ηA ηB

G(f) G(A) G(B)

The collection of all functors again forms a category with the natural transfor- mations as morphisms. This is enough notation to get us started and we can now look at how category theory applies to Haskell.

2 The catgeory Hask 2.1 Data types The category Hask of Haskell has data types as its objects. The morphisms f : T → U are simply given by , i.e. programs, of the specified types, e.g.

showSquare :: Int -> String showSquare x = show (x*x)

2 is a morphism between Int and String. Composition of morphisms is given by standard function composition (written as . in Haskell) which is associative and for any f :: a → b2 we have

f . (id :: a) = (id :: b) . f

2.2 Problems of lazyness In the category Hask morphisms are themselves objects of the corresponding function type, e.g. showSquare :: (Int → String)3. Unfortunately, many of the required constructions fail in Hask due to laziness. Consider for example the notion of a product. The product A × B of objects A and B is defined by two morphisms fst : A × B → B and snd : A × B → B such that for all morphisms f : C → A and g : C → B the following diagram commutes C g h f A A × Bsnd B fst with a unique morphism h : C → A × B. This is an example of a so called universal construction and the uniques of the morphism h implies that the product is unique (up to isomorphism). Proof. Assume there exists a second product A׈ B such that the above diagram commutes with a unique morphism hˆ. Then by identifying C with A׈ B and A × B from the corresponding diagrams we obtain unique morphisms times : A׈ B → A × B and times : A × B → A׈ B respectively. Now, by composition d we know that times ◦ times : A × B → A × B. Thus, times is an isomorphism d with inverse times. Furthermore, this isomorphism is unique. d In Hask each data type contains an additional value ⊥ corresponding to the failing or non-terminating computation. This leads to problems when we try to identify the tuple type with the categorical product.

fst :: (A,B) -> A snd :: (A,B) -> B

f :: C -> A g :: C -> B

delta :: (C -> A) -> (C -> B) -> (C -> (A,B)) delta f g = \x -> (f x, g x)

2Note that Haskell uses lower case letters to denote type variables and function composition is defined from right to left. 3A category with this and additional properties (products, terminal object, . . . ) is called cartesian closed. The category Set is another example since mappings between sets are themselves sets.

3 h :: C -> (A,B) h = delta f g

The commutativity of the diagram requires

f = fst . h and g = snd . h which holds with the provided definitions. Unfortunately h is not unique for special empty types A, B and C.

data A data B data C

instance Show A where show _ = "A"

instance Show B where show _ = "B"

instance Show C where show _ = "C"

f :: C -> A f _ = undefined

g :: C -> B g _ = undefined

h :: C -> (A,B) h _ = (undefined,undefined)

h’ :: C -> (A,B) h’ _ = undefined

Both h and h′ are valid candidates, but due to laziness they can be distinguished:

check tup = case tup of (_,_) -> True _ -> False

2.3 Practical issues Usually this sublety is ignored by assuming the category of strict computations. In this sense and for all practical purposes Hask forms a nice category where the standard constructions can be identified with certain type constructors: Initial object data Empty Terminal object data () = () data Either a b = Left a | Right b Product data (a,b) = (,) { fst :: a, snd :: b}

4 3 Functors and polymorphic functions 3.1 Functors In Haskell no function ever leaves the Haskell data types. Thus only endo- functors from Hask into (a subset of) Hask can be defined. Consider for example the subcategory Lst which only contains data types [A] that are lists of some type A. The idea is that the type constructor [] for lists forms a functor [] : Hask → Lst. Every object A of Hask is transformed to an object [A] of Lst. What about a morphism f : A → B? In Haskell this corresponds to a function f :: a -> b. We now need a new function f[] :: [a] → [b] which suggest to look at f :: [a] -> [b]. To define a proper functor this new function map f has to respect function compo- sition, i.e. map id = id

map f . map g = map (f . g) Indeed, these are the so called functor laws and the type functor is defined as follows: class Functor’ f where fmap’ :: (a -> b) -> (f a -> f b)

instance Functor’ [] where fmap’ = map

instance Functor’ Maybe where fmap’ f (Just x) = Just (f x) fmap’ f Nothing = Nothing Basically any composed data structure which has a meaningful notion of ap- plying a function to its parts can implement a functor instance. Nevertheless, it is important to check the functor laws since the are used internally by the compiler for optimizations, e.g. the second law allows to fuse two traversals into one! Exercise: 1. Define a Functor instance for binary trees, .i.e data Tree a = Leaf | Branch a (Tree a) (Tree a) and check the functor laws.

3.2 Natural transformations What are natural transformations in Haskell? Consider two functors, e.g. [] and Maybe. A natural transformation is a morphism η between those types such that: η :: [a] → Maybea

5 and for any type a and function f :: a− >b we require the following commuta- tivity:

(fmap f :: Maybe a -> Maybe b) . (eta :: [a] -> Maybe a) \ = (eta :: [b] -> Maybe b) . (fmap f :: [a] -> [b])

fmap f . eta = eta . fmap f

Interestingly, this property ensures that η cannot look inside its arguments, i.e. it cannot behave differently depending on the type that the list contains. It really captures the notion of a polymorphic function that works for any type and relates the structure of the functors, i.e. data constructors.

eta [] = Nothing eta (x:_) = Just x

Exercise: 1. Show that this definition gives a natural transformation.

2. Define a natural transformation from binary trees to lists and vice versa

4 Monads

Basically, a monad is a functor with additional structure that resembles prop- erties of a (therefore the name). Definition 4. A monad on a category C is a functor T : C → C together with two natural transformations η :1C → T and µ : T 2 → T (where T 2 is the functor T ◦ T : C → C. The following diagrams have to commute for each object A of C:

T (µA) ηT (A) T (T (T (A))) T (T (A)) T (A) T (T (A))

µT (A) µA) T (ηA) µA

µA µA T (T (A)) T (A) T (T (A)) T (A)

4.1 Monads in Haskell For reasons that hopefully become clear later, the natural transformations of a monad are called return and join in Haskell.

class Functor m => Monad’ m where return’ :: a -> m a join’ :: m (m a) -> m a

The commutativity of the above diagrams corresponds to the following monad laws:

6 join . join = join . fmap join

join . return = join . fmap return = id

fmap f . return = return . f fmap f . join = join . fmap (fmap f) where the last two equations specify that return and join are natural transfor- mations. Exercise: 1. Compare the last two monad laws to the law of a natural transformation fmap f . eta = eta . fmap f and show why the have to be defined as given. What do these laws mean and why are monads useful? Let us look at an example and consider the definition of the list monad:

-- instance Functor’ [] where -- fmap’ f xs = [ f x | x <- xs ]

instance Monad’ [] where return’ x = [x] join’ xss = [ x | xs <- xss, x <- xs ] -- concat xss

Mathematically this corresponds to the powerset functor: Powerset functor P on Set Given a set S and a morphism f : A → B Function type Definition P (f): P (A) → P (B) (P (f))(S)= {f(a): a ∈ S} ηS : S → P (S) ηS(x)= {x} µS : P (P (S)) → P (S) µS(L)= S L List monad [] on Hask Given a type t and a morphism f :: a → b Function type Definition fmap f :: [a] -> [b] fmapf xs = [ f x | x <- xs ] return :: a -> [a] return x = [x] join :: [[a]] -> [a] join xss = concat xss

Using these definitions we can now prove the monad laws. As an example, consider the laws join . fmap return = id:

(join . fmap return) xs = (concat . fmap return) xs = concat (fmap return xs) = concat [ return x | x <- xs ] = concat [ [x] | x <- xs ] = xs -- by definition of concat and join . return = id:

7 (join . return) xs = concat (return xs) = concat [xs] = xs

Exercise: 1. Proof the other monad laws for the list monad. 2. Define a monad instance for the Maybe functor and check the monad laws.

4.2 Monads and computations Why are monads useful? To answer this question consider that you could have derived monads when thinking about computations and chaining them together (remember the Parser example). Standard function composition allows you to connect a computation f :: a− >b to a computation g :: b− >c to obtain a new computation h :: a− >c.

h x = g (f x)

h = (flip (.)) f g

What if your computation is not as simple and each function not just computes a value, but also does some additional stuff (side effects) which need to be tracked? The parser was such a function, it consumes a string as input to compute the resulting parse, but in addition also the non-consumed input has to be tracked. As an other example consider a function which computes a value, but in addition logs some information. Collecting this information in a string would give you the following type4:

f :: a− > (b, String)

Hiding the details of the additional effects, such a type can be represented as f :: a− > mb where m is a suitable data structure (think functor) that includes the additional information. Now assume you are given two such functions, i.e. f :: a− > mb and g :: b− > mc. How would you compose such functions? This is were monads come into play, because they provide the required compos- ability:

compose :: (Functor m, Monad m) => (a -> m b) -> (b -> m c) -> (a -> m c) compose f g = join . fmap g . f -- compose f g = \x -> join (fmap g (f x)) To understand how this works, just follow the types:

f :: a -> m b f x :: m b

g :: b -> m c

4This is known as the Writer monad.

8 fmap g :: m b -> m (m c)

fmap g . f :: a -> m (m c)

join :: m (m c) -> m c

join . fmap g . f :: a -> m c Thus, monads allow the sequential composition of computational effects. This aspect is somewhat hidden when defining a monad in terms of join and return. The actual Monad class of Haskell exports another function (>>=) :: Monad m => m a -> (a -> m b) -> m which chains a monad with a monadic computation. For any functor, join and (>>=) are equivalent: m >>= f = join (fmap f m) join mm = mm >>= id Exercise: 1. Convince yourself that this equivalence holds. Hint: Make use of the identity monad which is based on the idenity func- tor: fmapidf = f

2. Show that the parser from the previous lectures forms a monad. Now it should also be clear, what kind of additional effects are provided by the list and Maybe monad: Maybe Computations that can fail, i.e. result in Nothing, and compose f g fails when f or g fail. List Computations that can result in any number of results, i.e. each compu- tation gives a list of possible results. With the given definition xs >>= f runs f on all values in xs and collects all resulting values. [1,2,3] >>= (\x -> [’a’,’b’,’c’] >>= (\y -> return (x,y))) == [ (x,y) | x <- [1,2,3], y <- [’a’,’b’,’c’] ] Therefore, this monad is sometimes also called the non-determinism monad. It corresponds to non-deterministic computations that can result in no or more than one value.

5 Yoneda’s lemma

Yoneda’s lemma is a famous theorem in category theory. Before we can state it additional terminology is required. Hom(A, B) denotes the collection of all morphisms from A to B. Here, we assume that Hom(A, B) is actually a set. If this is the case for all objects of a category C, the category is called locally small.

9 For any fixed object A of C, Hom(A, −): C → Set is a functor which takes each object B to its Hom-Set Hom(A, B). In Haskell this functor can be defined as follows:

data Hom a b = Hom (a -> b)

instance Functor (Hom a) where fmap g (Hom f) = Hom (g . f)

-- or directly using the type constructor (->) instance Functor ((->) a) where fmap g f = g . f

This definition can be read of from the following diagram: Hom(A,−)(g) Hom(A, −)(B) Hom(A, −)(C)

Hom(A,−) Hom(A,−) g B C Yoneda’s lemma5 now states that: Theorem 1. Let C be a locally-small category and F : C → Set. Then, for each object A of C, the natural transformations from Hom(A, −) to F are in one-to-one correspondence with the elements of F (A), i.e.

Nat(Hom(A, −), F ) =∼ F (A)

What would that mean in Haskell? First of all we stay in the category Hask for which we have already defined the Hom-functor. Consider any functor F : Hask− > Hask. We already know that natural transformations correspond to polymorphic func- tions. So, we should be able to follow the types and implement the isomorphism stated in Yoneda’s lemma:

iso :: Functor f => (forall b. (Hom a b -> f b)) -> f a iso’ :: Functor f => f a -> (Hom a b -> f b)

iso eta = eta (Hom id) iso’ fa (Hom g) = fmap g fa

Yoneda’s lemma now claims that iso and iso’ are inverses of each other. Con- sider a specific functor F , e.g. list, Maybe, and think of iso’ fa :: Hom A B -> F B as some kind of machine that you can hand a function f :: A− > B in Hom(A, B) to get back a result of type FB. Since this has to work for any type B which is unknown when the machine was created, the only way to im- plement such a machine is to keep some object of type F A in the machine and pass this to the function f whenever a result is requested:

5There is also a contra-variant version which consider the Hom-functor Hom(−,A).

10 (iso . iso’) fa = iso (iso’ fa) = iso ( \(Hom g) -> fmap g fa ) = ( \(Hom g) -> fmap g fa ) (Hom id) = fmap id fa = fa

The contra-variant version of the theorem is more interesting for theoretical computer science. Written in Haskell it reads as follows:

class ContraFunctor c where cmap :: (a -> b) -> c b -> c a

data Com a b = Com (b -> a)

instance ContraFunctor (Com a) where cmap g (Com f) = Com (f . g)

ciso :: ContraFunctor c => (forall b. (Com a b -> c b)) -> c a ciso’ :: ContraFunctor c => c a -> (Com a b -> c b)

ciso eta = eta (Com id) ciso’ ca (Com g) = cmap g ca

As it turns out, this definition has a close connection to continuation-passing style (CPS). CPS is a way to write a function that explicitly tracks what is being done with its return value. As an example consider the functions

incShow :: Integer -> String incShow x = show (x + 1)

fac :: Integer -> Float -- Just to distinguish input and output types fac n = if (n < 1) then 1.0 else (fromIntegral n) * (fac (n - 1))

In continuation-passing style, the same function looks as follows:

incShowCPS :: (String -> a) -> (Integer -> a) incShowCPS k x = k (show (x + 1))

facCPS :: (Float -> a) -> (Integer -> a) facCPS k n = if (n < 1) then k 1.0 else facCPS (\ c -> k (fromIntegral n * c)) (n - 1)

The first argument k is called the continuation and called on the value computed by the function (note that results of type Float are computed and in the then- branch instead of returning the value 1.0 it is handed to the continuation). In CPS every function is tail-recursive and the rest of the computation is handled in the new continuation that is handed to the recursive call. Thus, we have the following identities:

11 incShow = incShowCPS id fac = facCPS id

From the types, we can see that CPS corresponds to a contra-variant program transformation:

incShow :: Integer -> String fac :: Integer -> Float

get transformed to

incShowCPS :: (String -> a) -> (Integer -> a) facCPS :: (Float -> a) -> (Integer -> a)

Furthermore, we can see that the new types correspond to Com a String -> Com a Integer and Com a Float -> Com a Integer respectively. Yoneda’s lemma now states that programs in regular style and CPS are iso- morphic. Here, cmap f can be used to obtain a CPS version of the function f :: a− > b and ciso corresponds to running such a program on the identity continuation. Exercise 1. What are the types of cmap incShow and cmap fac? 2. What does ciso’ do? Hint: You might want to use flip :: (a -> b -> c) -> b -> a -> c to flip the arguments of ciso’ and

runCom :: Com a b -> b -> a runCom (Com f) x = f x

to get rid of the data constructor as necessary.

12