ANN: data-category, restricted categories

Hi everybody, At ZuriHac I released data-category. It is an implementation of several category-theoretical constructions. I started this library to learn about both category theory and type level programming, so I wanted to implement the CT concepts as directly as possible. This in contrast to the excellent category-extras library, which (I think) also tries to be as useful as possible. CT is about studying categories, so for data-category I wanted to implement all kinds of categories. The Control.Category module unfortunately requires you to implement id :: cat a a (for all a), which means it only supports categories that have exactly the same objects as Hask. So Data.Category contains an implementation of restricted categories, using inspiration from Oleg's restricted monads. It is well known that the Functor class also is a bit limited, as it only supports endofunctors in Hask. But there's another problem, if you want to define the identity functor, or the composition of 2 functors, then you have to use newtype wrappers, which can get in the way. Data.Category has an implementation of functors which solves this by using type families. Functors are represented by labels, and the type family F turns the label into the actual functor. F.e. type instance F List a = [a], type instance F Id a = a. The current version contains: - categories - Void, Unit, Pair (discrete categories with 0, 1 and 2 objects respectively) - Boolean - Omega, the natural numbers as an ordered set (ω) - Monoid - Functor, the category of functors from one category to another - Hask - Kleisli - Alg, the category of F-Algebras - functors - the identity functor - functor composition - the constant functor - the co- and contravariant Hom-functors - the diagonal functor - natural transformations - universal arrows - limits and colimits (as universal arrows from/to the diagonal functor) - using Void as index category this gives initial and terminal objects - f.e. in Alg the arrows from the initial object are catamorphisms - using Pair as index category this gives products and coproducts - f.e. in Omega they are the minimum and maximum and in Boolean and and or. - adjunctions Of course the are still a lot of things missing, especially in the details. And I'm a category theory beginner, so there will probably be some mistakes in there as well. F.e. Edward Kmett doesn't like () being the terminal object in Hask, which I thought I understood, but after thinking about it a bit more I don't. You can find data-category on hackage and on github: http://hackage.haskell.org/package/data-category http://github.com/sjoerdvisscher/data-category greetings, Sjoerd Visscher

Mainly that category-extras doesn't have restricted categories, so most of the categories in data-category cannot be defined with category-extras. This also means that in category-extras many constructions are built from the ground up, instead of being built with a few basic building blocks, because that often requires a restricted category. But data-category certainly isn't meant as a replacement of category-extras. It is a totally different way of working with CT. On Mar 22, 2010, at 6:10 PM, Maciej Piechotka wrote:
Hmm. What are benefits of data-category over category-extras?
Regards
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Sjoerd Visscher http://w3future.com

On Mon, Mar 22, 2010 at 12:33 PM, Sjoerd Visscher
Of course the are still a lot of things missing, especially in the details. And I'm a category theory beginner, so there will probably be some mistakes in there as well. F.e. Edward Kmett doesn't like () being the terminal object in Hask, which I thought I understood, but after thinking about it a bit more I don't.
I love the library. Don't get me wrong. =) As for (), consider: data Unit unit :: Unit unit = undefined is ever so slightly more anally retentive about being a true terminal object. There is only one canonical morphism from every object in Hask to Unit: terminate :: a -> Unit terminate = const unit -- as long as you're ignoring 'seq' terminateSeq :: a -> Unit terminateSeq a = a `seq` unit -- And of course with runtime exception catching you can distinguish a whole lot more and the category theoretic viewpoint becomes mostly useless. ;) Regardless, continuing to ignore seq there are two morphisms of type a -> (). terminate1 :: a -> () terminate1 _ = () terminate2 :: a -> () terminate2 _ = undefined -- discounting the extraneous terminateUnitSeq a = a `seq` undefined So taking the definition of a terminal object being that there exists one canonical arrow to the object from every object in Hask, Unit seems to fit the bill. This is as opposed to the pleasant fiction of an initial object: data Void -- or newtype Void = Void Void -- or newtype Void = Void { void :: forall a. a } which should have a morphism Void -> a for every type, but which should never be inhabited, but alas, bottom infects every type in Haskell, so ultimately each of these is Unit with an additional unsafe morphism. If it could exist then Right undefined :: Either a Void should fail to typecheck and Either a Void -> a should be a total function. Welcome to Coq or Adga. ;) Of course, you can argue that we already look at products and coproducts through fuzzy lenses that don't see the extra bottom, and that it is close enough to view () as Unit and Unit as Void, or go so far as to unify Unit and Void, even though one is always inhabited and the other should never be. But in the sea of ideas that don't quite map onto Haskell, I can at least go out of my way to make sure that my terminal object is terminal. =)

