Proposal: merge Data.Functor.Coproduct into transformers

At the instigation of Edward Kmett, I hereby propose to merge Data.Functor.Coproduct module from comonad-transformers into transformers. The module defines the Coproduct data type, together with several class instances. All non-base instances would have to be left out, leaving the following instances to be merged in: instance (Functor f, Functor g) => Functor (Coproduct f g) instance (Foldable f, Foldable g) => Foldable (Coproduct f g) instance (Traversable f, Traversable g) => Traversable (Coproduct f g) Unfortunately, the Applicative and Monad instances cannot be defined on this type, though their duals can. In that sense, the existing comonad-transformers package is a more fitting home for the type. However, there are good reasons for the move: - The dual type of Coproduct, namely Data.Functor.Product, is already defined by transformers. It would make sense to keep the duals together. - Data.Functor.Compose and Data.Functor.Constant which also defined by transformers are not monads either, so there is precedent for having non-monads there. - Most obviously, transformers is a haskell-platform package while comonad-transformers seems unlikely to become one any time soon (as much as I'd like that). - The existing Comonad instance can be moved from comonad-transformers to comonad; it would not be orphaned. The patch against the darcs repository is attached. An alternative naming for the module (and the type) would be Data.Functor.Sum. This name would be shorter and less frightening to newcomers, but it clashes with its namesake type from Data.Monoid. On the other hand, so does Data.Functor.Product. I'm ambivalent on the naming, but I'm throwing this out because I don't expect it to become a bikeshed issue. If you have any name preference, state it together with your vote; if the proposal succeeds we can use whichever name is preferred.

+1 for it, sans bikeshedding, as Coproduct.
-Edward
On Mon, Dec 10, 2012 at 11:54 PM, Mario Blazevic
At the instigation of Edward Kmett, I hereby propose to merge Data.Functor.Coproduct module from comonad-transformers into transformers.
The module defines the Coproduct data type, together with several class instances. All non-base instances would have to be left out, leaving the following instances to be merged in:
instance (Functor f, Functor g) => Functor (Coproduct f g) instance (Foldable f, Foldable g) => Foldable (Coproduct f g) instance (Traversable f, Traversable g) => Traversable (Coproduct f g)
Unfortunately, the Applicative and Monad instances cannot be defined on this type, though their duals can. In that sense, the existing comonad-transformers package is a more fitting home for the type. However, there are good reasons for the move:
- The dual type of Coproduct, namely Data.Functor.Product, is already defined by transformers. It would make sense to keep the duals together. - Data.Functor.Compose and Data.Functor.Constant which also defined by transformers are not monads either, so there is precedent for having non-monads there. - Most obviously, transformers is a haskell-platform package while comonad-transformers seems unlikely to become one any time soon (as much as I'd like that). - The existing Comonad instance can be moved from comonad-transformers to comonad; it would not be orphaned.
The patch against the darcs repository is attached.
An alternative naming for the module (and the type) would be Data.Functor.Sum. This name would be shorter and less frightening to newcomers, but it clashes with its namesake type from Data.Monoid. On the other hand, so does Data.Functor.Product. I'm ambivalent on the naming, but I'm throwing this out because I don't expect it to become a bikeshed issue. If you have any name preference, state it together with your vote; if the proposal succeeds we can use whichever name is preferred.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

So far we have a consensus on the proposal (yay!), but no firm agreement on the naming. Of the two alternatives I've suggested, Sum appears to have edged ahead of Coproduct. Let me know if I misrepresented anybody's position: Edward Coproduct (LeftF | RightF) Erik Sum Wren Coproduct (InL | InR) Gábor ? (LeftF | RightF) Andreas Either1 (Left1 | Right1) Sean Sum (InL | InR) Henning Sum no prefixes Unfortunately, there seems to be a preference for a new data type instead of a newtype wrapping for Either, which gives us three bike sheds to paint instead of one. I'm going to list some of the suggested alternatives here:
data Coproduct f g a = LeftF (f a) | RightF (g a) data Sum f g a = InL (f a) | InR (g a) data Either1 f g a = Left1 (f a) | Right1 (g a) data Either f g a = Left (f a) | Right (g a) -- use qualification
I like the Either1 naming, but only if it's a start of a new trend. In other words, that's a good choice only if it gains a consensus so that other higher-order types switch to the scheme in the future. If that doesn't happen, my second choice would be Sum (InL, InR).

On Fri, 14 Dec 2012, Mario Blažević wrote:
So far we have a consensus on the proposal (yay!), but no firm agreement on the naming. Of the two alternatives I've suggested, Sum appears to have edged ahead of Coproduct. Let me know if I misrepresented anybody's position:
Edward Coproduct (LeftF | RightF) Erik Sum Wren Coproduct (InL | InR) Gábor ? (LeftF | RightF) Andreas Either1 (Left1 | Right1) Sean Sum (InL | InR) Henning Sum no prefixes
Unfortunately, there seems to be a preference for a new data type instead of a newtype wrapping for Either, which gives us three bike sheds to paint instead of one. I'm going to list some of the suggested alternatives here:
data Coproduct f g a = LeftF (f a) | RightF (g a) data Sum f g a = InL (f a) | InR (g a) data Either1 f g a = Left1 (f a) | Right1 (g a) data Either f g a = Left (f a) | Right (g a) -- use qualification
Oh, I missed the optio "newtype wrapper around Either". A newtype wrapper would simplify the naming discussion I think and it would simplify remembering names and simplifies the qualification issue. I think I prefer that.

On Fri, Dec 14, 2012 at 9:50 PM, Bardur Arantsson
On 12/14/2012 08:37 PM, Mario Blažević wrote:
So far we have a consensus on the proposal (yay!), but no firm agreement on the naming.
Throw some dice?
Given that no one has tied their approval to a particular name, what about giving Ross Paterson, maintainer of transformers, the final vote? If I'm not missing one, the possibilities mentioned have been: newtype Coproduct f g a = Coproduct { getCoproduct :: Either (f a) (g a) } data Sum f g a = SumLeft (f a) | SumRight (g a) data Coproduct f g a = InL (f a) | InR (g a) data Sum f g a = InL (f a) | InR (g a) data Coproduct f g a = LeftF (f a) | RightF (g a) data EitherF f g a = LeftF (f a) | RightF (g a) data Either1 f g a = Left1 (f a) | Right1 (g a) data Either f g a = Left (f a) | Right (g a) -- import qualified -- Your ship was destroyed in a monadic eruption.

On Sat, 15 Dec 2012, Gábor Lehel wrote:
On Fri, Dec 14, 2012 at 9:50 PM, Bardur Arantsson
wrote: On 12/14/2012 08:37 PM, Mario Blažević wrote:
So far we have a consensus on the proposal (yay!), but no firm agreement on the naming.
Throw some dice?
Given that no one has tied their approval to a particular name, what about giving Ross Paterson, maintainer of transformers, the final vote?
If I'm not missing one, the possibilities mentioned have been:
newtype Coproduct f g a = Coproduct { getCoproduct :: Either (f a) (g a) } data Sum f g a = SumLeft (f a) | SumRight (g a) data Coproduct f g a = InL (f a) | InR (g a) data Sum f g a = InL (f a) | InR (g a) data Coproduct f g a = LeftF (f a) | RightF (g a) data EitherF f g a = LeftF (f a) | RightF (g a) data Either1 f g a = Left1 (f a) | Right1 (g a)
data Either f g a = Left (f a) | Right (g a) -- import qualified
Since I proposed that and became aware of the newtype solution in the meantime, I change my mind to:
data Sum f g a = Sum { getSum :: Either (f a) (g a) }

On Sat, Dec 15, 2012 at 09:24:48PM +0000, Henning Thielemann wrote:
Since I proposed that and became aware of the newtype solution in the meantime, I change my mind to:
data Sum f g a = Sum { getSum :: Either (f a) (g a) }
OK, let's do that. It matches the treatment of Product. (So now they'll both clash with Data.Monoid.)

On Sun, Dec 16, 2012 at 1:57 AM, Ross Paterson wrote:
On Sat, Dec 15, 2012 at 09:24:48PM +0000, Henning Thielemann wrote:
Since I proposed that and became aware of the newtype solution in the meantime, I change my mind to:
data Sum f g a = Sum { getSum :: Either (f a) (g a) }
OK, let's do that. It matches the treatment of Product. (So now they'll both clash with Data.Monoid.)
Great! I'm guessing the smart constructors and eliminator should still be included? We had: left, right, coproduct. Do we now have: left, right, sum? Regards, Sean

