Re: [Haskell-cafe] Why aren't there anonymous sum types in Haskell?

On 6/21/11 10:48 PM, Casey McCann wrote:
On Tue, Jun 21, 2011 at 9:51 PM, wren ng thornton
wrote: I don't think there are any problems[1]. (...) [1] modulo the A:+:A ~ A issue.
Oops, I should've said A:*:A there.
That issue is exactly my concern, though, and it seems a bit too thorny to handwave aside.
Indeed. If we have A:*:A ~ A, then A:*:A is not a categorical product. The reasoning is as follows. An object A*B with morphisms fst :: A*B->A and snd :: A*B->B is a product iff for all objects P with morphisms p1 :: P -> A and p2 :: P -> B, there is a unique morphism p1&&&p2 :: P -> A*B, such that p1 = fst . p1&&&p2 and p2 = snd . p1&&&p2. Given the definition, if we further say that A*A ~ A, then it's clear that we can't come up with any satisfactory definitions of fst and snd which obey the laws--- unless there can be only one morphism between any two objects, in which case we know that p1 = p2 and so it's okay for fst = snd; or unless there can be only two morphisms between any two objects and we have a canonical property for distinguishing them so that we can correlate p1 with fst and p2 with snd. In all other cases, there are simply too many possible choices of p1 and p2, and there's no way for fst and snd to carry enough information to make the equations hold. What that means then is that the category which tries to use :*: to make products would only have products in the cases where the first and second component are different; which would be a strange category indeed. Alternatively, it could always have products but would only allow one morphism between objects; in which case the category is just a meet-semilattice (actually, the preorder generalization thereof).
In contrast, ordered pairs and disjoint unions are tidy, simple, and obvious.
Disjoint pairs are sufficient; they needn't be ordered. All we need is that they are "tagged" in the same way that disjoint unions are, so that we can distinguish the components of A*A. -- Live well, ~wren

On Jun 22, 2:19 pm, "wren ng thornton"
In contrast, ordered pairs and disjoint unions are tidy, simple, and obvious.
Disjoint pairs are sufficient; they needn't be ordered. All we need is that they are "tagged" in the same way that disjoint unions are, so that we can distinguish the components of A*A.
So union types are a bad idea; disjoint unions are the far superior option for a variety of reasons. Is there any reason why we don't have either anonymous disjoint union types, or why some of the proposals here (e.g. type (:|:) a b = Either a b ) haven't been implemented, or put into the standard libraries (and publicised in beginner texts)? Also, I don't think that the formulation of (:|:) above is sufficient. Suppose: foo :: Foo -> Bar baz :: Baz -> Quux foobaz :: [Foo :|: Baz] -- map foo and baz over foobaz barquux :: [Bar :|: Quux] barquux = map f foobaz how would f be implemented? It seems to me that you'd need an additional function: either' :: (a -> c) -> (b -> d) -> Either a b -> Either c d However, it still seems to me that that isn't sufficient. Suppose instead: a :: A -> B :|: C d :: D -> E :|: F ad :: [A :|: D] if we want to map a and d over ad using either' to get bcef :: [B :|: C :|: E :|: F] it wouldn't work, we'd get bcef :: [(B :|: C) :|: (E :|: F)] i.e. bcef :: [Either (Either B C) (Either E F)] instead, which is presumably not what we wanted... Is there a better formulation or something that would allow you to do that?

