Difference between revisions of "Hask"

From HaskellWiki
Jump to navigation Jump to search
(Add a section on limits failing to match up with Haskell datatypes)
(id is a function :))
(19 intermediate revisions by 2 users not shown)
Line 1: Line 1:
'''Hask''' is the name usually given to the [[Category theory|category]] having Haskell types as objects and Haskell functions between them as morphisms.
+
'''Hask''' is the [[Category theory|category]] of Haskell types and functions.
   
  +
The objects of '''Hask''' are Haskell types, and the morphisms from objects <hask>A</hask> to <hask>B</hask> are Haskell functions of type <hask>A -> B</hask>. The identity morphism for object <hask>A</hask> is <hask>id :: A -> A</hask>, and the composition of morphisms <hask>f</hask> and <hask>g</hask> is <hask>f . g = \x -> f (g x)</hask>.
A type-constructor that is an instance of the Functor class is an endofunctor on Hask.
 
   
  +
== Is '''Hask''' even a category? ==
* [http://www.cs.gunma-u.ac.jp/~hamana/Papers/cpo.pdf Makoto Hamana: ''What is the category for Haskell?'']
 
   
  +
Consider:
A solution approach to the issue of partiality making many of the identities required by categorical constructions not literally true in Haskell:
 
   
  +
<haskell>
* [http://www.cs.nott.ac.uk/~nad/publications/danielsson-popl2006-tr.pdf Nils A. Danielsson, John Hughes, Patrik Jansson, and Jeremy Gibbons. ''Fast and loose reasoning is morally correct.'']
 
  +
undef1 = undefined :: a -> b
  +
undef2 = \_ -> undefined
  +
</haskell>
   
  +
Note that these are not the same value:
   
  +
<haskell>
  +
seq undef1 () = undefined
  +
seq undef2 () = ()
  +
</haskell>
   
  +
This might be a problem, because <hask>undef1 . id = undef2</hask>. In order to make '''Hask''' a category, we define two functions <hask>f</hask> and <hask>g</hask> as the same morphism if <hask>f x = g x</hask> for all <hask>x</hask>. Thus <hask>undef1</hask> and <hask>undef2</hask> are different ''values'', but the same ''morphism'' in '''Hask'''.
== The seq problem ==
 
   
  +
== '''Hask''' is not Cartesian closed ==
The right identity law fails in '''Hask''' if we distinguish values which can be distinguished by <hask>seq</hask>, since:
 
   
  +
Actual '''Hask''' does not have sums, products, or an initial object, and <hask>()</hask> is not a terminal object. The Monad identities fail for almost all instances of the Monad class.
<hask>id . undefined = \x -> id (undefined x) = \x -> undefined x</hask>
 
   
  +
{| class="wikitable"
should be equal to <hask>undefined</hask>, but can be distinguished from it using <hask>seq</hask>:
 
  +
|+ Why '''Hask''' isn't as nice as you'd thought.
  +
! scope="col" |
  +
! scope="col" | Initial Object
  +
! scope="col" | Terminal Object
  +
! scope="col" | Sum
  +
! scope="col" | Product
  +
! scope="col" | Product
  +
|-
  +
! scope="row" | Type
  +
| <hask>data Empty</hask>
  +
| <hask>data () = ()</hask>
  +
| <hask>data Either a b
  +
= Left a | Right b</hask>
  +
| <hask>data (a,b) =
  +
(,) { fst :: a, snd :: b}</hask>
  +
| <hask>data P a b =
  +
P {fstP :: !a, sndP :: !b}</hask>
  +
|-
  +
! scope="row" | Requirement
  +
| There is a unique function
  +
<br /><hask>u :: Empty -> r</hask>
  +
| There is a unique function
  +
<br /><hask>u :: r -> ()</hask>
  +
| For any functions
  +
<br /><hask>f :: a -> r</hask>
  +
<br /><hask>g :: b -> r</hask>
   
  +
there is a unique function
ghci> <hask>(undefined :: Int -> Int) `seq` ()</hask>
 
  +
<hask>u :: Either a b -> r</hask>
* Exception: Prelude.undefined
 
ghci> <hask>(id . undefined :: Int -> Int) `seq` ()</hask>
 
()
 
   
  +
such that:
== The limits problem ==
 
  +
<hask>u . Left = f</hask>
  +
<br /><hask>u . Right = g</hask>
  +
| For any functions
  +
<br /><hask>f :: r -> a</hask>
  +
<br /><hask>g :: r -> b</hask>
   
  +
there is a unique function
Even in the absence of seq, bottoms cause datatypes to not actually be instances of the expected categorical constructions. For instance, using some intuition from the category of sets, one might expect the following:
 
  +
<hask>u :: r -> (a,b)</hask>
   
  +
such that:
<haskell>
 
  +
<hask>fst . u = f</hask>
data Void -- no elements ; initial object
 
  +
<br /><hask>snd . u = g</hask>
data () = () -- terminal object
 
  +
| For any functions
  +
<br /><hask>f :: r -> a</hask>
  +
<br /><hask>g :: r -> b</hask>
   
  +
there is a unique function
data (a, b) = (a, b) -- product
 
  +
<hask>u :: r -> P a b</hask>
data Either a b = Left a | Right b -- coproduct
 
</haskell>
 
   
  +
such that:
However, Void actually does contain an element, bottom, so for each <code>x :: T</code>, <code>const x</code> is a different function <code>Void -> T</code>, meaning <code>Void</code> isn't initial (it's actually terminal).
 
  +
<hask>fstP . u = f</hask>
  +
<br /><hask>sndP . u = g</hask>
  +
|-
  +
! scope="row" | Candidate
  +
| <hask>u1 r = case r of {}</hask>
  +
| <hask>u1 _ = ()</hask>
  +
| <hask>u1 (Left a) = f a</hask>
  +
<br /><hask>u1 (Right b) = g b</hask>
  +
| <hask>u1 r = (f r,g r)</hask>
  +
| <hask>u1 r = P (f r) (g r)</hask>
  +
|-
  +
! scope="row" | Example failure condition
  +
| <hask>r ~ ()</hask>
  +
| <hask>r ~ ()</hask>
  +
| <hask>r ~ ()</hask>
  +
<br /><hask>f _ = ()</hask>
  +
<br /><hask>g _ = ()</hask>
  +
| <hask>r ~ ()</hask>
  +
<br /><hask>f _ = undefined</hask>
  +
<br /><hask>g _ = undefined</hask>
  +
| <hask>r ~ ()</hask>
  +
<br /><hask>f _ = ()</hask>
  +
<br /><hask>g _ = undefined</hask>
  +
|-
  +
! scope="row" | Alternative u
  +
| <hask>u2 _ = ()</hask>
  +
| <hask>u2 _ = undefined</hask>
  +
| <hask>u2 _ = ()</hask>
  +
| <hask>u2 _ = undefined</hask>
  +
|
  +
|-
  +
! scope="row" | Difference
  +
| <hask>u1 undefined = undefined</hask>
  +
<br /><hask>u2 undefined = ()</hask>
  +
| <hask>u1 _ = ()</hask>
  +
<br /><hask>u2 _ = undefined</hask>
  +
| <hask>u1 undefined = undefined</hask>
  +
<br /><hask>u2 undefined = ()</hask>
  +
| <hask>u1 _ = (undefined,undefined)</hask>
  +
<br /><hask>u2 _ = undefined</hask>
  +
| <hask>f _ = ()</hask>
  +
<br /><hask>(fstP . u1) _ = undefined</hask>
  +
|- style="background: red;"
  +
! scope="row" | Result
  +
! scope="col" | FAIL
  +
! scope="col" | FAIL
  +
! scope="col" | FAIL
  +
! scope="col" | FAIL
  +
! scope="col" | FAIL
  +
|}
   
  +
== "Platonic" '''Hask''' ==
Similarly, <code>const undefined</code> and <code>const ()</code> are two distinct functions into <code>()</code>. Consider:
 
   
  +
Because of these difficulties, Haskell developers tend to think in some subset of Haskell where types do not have bottom values. This means that it only includes functions that terminate, and typically only finite values. The corresponding category has the expected initial and terminal objects, sums and products, and instances of Functor and Monad really are endofunctors and monads.
<haskell>
 
t :: () -> Int
 
t () = 5
 
   
  +
== Links ==
t . const () = \x -> 5
 
t . const undefined = \x -> undefined
 
</haskell>
 
   
  +
* [http://www.cs.gunma-u.ac.jp/~hamana/Papers/cpo.pdf Makoto Hamana: ''What is the category for Haskell?'']
So, () is not terminal.
 
  +
* [http://www.cs.nott.ac.uk/~nad/publications/danielsson-popl2006-tr.pdf Nils A. Danielsson, John Hughes, Patrik Jansson, and Jeremy Gibbons. ''Fast and loose reasoning is morally correct.'']
 
Similar issues occur with (co)products. Categorically:
 
 
<haskell>
 
\p -> (fst p, snd p) = id
 
 
\s -> case s of Left x -> p (Left x) ; Right y -> p (Right y) = p
 
</haskell>
 
 
but in Haskell
 
 
<haskell>
 
id undefined = undefined /= (undefined, undefined) = (fst undefined, snd undefined)
 
 
const 5 undefined = 5
 
/= undefined = case undefined of
 
Left x -> const 5 (Left x)
 
Right y -> const 5 (Right y)
 
</haskell>
 
   
{{stub}}
 
 
[[Category:Mathematics]]
 
[[Category:Mathematics]]
 
[[Category:Theoretical foundations]]
 
[[Category:Theoretical foundations]]

Revision as of 20:35, 13 September 2012

Hask is the category of Haskell types and functions.

The objects of Hask are Haskell types, and the morphisms from objects A to B are Haskell functions of type A -> B. The identity morphism for object A is id :: A -> A, and the composition of morphisms f and g is f . g = \x -> f (g x).

Is Hask even a category?

Consider:

undef1 = undefined :: a -> b
undef2 = \_ -> undefined

Note that these are not the same value:

seq undef1 () = undefined
seq undef2 () = ()

This might be a problem, because undef1 . id = undef2. In order to make Hask a category, we define two functions f and g as the same morphism if f x = g x for all x. Thus undef1 and undef2 are different values, but the same morphism in Hask.

Hask is not Cartesian closed

Actual Hask does not have sums, products, or an initial object, and () is not a terminal object. The Monad identities fail for almost all instances of the Monad class.

Why Hask isn't as nice as you'd thought.
Initial Object Terminal Object Sum Product Product
Type data Empty data () = () data Either a b = Left a | Right b data (a,b) = (,) { fst :: a, snd :: b} data P a b = P {fstP :: !a, sndP :: !b}
Requirement There is a unique function


u :: Empty -> r

There is a unique function


u :: r -> ()

For any functions


f :: a -> r
g :: b -> r

there is a unique function u :: Either a b -> r

such that: u . Left = f
u . Right = g

For any functions


f :: r -> a
g :: r -> b

there is a unique function u :: r -> (a,b)

such that: fst . u = f
snd . u = g

For any functions


f :: r -> a
g :: r -> b

there is a unique function u :: r -> P a b

such that: fstP . u = f
sndP . u = g

Candidate u1 r = case r of {} u1 _ = () u1 (Left a) = f a


u1 (Right b) = g b

u1 r = (f r,g r) u1 r = P (f r) (g r)
Example failure condition r ~ () r ~ () r ~ ()


f _ = ()
g _ = ()

r ~ ()


f _ = undefined
g _ = undefined

r ~ ()


f _ = ()
g _ = undefined

Alternative u u2 _ = () u2 _ = undefined u2 _ = () u2 _ = undefined
Difference u1 undefined = undefined


u2 undefined = ()

u1 _ = ()


u2 _ = undefined

u1 undefined = undefined


u2 undefined = ()

u1 _ = (undefined,undefined)


u2 _ = undefined

f _ = ()


(fstP . u1) _ = undefined

Result FAIL FAIL FAIL FAIL FAIL

"Platonic" Hask

Because of these difficulties, Haskell developers tend to think in some subset of Haskell where types do not have bottom values. This means that it only includes functions that terminate, and typically only finite values. The corresponding category has the expected initial and terminal objects, sums and products, and instances of Functor and Monad really are endofunctors and monads.

Links