On Sun, Dec 16, 2012 at 12:57 AM, Ross Paterson
On Sat, Dec 15, 2012 at 09:24:48PM +0000, Henning Thielemann wrote:
Since I proposed that and became aware of the newtype solution in the meantime, I change my mind to:
data Sum f g a = Sum { getSum :: Either (f a) (g a) }
OK, let's do that. It matches the treatment of Product.
Do you mean in name or in implementation? Product is not a newtype, so the most consistent thing to do would surely be to make Sum not a newtype. (This is not a vote, merely a comment).

If you're going to update transformers, could you perhaps export fstP and sndP from Product? I keep having to redefine them. And perhaps also a function dual to coproduct of type (a -> f b) -> (a -> g b) -> a -> Product f g b. Here's an example where they are very useful: {-# LANGUAGE MultiParamTypeClasses, UndecidableInstances #-} import Data.Functor.Product import Data.Functor.Coproduct import Data.Functor.Adjunction fstP :: Product f g a -> f a fstP (Pair x _) = x sndP :: Product f g a -> g a sndP (Pair _ x) = x productP :: (a -> f b) -> (a -> g b) -> a -> Product f g b productP f g a = Pair (f a) (g a) instance (Adjunction f g, Adjunction f' g') => Adjunction (Coproduct f f') (Product g g') where unit = productP (leftAdjunct left) (leftAdjunct right) counit = coproduct (rightAdjunct fstP) (rightAdjunct sndP) leftAdjunct f = productP (leftAdjunct (f . left)) (leftAdjunct (f . right)) rightAdjunct f = coproduct (rightAdjunct (fstP . f)) (rightAdjunct (sndP . f)) greetings, Sjoerd

Standing up against the dictator... I like neither 'Product' nor 'Sum'. For one, they are ambiguous already in type theory. They mean something different in the context of simple types and the context of dependent types: Sum Product simple types set of tagged elements set of pairs dependent types set of pairs set of functions Further they have this number-connotation. Sum and Product are mathematician's terms inspired by the cardinality of the sets they construct (in the simply typed setting), or the likeness to summation and product terms (in the dependently typed setting). IMHO, programming is much more based on logics and information theory than on mathematics and numbers. The logical content of 'Sum' is making a decision (left or right) and the one of 'Product' is adjoining two things, putting them next to each other. Disjunction and conjunction would be the logically correct terms, but we can say it simpler. I think the current Haskell approach to speak of 'Either' and pairing is the good one, free of mathematical burden, and it can be extended to higher-order kinds: Either :: * -> * -> * Either1 :: (* -> *) -> (* -> *) -> (* -> *) Either2 :: (* -> * -> *) -> (* -> * -> *) -> (* -> * -> *) (,) :: * -> * -> * Pair1 :: (* -> *) -> (* -> *) -> (* -> *) Pair2 :: (* -> * -> *) -> (* -> * -> *) -> (* -> * -> *) Cheers, Andreas On 16.12.12 1:57 AM, Ross Paterson wrote:
On Sat, Dec 15, 2012 at 09:24:48PM +0000, Henning Thielemann wrote:
Since I proposed that and became aware of the newtype solution in the meantime, I change my mind to:
data Sum f g a = Sum { getSum :: Either (f a) (g a) }
OK, let's do that. It matches the treatment of Product. (So now they'll both clash with Data.Monoid.)
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

