1 Category Theory
Total Page:16
File Type:pdf, Size:1020Kb
{-# LANGUAGE RankNTypes #-} module AbstractNonsense where import Control.Monad 1 Category theory Definition 1. A category consists of • a collection of objects • and a collection of morphisms between those objects. We write f : A → B for the morphism 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 category theory apply to them. As an example consider the cate- gories • Set whose objects are sets and morphisms are functions between those sets. • Grp whose objects are groups and morphisms are group homomorphisms, i.e. structure preserving functions, between those groups. 1.1 Functors Category theory is mainly interested in relationships between different kinds of mathematical structures. Therefore the fundamental notion of a functor 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 natural transformation. 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 function, 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 () = () Coproduct 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 map 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 class 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 monoid (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 .