[Haskell-cafe] Why aren't there anonymous sum types in Haskell?
pipoca
eliyahu.ben.miney at gmail.com
Wed Jun 22 22:25:10 CEST 2011
On Jun 22, 2:19 pm, "wren ng thornton" <w... at freegeek.org> wrote:
> > 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?
More information about the Haskell-Cafe
mailing list