On 12/16/12 9:36 AM, Andreas Abel wrote:
Standing up against the dictator...
I like neither 'Product' nor 'Sum'. For one, they are ambiguous already in type theory.
Yeah, this is one of the reasons I prefer Coproduct (or EitherF, or Either1). FWIW, I wrote a short blog post about this terminological confusion some time back: http://winterkoninkje.dreamwidth.org/72346.html -- Live well, ~wren

On Mon, Dec 17, 2012 at 2:39 AM, wren ng thornton
On 12/16/12 9:36 AM, Andreas Abel wrote:
Standing up against the dictator...
I like neither 'Product' nor 'Sum'. For one, they are ambiguous already in type theory.
Yeah, this is one of the reasons I prefer Coproduct (or EitherF, or Either1). FWIW, I wrote a short blog post about this terminological confusion some time back:
Hmm. As I always understood it, the confusion was because a dependent sum (i.e. a dependent pair type) is really very similar to a disjoint union of the A-indexed family of types given by "for each a in A, { : b in P(a)}". Categorically, this could also be considered as an A-indexed coproduct, so I'm not sure you resolve the ambiguity like that, except by avoiding convention. (It was one of the great epiphanies in my understanding of Type Theory that a dependent sum involving a constant dependent type was a product, by analogy with how the sum over n = 1 to N of a constant function M is the product NM).