On Fri, Mar 26, 2010 at 11:04 AM, Edward Kmett
-- as long as you're ignoring 'seq' terminateSeq :: a -> Unit terminateSeq a = a `seq` unit
Er ignore that language about seq. a `seq` unit is either another bottom or undefined, so there remains one canonical morphism even in the presence of seq (ignoring unsafePerformIO) =)
-- discounting the extraneous terminateUnitSeq a = a `seq` undefined
-- and here I should have said. terminateUnitSeq a = a `seq` () -Edward Kmett

On Fri, Mar 26, 2010 at 11:07 AM, Edward Kmett
On Fri, Mar 26, 2010 at 11:04 AM, Edward Kmett
wrote: -- as long as you're ignoring 'seq' terminateSeq :: a -> Unit terminateSeq a = a `seq` unit
Er ignore that language about seq. a `seq` unit is either another bottom or undefined, so there remains one canonical morphism even in the presence of seq (ignoring unsafePerformIO) =)
It all depends on how you define equality for functions. If you mean
indistinguishable in contexts which may involve seq, then there are at
least two values of type Unit -> ().
foo :: (Unit -> ()) -> ()
foo x = x `seq` ()
foo terminate = ()
foo undefined = undefined
Even this uses the convention that undefined = error "whatever" =
loop, which isn't technically true, since you can use exception
handling to write code which treats them differently.
--
Dave Menendez

Very true. I oversimplified matters by mistake.
One question, I suppose, is does seq distinguish the arrows, or does it
distinguish the exponential objects in the category? since you are using it
as an object in order to apply seq, and does that distinction matter? I'd
hazard not, but its curious to me.
2010/3/26 David Menendez
On Fri, Mar 26, 2010 at 11:07 AM, Edward Kmett
wrote: On Fri, Mar 26, 2010 at 11:04 AM, Edward Kmett
wrote: -- as long as you're ignoring 'seq' terminateSeq :: a -> Unit terminateSeq a = a `seq` unit
Er ignore that language about seq. a `seq` unit is either another bottom
or
undefined, so there remains one canonical morphism even in the presence of seq (ignoring unsafePerformIO) =)
It all depends on how you define equality for functions. If you mean indistinguishable in contexts which may involve seq, then there are at least two values of type Unit -> ().
foo :: (Unit -> ()) -> () foo x = x `seq` ()
foo terminate = () foo undefined = undefined
Even this uses the convention that undefined = error "whatever" = loop, which isn't technically true, since you can use exception handling to write code which treats them differently.
-- Dave Menendez
<http://www.eyrie.org/~zednenem/ http://www.eyrie.org/%7Ezednenem/>

Edward Kmett wrote:
Of course, you can argue that we already look at products and coproducts through fuzzy lenses that don't see the extra bottom, and that it is close enough to view () as Unit and Unit as Void, or go so far as to unify Unit and Void, even though one is always inhabited and the other should never be.
The alternative is to use _consistently_ "fuzzy lenses" and not consider bottom to be a value. I call this the "bottomless" interpretation. I prefer it, because it's easier to reason about. In the bottomless interpretation, laws for Functor, Monad etc. work. Many widely-accepted instances of these classes fail these laws when bottom is considered a value. Even reflexivity of Eq fails. Bear in mind bottom includes non-termination. For instance: x :: Integer x = x + 1 data Nothing n :: Nothing n = seq x undefined x is bottom, since calculation of it doesn't terminate, but one cannot write a program even in IO to determine that x is bottom. And if Nothing is inhabited with a value, does n have that value? Or does the calculation to find which value n is not terminate, so n never gets a value? I avoid explicit "undefined" in my programs, and also hopefully non-termination. Then the bottomless interpretation becomes useful, for instance, to consider Nothing as an initial object of Hask particularly when using GADTs. I also dislike "Void" for a type declared empty, since it reminds me of the C/C++/C#/Java return type "void". In those languages, a function of return type "void" may either terminate or not, exactly like Haskell's "()". -- Ashley Yakeley