On Wed, Jun 22, 2011 at 1:25 PM, pipoca
Also, I don't think that the formulation of (:|:) above is sufficient. Suppose:
foo :: Foo -> Bar baz :: Baz -> Quux
foobaz :: [Foo :|: Baz]
-- map foo and baz over foobaz barquux :: [Bar :|: Quux] barquux = map f foobaz how would f be implemented?
It seems to me that you'd need an additional function: either' :: (a -> c) -> (b -> d) -> Either a b -> Either c d
Sure, you would want to treat Either as a bifunctor. Your either' function is usually called bimap. So the call would look like: map (bimap f g) foobaz for some f and g.
However, it still seems to me that that isn't sufficient. Suppose instead:
a :: A -> B :|: C d :: D -> E :|: F
ad :: [A :|: D]
if we want to map a and d over ad using either' to get bcef :: [B :|: C :|: E :|: F] it wouldn't work, we'd get bcef :: [(B :|: C) :|: (E :|: F)] i.e. bcef :: [Either (Either B C) (Either E F)] instead, which is presumably not what we wanted...
You need is a proof that :|: is associative. In other words, we need to pick a "normal form" for expressions like (a :|: (b :|: c)) and ((a :|: b) :|: c) and show that they can all be normalized into the normal form. I use a typeclass: class Monic a b where inject :: a -> b for that kind of work. I always have an instance instance Monic a a where inject = id so I might pick to write: instance Monic ((a :|: b) :|: c) (a :|: (b :|: c)) where inject (Left (Left a)) = Left a inject (Left (Right b)) = (Right (Left b)) inject (Right c) = (Right (Right c)) If you do that, you will soon run into two other problems I can think of (relating to MacLane's coherence conditions, which I think would be fixed by judicious composition with "inject"). You're building up (Either a b) into a monoidal category. There used to be a package called category-extras for this kind of stuff. I think it has been broken up. Does anybody know the status of its replacement(s)?

On Wed, Jun 22, 2011 at 5:00 PM, Alexander Solla
You're building up (Either a b) into a monoidal category. There used to be a package called category-extras for this kind of stuff. I think it has been broken up. Does anybody know the status of its replacement(s)?
You probably want to look at Edward Kmett's github: http://github.com/ekmett Also, both bifunctors and monoidal categories seem to now be in the "categories" package, which is on Hackage: http://hackage.haskell.org/package/categories - C.

On Wed, Jun 22, 2011 at 1:25 PM, pipoca
Is there any reason why we don't have either anonymous disjoint union types, or why some of the proposals here (e.g. type (:|:) a b = Either a b ) haven't been implemented, or put into the standard libraries (and publicised in beginner texts)?
I know that {-# LANGUAGE TypeOperators #-} has been in GHC for a while, but I'm not sure how widely accepted among other Haskell implementations it is. It seems to me that you'd need an additional function:
either' :: (a -> c) -> (b -> d) -> Either a b -> Either c d
import Control.Arrow (+++, |||) The '+++' operator from ArrowChoice already does what you need here. And the '|||' operator is a more generic form of the '???' operator I mentioned earlier.
if we want to map a and d over ad using either' to get bcef :: [B :|: C :|: E :|: F] it wouldn't work, we'd get bcef :: [(B :|: C) :|: (E :|: F)] instead, which is presumably not what we wanted...
Actually, we do want [(B :|: C) :|: (E :|: F)] in this case. It's important for generic programming. However, these types are associative, so we could develop a standard set of re-association operators.

On Wed, Jun 22, 2011 at 2:19 PM, wren ng thornton
[1] modulo the A:+:A ~ A issue.
Oops, I should've said A:*:A there.
That issue is exactly my concern, though, and it seems a bit too thorny to handwave aside.
Indeed. If we have A:*:A ~ A, then A:*:A is not a categorical product. (...)
Thank you, that clarified my intuitive sense of why it didn't seem to work. The same argument, with arrows flipped appropriately, would apply to a hypothetical coproduct where A :+: A ~ A, wouldn't it?
Disjoint pairs are sufficient; they needn't be ordered. All we need is that they are "tagged" in the same way that disjoint unions are, so that we can distinguish the components of A*A.
Oh. Yes, of course, I probably knew that. I think confused myself by habitually calling the components "fst" and "snd". Sigh. - C.
participants (5)
-
Alexander Solla
-
Casey McCann
-
David Barbour
-
pipoca
-
wren ng thornton