Sure. I'd rather have a solution than no solution. I hereby delegate my
vote to Ross.
On Sat, Dec 15, 2012 at 1:29 PM, Gábor Lehel
On Fri, Dec 14, 2012 at 9:50 PM, Bardur Arantsson
wrote: On 12/14/2012 08:37 PM, Mario Blažević wrote:
So far we have a consensus on the proposal (yay!), but no firm agreement on the naming.
Throw some dice?
Given that no one has tied their approval to a particular name, what about giving Ross Paterson, maintainer of transformers, the final vote?
If I'm not missing one, the possibilities mentioned have been:
newtype Coproduct f g a = Coproduct { getCoproduct :: Either (f a) (g a) } data Sum f g a = SumLeft (f a) | SumRight (g a) data Coproduct f g a = InL (f a) | InR (g a) data Sum f g a = InL (f a) | InR (g a) data Coproduct f g a = LeftF (f a) | RightF (g a) data EitherF f g a = LeftF (f a) | RightF (g a) data Either1 f g a = Left1 (f a) | Right1 (g a) data Either f g a = Left (f a) | Right (g a) -- import qualified
-- Your ship was destroyed in a monadic eruption.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 12-12-15 05:48 PM, Edward Kmett wrote:
Sure. I'd rather have a solution than no solution. I hereby delegate my vote to Ross.
+1. Since it appears we're voting on whether to appoint a dictator.
On Sat, Dec 15, 2012 at 1:29 PM, Gábor Lehel
mailto:illissius@gmail.com> wrote: On Fri, Dec 14, 2012 at 9:50 PM, Bardur Arantsson
mailto:spam@scientician.net> wrote: > On 12/14/2012 08:37 PM, Mario Blažević wrote: >> So far we have a consensus on the proposal (yay!), but no firm >> agreement on the naming. > > Throw some dice? > Given that no one has tied their approval to a particular name, what about giving Ross Paterson, maintainer of transformers, the final vote?
If I'm not missing one, the possibilities mentioned have been:
newtype Coproduct f g a = Coproduct { getCoproduct :: Either (f a) (g a) } data Sum f g a = SumLeft (f a) | SumRight (g a) data Coproduct f g a = InL (f a) | InR (g a) data Sum f g a = InL (f a) | InR (g a) data Coproduct f g a = LeftF (f a) | RightF (g a) data EitherF f g a = LeftF (f a) | RightF (g a) data Either1 f g a = Left1 (f a) | Right1 (g a) data Either f g a = Left (f a) | Right (g a) -- import qualified
-- Your ship was destroyed in a monadic eruption.
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 12/14/12 2:37 PM, Mario Blažević wrote:
So far we have a consensus on the proposal (yay!), but no firm agreement on the naming. Of the two alternatives I've suggested, Sum appears to have edged ahead of Coproduct. Let me know if I misrepresented anybody's position:
Edward Coproduct (LeftF | RightF) Erik Sum Wren Coproduct (InL | InR)
I'd rather have LeftF|RightF. I only mentioned InL|InR in case people wanted to bikeshed some more.
Gábor ? (LeftF | RightF) Andreas Either1 (Left1 | Right1) Sean Sum (InL | InR) Henning Sum no prefixes
-- Live well, ~wren

