Hask
Hask is the category of Haskell types and functions.
Informally, 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)
.
However, subtleties arise from questions such as the following.
- When are two morphisms equal? People often like to reason using some axioms or rewrite theory, such as beta reduction and eta conversion, but these are subtle with non-termination. A more basic notion of equality comes from contextual equivalence, or observational equivalence, which requires us to pick a basic notion of observation (e.g. termination versus non-termination).
- Do we consider the entire Haskell language, or just a fragment? Possible language fragment choices are: do we focus on terminating programs? do we consider seq? do we consider errors and exceptions? what about unsafe functions? and do we only consider the kind
*
, or also other kinds? The choice of fragment that is used affects the contextual equivalence, the notions of observation, and the universal properties within the category.
One can easily make a syntactic category for a typed lambda calculus, and there are many books about this. Perhaps the first place this becomes delicate in Haskell is the fact that Haskell types are not unboxed by default. This means we have an undefined
expression at every type. Even the function type A -> B
, which we would like to use as the type of morphisms, is boxed.
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.
A way to resolve this would be to say that a morphism is not an arbitrary expression of type a -> b
, but rather an expression of the form \x -> e
, or an expression e
of type b
with a free variable x:a
. Indeed the latter is the usual way to build a syntactic category.
Does Hask have categorical coproducts and products?
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.
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
|
There is a unique function
|
For any functions
there is a unique function
such that:
|
For any functions
there is a unique function
such that:
|
For any functions
there is a unique function
such that:
|
Candidate | u1 r = case r of {}
|
u1 _ = ()
|
u1 (Left a) = f a
|
u1 r = (f r,g r)
|
u1 r = P (f r) (g r)
|
Example failure condition | r ~ ()
|
r ~ ()
|
r ~ ()
|
r ~ ()
|
r ~ ()
|
Alternative u | u2 _ = ()
|
u2 _ = undefined
|
u2 _ = ()
|
u2 _ = undefined
|
|
Difference | u1 undefined = undefined
|
u1 _ = ()
|
u1 undefined = undefined
|
u1 _ = (undefined,undefined)
|
f _ = ()
|
Result | FAIL | FAIL | FAIL | FAIL | FAIL |
Using unboxed types might alleviate some of these problems. For example, revisiting the first column, but using the UnliftedDatatypes extension, we can define
data UEmpty :: UnliftedType where
,
but now if we instist that u1
and u2
have type UEmpty -> ()
, then u2 undefined = undefined = u1 undefined
.
"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.