Quoting Ashley Yakeley
data Nothing
I avoid explicit "undefined" in my programs, and also hopefully non-termination. Then the bottomless interpretation becomes useful, for instance, to consider Nothing as an initial object of Hask particularly when using GADTs.
Forgive me if this is stupid--I'm something of a category theory newbie--but I don't see that Hask necessarily has an initial object in the bottomless interpretation. Suppose I write data Nothing2 Then if I understand this correctly, for Nothing to be an initial object, there would have to be a function f :: Nothing -> Nothing2, which seems hard without bottom. This is a difference between Hask and Set, I guess: we can't write down the "empty function". (I suppose unsafeCoerce might have that type, but surely if you're throwing out undefined you're throwing out the more frightening things, too...) ~d

wagnerdm@seas.upenn.edu wrote:
Forgive me if this is stupid--I'm something of a category theory newbie--but I don't see that Hask necessarily has an initial object in the bottomless interpretation. Suppose I write
data Nothing2
Then if I understand this correctly, for Nothing to be an initial object, there would have to be a function f :: Nothing -> Nothing2, which seems hard without bottom.
This is a difference between Hask and Set, I guess: we can't write down the "empty function".
Right. It's an unfortunate limitation of the Haskell language that one cannot AFAIK write this: f :: Nothing -> Nothing2; f n = case n of { }; However, one can work around it with this function: never :: Nothing -> a never n = seq n undefined; Of course, this workaround uses undefined, but at least "never" has the property that it doesn't return bottom unless it is passed bottom. -- Ashley Yakeley

The uniqueness of the definition of Nothing only holds up to isomorphism.
This holds for many unique types, products, sums, etc. are all subject to
this multiplicity of definition when looked at through the concrete-minded
eye of the computer scientist.
The mathematician on the other hand can put on his fuzzy goggles and just
say that they are all the same up to isomorphism. =)
-Edward Kmett
On Tue, Mar 30, 2010 at 3:45 PM,
Quoting Ashley Yakeley
: data Nothing
I avoid explicit "undefined" in my programs, and also hopefully non-termination. Then the bottomless interpretation becomes useful, for instance, to consider Nothing as an initial object of Hask particularly when using GADTs.
Forgive me if this is stupid--I'm something of a category theory newbie--but I don't see that Hask necessarily has an initial object in the bottomless interpretation. Suppose I write
data Nothing2
Then if I understand this correctly, for Nothing to be an initial object, there would have to be a function f :: Nothing -> Nothing2, which seems hard without bottom. This is a difference between Hask and Set, I guess: we can't write down the "empty function". (I suppose unsafeCoerce might have that type, but surely if you're throwing out undefined you're throwing out the more frightening things, too...)
~d
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Getting back to the question, whatever happened to empty case
expressions? We should not need bottom to write total functions from
empty types.
Correspondingly, we should have that the map from an empty type to
another given type is unique extensionally, although it may have many
implementations. Wouldn't that make any empty type initial? Of course,
one does need one's isogoggles on to see the uniqueness of the initial
object.
An empty type is remarkably useful, e.g. as the type of free variables
in closed terms, or as the value component of the monadic type of a
server process. If we need bottom to achieve vacuous satisfaction,
something is a touch amiss.
Cheers
Conor
On 30 Mar 2010, at 22:02, Edward Kmett
The uniqueness of the definition of Nothing only holds up to isomorphism.
This holds for many unique types, products, sums, etc. are all subject to this multiplicity of definition when looked at through the concrete-minded eye of the computer scientist.
The mathematician on the other hand can put on his fuzzy goggles and just say that they are all the same up to isomorphism. =)
-Edward Kmett
On Tue, Mar 30, 2010 at 3:45 PM,
wrote: Quoting Ashley Yakeley : data Nothing
I avoid explicit "undefined" in my programs, and also hopefully non- termination. Then the bottomless interpretation becomes useful, for instance, to consider Nothing as an initial object of Hask particularly when using GADTs.
Forgive me if this is stupid--I'm something of a category theory newbie--but I don't see that Hask necessarily has an initial object in the bottomless interpretation. Suppose I write
data Nothing2
Then if I understand this correctly, for Nothing to be an initial object, there would have to be a function f :: Nothing -> Nothing2, which seems hard without bottom. This is a difference between Hask and Set, I guess: we can't write down the "empty function". (I suppose unsafeCoerce might have that type, but surely if you're throwing out undefined you're throwing out the more frightening things, too...)
~d
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I believe I was claiming that, in the absence of undefined, Nothing
and Nothing2 *aren't* isomorphic (in the CT sense).
But this is straying dangerously far from Ashley's point, which I
think is a perfectly good one: Hask without bottom is friendlier than
Hask with bottom.
~d
Quoting Edward Kmett
The uniqueness of the definition of Nothing only holds up to isomorphism.
This holds for many unique types, products, sums, etc. are all subject to this multiplicity of definition when looked at through the concrete-minded eye of the computer scientist.
The mathematician on the other hand can put on his fuzzy goggles and just say that they are all the same up to isomorphism. =)
-Edward Kmett
On Tue, Mar 30, 2010 at 3:45 PM,
wrote: Quoting Ashley Yakeley
: data Nothing
I avoid explicit "undefined" in my programs, and also hopefully non-termination. Then the bottomless interpretation becomes useful, for instance, to consider Nothing as an initial object of Hask particularly when using GADTs.
Forgive me if this is stupid--I'm something of a category theory newbie--but I don't see that Hask necessarily has an initial object in the bottomless interpretation. Suppose I write
data Nothing2
Then if I understand this correctly, for Nothing to be an initial object, there would have to be a function f :: Nothing -> Nothing2, which seems hard without bottom. This is a difference between Hask and Set, I guess: we can't write down the "empty function". (I suppose unsafeCoerce might have that type, but surely if you're throwing out undefined you're throwing out the more frightening things, too...)
~d
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