I'd be willing to go with Sum(InL, InR) to move us toward consensus, then Sum has a majority and InL|InR are the most common constructor choices. They are fairly traditional as well.
Sent from my iPad
On Dec 14, 2012, at 2:37 PM, Mario Blažević
So far we have a consensus on the proposal (yay!), but no firm agreement on the naming. Of the two alternatives I've suggested, Sum appears to have edged ahead of Coproduct. Let me know if I misrepresented anybody's position:
Edward Coproduct (LeftF | RightF) Erik Sum Wren Coproduct (InL | InR) Gábor ? (LeftF | RightF) Andreas Either1 (Left1 | Right1) Sean Sum (InL | InR) Henning Sum no prefixes
Unfortunately, there seems to be a preference for a new data type instead of a newtype wrapping for Either, which gives us three bike sheds to paint instead of one. I'm going to list some of the suggested alternatives here:
data Coproduct f g a = LeftF (f a) | RightF (g a) data Sum f g a = InL (f a) | InR (g a) data Either1 f g a = Left1 (f a) | Right1 (g a) data Either f g a = Left (f a) | Right (g a) -- use qualification
I like the Either1 naming, but only if it's a start of a new trend. In other words, that's a good choice only if it gains a consensus so that other higher-order types switch to the scheme in the future. If that doesn't happen, my second choice would be Sum (InL, InR).
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Are the 'left' and 'right' functions also going to be inlcuded in the
move? Because if we're worried about clashes with base, those names
are also defined in Control.Arrow.
In general I'd prefer the Sum name, but I'd +1 either name.
Erik
On Tue, Dec 11, 2012 at 5:54 AM, Mario Blazevic
At the instigation of Edward Kmett, I hereby propose to merge Data.Functor.Coproduct module from comonad-transformers into transformers.
The module defines the Coproduct data type, together with several class instances. All non-base instances would have to be left out, leaving the following instances to be merged in:
instance (Functor f, Functor g) => Functor (Coproduct f g) instance (Foldable f, Foldable g) => Foldable (Coproduct f g) instance (Traversable f, Traversable g) => Traversable (Coproduct f g)
Unfortunately, the Applicative and Monad instances cannot be defined on this type, though their duals can. In that sense, the existing comonad-transformers package is a more fitting home for the type. However, there are good reasons for the move:
- The dual type of Coproduct, namely Data.Functor.Product, is already defined by transformers. It would make sense to keep the duals together. - Data.Functor.Compose and Data.Functor.Constant which also defined by transformers are not monads either, so there is precedent for having non-monads there. - Most obviously, transformers is a haskell-platform package while comonad-transformers seems unlikely to become one any time soon (as much as I'd like that). - The existing Comonad instance can be moved from comonad-transformers to comonad; it would not be orphaned.
The patch against the darcs repository is attached.
An alternative naming for the module (and the type) would be Data.Functor.Sum. This name would be shorter and less frightening to newcomers, but it clashes with its namesake type from Data.Monoid. On the other hand, so does Data.Functor.Product. I'm ambivalent on the naming, but I'm throwing this out because I don't expect it to become a bikeshed issue. If you have any name preference, state it together with your vote; if the proposal succeeds we can use whichever name is preferred.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I'm not wedded to its current behavior of wrapping an Either. It was kind
of nice that converting to and from Either was a no-op on GHC, but that
could change.
I agree that I wouldn't want to add functions named 'left' and 'right', so
moving to a data type rather than a newtype seems reasonable.
Perhaps
data Coproduct f g a = LeftF (f a) | RightF (g a)
would be a nice color for the bikeshed?
-Edward
On Tue, Dec 11, 2012 at 4:27 AM, Erik Hesselink
Are the 'left' and 'right' functions also going to be inlcuded in the move? Because if we're worried about clashes with base, those names are also defined in Control.Arrow.
In general I'd prefer the Sum name, but I'd +1 either name.
Erik
On Tue, Dec 11, 2012 at 5:54 AM, Mario Blazevic
wrote: At the instigation of Edward Kmett, I hereby propose to merge Data.Functor.Coproduct module from comonad-transformers into transformers.
The module defines the Coproduct data type, together with several class instances. All non-base instances would have to be left out, leaving the following instances to be merged in:
instance (Functor f, Functor g) => Functor (Coproduct f g) instance (Foldable f, Foldable g) => Foldable (Coproduct f g) instance (Traversable f, Traversable g) => Traversable (Coproduct f g)
Unfortunately, the Applicative and Monad instances cannot be defined on this type, though their duals can. In that sense, the existing comonad-transformers package is a more fitting home for the type. However, there are good reasons for the move:
- The dual type of Coproduct, namely Data.Functor.Product, is already defined by transformers. It would make sense to keep the duals together. - Data.Functor.Compose and Data.Functor.Constant which also defined by transformers are not monads either, so there is precedent for having non-monads there. - Most obviously, transformers is a haskell-platform package while comonad-transformers seems unlikely to become one any time soon (as much as I'd like that). - The existing Comonad instance can be moved from comonad-transformers to comonad; it would not be orphaned.
The patch against the darcs repository is attached.
An alternative naming for the module (and the type) would be Data.Functor.Sum. This name would be shorter and less frightening to newcomers, but it clashes with its namesake type from Data.Monoid. On the other hand, so does Data.Functor.Product. I'm ambivalent on the naming, but I'm throwing this out because I don't expect it to become a bikeshed issue. If you have any name preference, state it together with your vote; if the proposal succeeds we can use whichever name is preferred.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Tue, Dec 11, 2012 at 5:29 AM, Edward Kmett
I'm not wedded to its current behavior of wrapping an Either. It was kind of nice that converting to and from Either was a no-op on GHC, but that could change.
I agree that I wouldn't want to add functions named 'left' and 'right', so moving to a data type rather than a newtype seems reasonable.
Perhaps
data Coproduct f g a = LeftF (f a) | RightF (g a)
would be a nice color for the bikeshed?
Nah, those constructor names are dumb. I prefer Shaun's
data Sum f g a = SumLeft (f a) | SumRight (g a)
If we're going with Sum, of course.

On 12/11/12 7:27 AM, Mario Blazevic wrote:
On Tue, Dec 11, 2012 at 5:29 AM, Edward Kmett
wrote: I'm not wedded to its current behavior of wrapping an Either. It was kind of nice that converting to and from Either was a no-op on GHC, but that could change.
I agree that I wouldn't want to add functions named 'left' and 'right', so moving to a data type rather than a newtype seems reasonable.
Perhaps
data Coproduct f g a = LeftF (f a) | RightF (g a)
would be a nice color for the bikeshed?
+1. I hesitate to suggest another alternative, but if folks are displeased with those names, there's always the tried and true InL/InR or InjL/InjR. But given the precedent of Either, I think LeftF/RightF have a nice ring to them.
Nah, those constructor names are dumb. I prefer Shaun's
data Sum f g a = SumLeft (f a) | SumRight (g a)
-1. What happened to the vaunted brevity? I type out the names of data constructors far more often than the names of type constructors. And those data constructor names are obnoxiously long for something as basic as a functor coproduct. -- Live well, ~wren

On Tue, Dec 11, 2012 at 1:42 PM, wren ng thornton
On 12/11/12 7:27 AM, Mario Blazevic wrote:
On Tue, Dec 11, 2012 at 5:29 AM, Edward Kmett
wrote: I'm not wedded to its current behavior of wrapping an Either. It was kind of nice that converting to and from Either was a no-op on GHC, but that could change.
I agree that I wouldn't want to add functions named 'left' and 'right', so moving to a data type rather than a newtype seems reasonable.
Perhaps
data Coproduct f g a = LeftF (f a) | RightF (g a)
would be a nice color for the bikeshed?
+1.
I hesitate to suggest another alternative, but if folks are displeased with those names, there's always the tried and true InL/InR or InjL/InjR. But given the precedent of Either, I think LeftF/RightF have a nice ring to them.
Another possibility is data EitherF f g a = LeftF (f a) | RightF (g a) But +1 to the proposal no matter the names, +1 to LeftF/RightF, +0 to any particular type name (including this one). -- Your ship was destroyed in a monadic eruption.

On 11.12.12 1:48 PM, Gábor Lehel wrote:
On Tue, Dec 11, 2012 at 1:42 PM, wren ng thornton
wrote: On 12/11/12 7:27 AM, Mario Blazevic wrote:
On Tue, Dec 11, 2012 at 5:29 AM, Edward Kmett
wrote: I'm not wedded to its current behavior of wrapping an Either. It was kind of nice that converting to and from Either was a no-op on GHC, but that could change.
I agree that I wouldn't want to add functions named 'left' and 'right', so moving to a data type rather than a newtype seems reasonable.
Perhaps
data Coproduct f g a = LeftF (f a) | RightF (g a)
would be a nice color for the bikeshed?
+1.
I hesitate to suggest another alternative, but if folks are displeased with those names, there's always the tried and true InL/InR or InjL/InjR. But given the precedent of Either, I think LeftF/RightF have a nice ring to them.
Another possibility is
data EitherF f g a = LeftF (f a) | RightF (g a)
But +1 to the proposal no matter the names, +1 to LeftF/RightF, +0 to any particular type name (including this one).
That sounds better to me than Coproduct or Sum which smell too much of theory. An alternative would be data Either1 f g a = Left1 (f a) | Right1 (g a) to indicate the arity of the functor. (The current Either is Either0.) One can go on this way and have bifunctors data Either2 f g a b = Left2 (f a b) | Right2 (g a b) and so on... -- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

On Tue, Dec 11, 2012 at 1:42 PM, wren ng thornton wrote:
On 12/11/12 7:27 AM, Mario Blazevic wrote:
On Tue, Dec 11, 2012 at 5:29 AM, Edward Kmett wrote:
I'm not wedded to its current behavior of wrapping an Either. It was kind of nice that converting to and from Either was a no-op on GHC, but that could change.
I agree that I wouldn't want to add functions named 'left' and 'right', so moving to a data type rather than a newtype seems reasonable.
Perhaps
data Coproduct f g a = LeftF (f a) | RightF (g a)
would be a nice color for the bikeshed?
These also work for Sum. ;)
I hesitate to suggest another alternative, but if folks are displeased
with those names, there's always the tried and true InL/InR or InjL/InjR. But given the precedent of Either, I think LeftF/RightF have a nice ring to them.
At first, I couldn't think of a standard library precedent for using L and R as left and right, but then I remembered ViewL/ViewR in Data.Sequencehttp://hackage.haskell.org/packages/archive/containers/latest/doc/html/Data-... . Of all the above, InL/InR are my favorites, since they pun "in" for elimination and "inject" for introduction (or you could think "put in"). Nah, those constructor names are dumb. I prefer Shaun's
data Sum f g a = SumLeft (f a) | SumRight (g a)
-1. What happened to the vaunted brevity? I type out the names of data constructors far more often than the names of type constructors. And those data constructor names are obnoxiously long for something as basic as a functor coproduct.
The verbosity of the Data.Functor.* modules in transformers is a general complaint of mine. But it's there already, so I was thinking we should match the style. Otherwise, I'd be happy with just L/R. ;) Regards, Sean

On Tue, 11 Dec 2012, Mario Blazevic wrote:
On Tue, Dec 11, 2012 at 5:29 AM, Edward Kmett
wrote: I'm not wedded to its current behavior of wrapping an Either. It was kind of nice that converting to and from Either was a no-op on GHC, but that could change.
I agree that I wouldn't want to add functions named 'left' and 'right', so moving to a data type rather than a newtype seems reasonable.
Perhaps
data Coproduct f g a = LeftF (f a) | RightF (g a)
would be a nice color for the bikeshed?
Nah, those constructor names are dumb. I prefer Shaun's
data Sum f g a = SumLeft (f a) | SumRight (g a)
If we're going with Sum, of course.
Please stop emulating qualification with custom prefixes or suffixes. We have real qualification! (On the other hand you can throw in that 'transformers' is already designed for unqualified import.) I find the analogies to algebraic sums and products appealing, thus I would prefer Sum to Coproduct. But I would also be very happy with Either(Left, Right) plus qualification.

On Tue, Dec 11, 2012 at 5:54 AM, Mario Blazevic wrote:
At the instigation of Edward Kmett, I hereby propose to merge Data.Functor.Coproduct module from comonad-transformers into transformers.
I've been wishing this datatype was there. An alternative naming for the module (and the type) would be
Data.Functor.Sum.
I prefer Sum. I have a much stronger preference for a new datatype rather than a wrapper around Either. The wrapping/unwrapping doesn't seem to add anything but more work when you use it (in pattern matching). Currently, you have:
newtype Coproduct f g a = Coproduct { getCoproduct :: Either (f a) (g a) }
Why not this?
data Sum f g a = SumLeft (f a) | SumRight (g a)
(I'm not particular about the constructor names, though these do seem to fit the explicit naming style of the transformer functors.) Then, we don't need the functions left and right, and coproduct becomes:
unSum :: (f a -> b) -> (g a -> b) -> Sum f g a -> b unSum f _ (SumLeft x) = f x unSum _ g (SumRight x) = f x
(Also not particular about the name unSum. Could be runSum or getSum, I suppose.) Regards, Sean

On 12/10/12 11:54 PM, Mario Blazevic wrote:
At the instigation of Edward Kmett, I hereby propose to merge Data.Functor.Coproduct module from comonad-transformers into transformers.
The module defines the Coproduct data type, together with several class instances. All non-base instances would have to be left out, leaving the following instances to be merged in:
instance (Functor f, Functor g) => Functor (Coproduct f g) instance (Foldable f, Foldable g) => Foldable (Coproduct f g) instance (Traversable f, Traversable g) => Traversable (Coproduct f g)
+1.
An alternative naming for the module (and the type) would be Data.Functor.Sum. This name would be shorter and less frightening to newcomers, but it clashes with its namesake type from Data.Monoid. On the other hand, so does Data.Functor.Product. I'm ambivalent on the naming, but I'm throwing this out because I don't expect it to become a bikeshed issue. If you have any name preference, state it together with your vote; if the proposal succeeds we can use whichever name is preferred.
+1 for Coproduct. -1 for Sum. -- Live well, ~wren
participants (14)
-
Andreas Abel
-
Bardur Arantsson
-
Ben Millwood
-
Edward Kmett
-
Erik Hesselink
-
Gábor Lehel
-
Henning Thielemann
-
Mario Blazevic
-
Mario Blažević
-
Mario Blažević
-
Ross Paterson
-
Sean Leather
-
Sjoerd Visscher
-
wren ng thornton