wagnerdm@seas.upenn.edu wrote:
I believe I was claiming that, in the absence of undefined, Nothing and Nothing2 *aren't* isomorphic (in the CT sense).
Well, this is only due to Haskell's difficulty with empty case expressions. If that were fixed, they would be isomorphic even without undefined. -- Ashley Yakeley

Of course Haskell' should have an empty case. As soon as empty data
declarations are allowed then empty case must be allowed just by using
common sense.
On Tue, Mar 30, 2010 at 11:03 PM, Ashley Yakeley
wagnerdm@seas.upenn.edu wrote:
I believe I was claiming that, in the absence of undefined, Nothing and Nothing2 *aren't* isomorphic (in the CT sense).
Well, this is only due to Haskell's difficulty with empty case expressions. If that were fixed, they would be isomorphic even without undefined.
-- Ashley Yakeley _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Ashley Yakeley wrote:
Edward Kmett wrote:
Of course, you can argue that we already look at products and coproducts through fuzzy lenses that don't see the extra bottom, and that it is close enough to view () as Unit and Unit as Void, or go so far as to unify Unit and Void, even though one is always inhabited and the other should never be.
The alternative is to use _consistently_ "fuzzy lenses" and not consider bottom to be a value. I call this the "bottomless" interpretation. I prefer it, because it's easier to reason about.
In the bottomless interpretation, laws for Functor, Monad etc. work. Many widely-accepted instances of these classes fail these laws when bottom is considered a value. Even reflexivity of Eq fails.
Worse than that, if bottom is a value, then Hask is not a category! Note that while undefined is bottom, (id . undefined) and (undefined . id) are not. That's a fuzzy lens... -- Ashley Yakeley

On Tuesday 30 March 2010 4:34:10 pm Ashley Yakeley wrote:
Worse than that, if bottom is a value, then Hask is not a category! Note that while undefined is bottom, (id . undefined) and (undefined . id) are not.
Hask can be a category even if bottom is a value, with slight modification. That specific problem can be overcome by eliminating seq (and associated stuff; strict fields, bang patterns, ...), because it is the only thing in the language that can distinguish between the extensionally equal: undefined \_ -> undefined the latter being what you get from id . undefined and undefined . id. Bottom, or more specifically, lifted types, tend to ruin other nice categorical constructions, though. Lifted sums are not Hask coproducts, lifted products are not Hask products, the "empty" type is terminal, rather than initial, and () isn't terminal. But, if we ignore bottoms, these deficiencies disappear. See, of course, Fast and Loose Reasoning is Morally Correct. * -- Dan [*] http://www.comlab.ox.ac.uk/jeremy.gibbons/publications/fast+loose.pdf
participants (10)
-
Ashley Yakeley
-
Conor McBride
-
Dan Doel
-
David Menendez
-
Edward Kmett
-
Lennart Augustsson
-
Maciej Piechotka
-
Ross Paterson
-
Sjoerd Visscher
-
wagnerdm@seas.upenn.edu