Proposal #3339: Add (+>) as a synonym for mappend

Ticket: http://hackage.haskell.org/trac/ghc/ticket/3339
From the ticket:
This proposal was, I think, originally suggested by Jules Bean. The idea is to add two functions to the Data.Monoid module, (+>) and (<+), corresponding to different uses of mappend. These should not be methods of the Monoidtypeclass, but top-level functions. I hope (but slightly doubt) that the visual nature of the two operators might help to counter the thought that monoids are just for gluing things together. (+>) :: (Monoid a) => a -> a -> a a +> b = a `mappend` b (<+) :: (Monoid a) => a -> a -> a a <+ b = b `mappend` a infixl 4 +> infixl 4 <+ Proposed deadline: two weeks. If this looks reasonable, I'll attach darcs patches.

Bikeshedding: Would it be better to put the definition for +> (or better yet
<>) in the dictionary for Monoid with a circular definition for mappend?
That way new code defining Monoid instances can avoid ever having to even
mention mappend. I'm ok with it either way. I admit adding it to the
dictionary might add dictionary passing overhead and risk inconsistent
definitions of <> and mappend.
-Edward Kmett
On Tue, Jun 30, 2009 at 5:37 PM, Bryan O'Sullivan
Ticket: http://hackage.haskell.org/trac/ghc/ticket/3339
From the ticket:
This proposal was, I think, originally suggested by Jules Bean. The idea is to add two functions to the Data.Monoid module, (+>) and (<+), corresponding to different uses of mappend. These should not be methods of the Monoid typeclass, but top-level functions.
I hope (but slightly doubt) that the visual nature of the two operators might help to counter the thought that monoids are just for gluing things together.
(+>) :: (Monoid a) => a -> a -> a a +> b = a `mappend` b
(<+) :: (Monoid a) => a -> a -> a a <+ b = b `mappend` a
infixl 4 +> infixl 4 <+
Proposed deadline: two weeks.
If this looks reasonable, I'll attach darcs patches.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Am Mittwoch, 1. Juli 2009 16:59 schrieb Edward Kmett:
Bikeshedding: Would it be better to put the definition for +> (or better yet <>) in the dictionary for Monoid with a circular definition for mappend? That way new code defining Monoid instances can avoid ever having to even mention mappend.
+1 Best wishes, Wolfgang

On Tue, Jun 30, 2009 at 5:37 PM, Bryan O'Sullivan
Ticket: http://hackage.haskell.org/trac/ghc/ticket/3339
From the ticket:
This proposal was, I think, originally suggested by Jules Bean. The idea is to add two functions to the Data.Monoid module, (+>) and (<+), corresponding to different uses of mappend. These should not be methods of the Monoid typeclass, but top-level functions.
I hope (but slightly doubt) that the visual nature of the two operators might help to counter the thought that monoids are just for gluing things together.
(+>) :: (Monoid a) => a -> a -> a a +> b = a `mappend` b
(<+) :: (Monoid a) => a -> a -> a a <+ b = b `mappend` a
infixl 4 +> infixl 4 <+
Proposed deadline: two weeks.
If this looks reasonable, I'll attach darcs patches.
I (and apparently a lot of other people who commented on that ticket) would prefer that (++) be generalized instead of introducing a new operator. Alex

The main concern with generalizing (++) is that it was once generalized -- completely differently! -- for mplus in MonadPlus. So whether Monoid's mappend is the natural generalization of (++) or MonadPlus's mplus is, is not entirely clear. Neither one can completely subsume all of the use-cases of the other. A secondary concern is that neither MonadPlus nor Monoid are in the Prelude, so its generalized form would have to be exported from Data.Monoid with a different type signature breaking any pre-existing code that brought in Data.Monoid unqualified and happened to use lists. I'm less sold by the second concern than the first one, but both make me hesitate. Bryan's/Jules's existing proposal of a new operator avoids both of these snarls. -Edward Kmett On Fri, Jul 17, 2009 at 10:53 AM, Alexander Dunlap < alexander.dunlap@gmail.com> wrote:
On Tue, Jun 30, 2009 at 5:37 PM, Bryan O'Sullivan
wrote: Ticket: http://hackage.haskell.org/trac/ghc/ticket/3339
From the ticket:
This proposal was, I think, originally suggested by Jules Bean. The idea is to add two functions to the Data.Monoid module, (+>) and (<+), corresponding to different uses of mappend. These should not be methods of the Monoid typeclass, but top-level functions.
I hope (but slightly doubt) that the visual nature of the two operators might help to counter the thought that monoids are just for gluing things together.
(+>) :: (Monoid a) => a -> a -> a a +> b = a `mappend` b
(<+) :: (Monoid a) => a -> a -> a a <+ b = b `mappend` a
infixl 4 +> infixl 4 <+
Proposed deadline: two weeks.
If this looks reasonable, I'll attach darcs patches.
I (and apparently a lot of other people who commented on that ticket) would prefer that (++) be generalized instead of introducing a new operator.
Alex _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Am Freitag, 17. Juli 2009 21:57 schrieb Edward Kmett:
The main concern with generalizing (++) is that it was once generalized -- completely differently! -- for mplus in MonadPlus. So whether Monoid's mappend is the natural generalization of (++) or MonadPlus's mplus is, is not entirely clear. Neither one can completely subsume all of the use-cases of the other.
I hope that in the long run, we will be able to drop Alternative and MonadPlus. This will be possible once we allow universal quantification in contexts. Instead of writing (MonadPlus m), we can write (Monad m, forall a. Monoid (m a)) then. This makes it rather clear that Monoid (mappend) would be the better generalization of (++). MonadPlus (mplus) is a bit of a hack. Best wishes, Wolfgang

On 18 Jul 2009, at 10:21, Wolfgang Jeltsch wrote:
Am Freitag, 17. Juli 2009 21:57 schrieb Edward Kmett:
The main concern with generalizing (++) is that it was once generalized -- completely differently! -- for mplus in MonadPlus. So whether Monoid's mappend is the natural generalization of (++) or MonadPlus's mplus is, is not entirely clear. Neither one can completely subsume all of the use-cases of the other.
I hope that in the long run, we will be able to drop Alternative and MonadPlus. This will be possible once we allow universal quantification in contexts. Instead of writing (MonadPlus m), we can write (Monad m, forall a. Monoid (m a)) then. This makes it rather clear that Monoid (mappend) would be the better generalization of (++). MonadPlus (mplus) is a bit of a hack.
Until that joyous day, I'd like to hope we might consider ensuring that MonadPlus m, Alternative m, and Monoid (m a) functionalities do at least coincide. I'm thinking in particular of Maybe, which behaves splendidly as an implementation of an exception monad, until you start using foldMap as a control operator. Cheers Conor

On Sat, Jul 18, 2009 at 6:14 AM, Conor McBride
Until that joyous day, I'd like to hope we might consider ensuring that MonadPlus m, Alternative m, and Monoid (m a) functionalities do at least coincide.
I'm thinking in particular of Maybe, which behaves splendidly as an implementation of an exception monad, until you start using foldMap as a control operator.
Yeah, the Monoid instance for Maybe is somewhat unfortunate. I can see where they were going as Maybe does provide the natural extension of a semigroup into a monoid by adding a unit element, but it doesn't have a Semigroup class to build on, and so has to require Monoid and in the end you get a definition that conflicts with the MonadPlus/Alternative instances for Maybe, and only really helps if you have broken Monoid instances around that are secretly just Semigroups. -Edward Kmett

Hi Edward On 18 Jul 2009, at 14:23, Edward Kmett wrote:
Yeah, the Monoid instance for Maybe is somewhat unfortunate.
I can see where they were going as Maybe does provide the natural extension of a semigroup into a monoid by adding a unit element, but it doesn't have a Semigroup class to build on, and so has to require Monoid and in the end you get a definition that conflicts with the MonadPlus/Alternative instances for Maybe, and only really helps if you have broken Monoid instances around that are secretly just Semigroups.
Exactly. Types should mean more than mere data representations. The current Monoid instance is inconsistent with the broad interpretation of Maybe as a monad for exceptional computations. An isomorphic data representation can and should be used to attach a unit element to a semigroup, Data structures are data with structure. All the best Conor

On Tue, Jun 30, 2009 at 02:37:51PM -0700, Bryan O'Sullivan wrote:
Ticket: http://hackage.haskell.org/trac/ghc/ticket/3339
From the ticket:
This proposal was, I think, originally suggested by Jules Bean. The idea is to add two functions to the Data.Monoid module, (+>) and (<+), corresponding to different uses of mappend. These should not be methods of the Monoid typeclass, but top-level functions.
I hope (but slightly doubt) that the visual nature of the two operators might help to counter the thought that monoids are just for gluing things together.
This proposal seems to have got stuck. Everyone wants an infix operator, but we can't agree what it should be. I prefer using a new operator instead of generalizing ++ (or +, *, && or ||), because I think that a monoid operation is so abstract that it needs a name that doesn't suggest one of the special cases. (I like <>)

On Thu, Sep 17, 2009 at 9:37 AM, Ross Paterson
This proposal seems to have got stuck. Everyone wants an infix operator, but we can't agree what it should be.
I prefer using a new operator instead of generalizing ++ (or +, *, && or ||), because I think that a monoid operation is so abstract that it needs a name that doesn't suggest one of the special cases. (I like <>)
I agree. <> really seems to fit well, even if it *does* reinforce the idea that Monoid is for gluing things together -- which, you know, it really is rather good for.

I also really like <>.
On Thu, Sep 17, 2009 at 4:52 PM, Samuel Bronson
On Thu, Sep 17, 2009 at 9:37 AM, Ross Paterson
wrote: This proposal seems to have got stuck. Everyone wants an infix operator, but we can't agree what it should be.
I prefer using a new operator instead of generalizing ++ (or +, *, && or ||), because I think that a monoid operation is so abstract that it needs a name that doesn't suggest one of the special cases. (I like <>)
I agree. <> really seems to fit well, even if it *does* reinforce the idea that Monoid is for gluing things together -- which, you know, it really is rather good for. _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Excerpts from Edward Kmett's message of Fri Sep 18 00:11:12 +0200 2009:
I also really like <>.
I'm also in favor of <>
On Thu, Sep 17, 2009 at 4:52 PM, Samuel Bronson
wrote: On Thu, Sep 17, 2009 at 9:37 AM, Ross Paterson
wrote: This proposal seems to have got stuck. Everyone wants an infix operator, but we can't agree what it should be.
I prefer using a new operator instead of generalizing ++ (or +, *, && or ||), because I think that a monoid operation is so abstract that it needs a name that doesn't suggest one of the special cases. (I like <>)
I agree. <> really seems to fit well, even if it *does* reinforce the idea that Monoid is for gluing things together -- which, you know, it really is rather good for. _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Nicolas Pouillard http://nicolaspouillard.fr

Nicolas Pouillard wrote:
Excerpts from Edward Kmett's message of Fri Sep 18 00:11:12 +0200 2009:
I also really like <>.
I'm also in favor of <>
mappend me to the list of people who prefer <> . Regards, apfelmus -- http://apfelmus.nfshost.com

On 9/17/09, Ross Paterson
I prefer using a new operator instead of generalizing ++ (or +, *, && or ||), because I think that a monoid operation is so abstract that it needs a name that doesn't suggest one of the special cases. (I like <>)
<> collides with the same operator defined in Text.PrettyPrint. Please don't add operator that collides with something else that is already in the standard libraries. The operators looks very ugly when they are quantified. We should save at least some very often used functions and operators from collision. Krasimir

<> collides with the same operator defined in Text.PrettyPrint. Please don't add operator that collides with something else that is already in the standard libraries.
Is it possible that the pretty-printing <> is in fact just another instance of the Monoidal mappend? Regards, Malcolm

Is it possible that the pretty-printing <> is in fact just another instance of the Monoidal mappend?
Yes. (<>) :: Doc -> Doc -> Doc Source Beside. <> is associative, with identity empty. http://haskell.org/ghc/docs/latest/html/libraries/pretty/Text-PrettyPrint-Hu...<> -- JP

Ok. Then this proposal should be accompanied with the proposal to
generalize Text.PrettyPrint.<>.
On 9/18/09, Jean-Philippe Bernardy
Is it possible that the pretty-printing <> is in fact just another instance of the Monoidal mappend?
Yes.
(<>) :: Doc -> Doc -> Doc Source Beside. <> is associative, with identity empty.
http://haskell.org/ghc/docs/latest/html/libraries/pretty/Text-PrettyPrint-Hu...<>
-- JP _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Thu, 2009-09-17 at 14:37 +0100, Ross Paterson wrote:
This proposal seems to have got stuck. Everyone wants an infix operator, but we can't agree what it should be.
I prefer using a new operator instead of generalizing ++ (or +, *, && or ||), because I think that a monoid operation is so abstract that it needs a name that doesn't suggest one of the special cases. (I like <>)
Nice. For some reason I much prefer a symbol like <> to one like +>. I want to say that it's because it looks symmetric, though of course mappend, ++ are associative not symmetric, so it's not a very good argument. But I still like it! :-) So I guess we should adjust the proposal, or make a new one. * Suggest the name <> (which so far seems to have popular support) * Get rid of the suggestion for a reverse mappend operator * As Krasimir says, include in the proposal that we would deal with the existing libraries that use a local <> for their mappend operator (at least Text.PrettyPrint). One thing we've not mentioned much is operator precedence. Existing uses: infixr 5 Data.Sequence.>< infixl 6 Text.PrettyPrint.<> Existing proposal about (+>) infixl 4 +> Duncan

I'ved chewed on the associativity and precedence issue for <> a little bit.
Here are my thoughts.
infixl 6 <> would match the precedence of +, which is nice on paper, and how
I happen to implement (+) in Data.Monoid.Sugar in the monoids library. I now
believe that it is not quite right.
On paper infixr vs. infixl is basically irrelevant because the result is
monoidal, but in practice infixr tends to work better for a lot of real
world monoids we care about like list appending. Take a look at the behavior
of ((... ++ b) ++ c) vs (a ++ (b ++ ...) for a compelling justification for
why infixr is probably better in practice for the poster child of the monoid
lineup.
Ross's infixr 5 >< in Data.Sequence is the same precedence and fixity as ++,
which also seems like a good answer at first, but infixr 5 <> would change
the behavior of programs that use Text.PrettyPrint.HughesPJ, which relies on
the fixity of <> and <+> being higher than $$ and $+$ which are infixl 5.
The original proposed infixr/l 4 is low enough that you couldn't even mix
the use of <> with the various comparators from Eq and Ord, and it
exacerbates all of the above issues -- by inverting the precedence of $$ and
<> -- so I think it should be off the table. For similar reasons I don't
like lowering the fixity off $$ and $+$ in HughesPJ to 4 to permit infixr 5
<>.
So, in light of all of that, it would seem that the most compatible general
change would be to set:
infixr 6 <>
and to change the associativity of <+> in Text.PrettyPrint.HughesPJ to
match, so that they can be intermixed. Version 3.0 of the HughesPJ
combinators, released back in 1997 has fixed any performance regression that
would be caused by changing the associativity. I hope everyone will have
upgraded by now. ;)
This binds slightly tighter than ++, but retains the same asymptotic
performance, works with == <=, etc. and only requires the minor
associativity tweak to HughesPJ, which should be allowed just fine under the
pretty printer combinator laws, so exxisting HughesPJ code should continue
to run just fine, and other existing code wouldn't be using the new
operator, so shouldn't require any tweaks.
-Edward Kmett
On Fri, Sep 18, 2009 at 7:18 AM, Duncan Coutts
On Thu, 2009-09-17 at 14:37 +0100, Ross Paterson wrote:
This proposal seems to have got stuck. Everyone wants an infix operator, but we can't agree what it should be.
I prefer using a new operator instead of generalizing ++ (or +, *, && or ||), because I think that a monoid operation is so abstract that it needs a name that doesn't suggest one of the special cases. (I like <>)
Nice. For some reason I much prefer a symbol like <> to one like +>.
I want to say that it's because it looks symmetric, though of course mappend, ++ are associative not symmetric, so it's not a very good argument. But I still like it! :-)
So I guess we should adjust the proposal, or make a new one. * Suggest the name <> (which so far seems to have popular support) * Get rid of the suggestion for a reverse mappend operator * As Krasimir says, include in the proposal that we would deal with the existing libraries that use a local <> for their mappend operator (at least Text.PrettyPrint).
One thing we've not mentioned much is operator precedence. Existing uses: infixr 5 Data.Sequence.>< infixl 6 Text.PrettyPrint.<> Existing proposal about (+>) infixl 4 +>
Duncan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Excerpts from Edward Kmett's message of Fri Sep 18 16:04:47 +0200 2009:
I'ved chewed on the associativity and precedence issue for <> a little bit. Here are my thoughts.
infixl 6 <> would match the precedence of +, which is nice on paper, and how I happen to implement (+) in Data.Monoid.Sugar in the monoids library. I now believe that it is not quite right.
On paper infixr vs. infixl is basically irrelevant because the result is monoidal, but in practice infixr tends to work better for a lot of real world monoids we care about like list appending. Take a look at the behavior of ((... ++ b) ++ c) vs (a ++ (b ++ ...) for a compelling justification for why infixr is probably better in practice for the poster child of the monoid lineup.
Ross's infixr 5 >< in Data.Sequence is the same precedence and fixity as ++, which also seems like a good answer at first, but infixr 5 <> would change the behavior of programs that use Text.PrettyPrint.HughesPJ, which relies on the fixity of <> and <+> being higher than $$ and $+$ which are infixl 5.
The original proposed infixr/l 4 is low enough that you couldn't even mix the use of <> with the various comparators from Eq and Ord, and it exacerbates all of the above issues -- by inverting the precedence of $$ and <> -- so I think it should be off the table. For similar reasons I don't like lowering the fixity off $$ and $+$ in HughesPJ to 4 to permit infixr 5 <>.
So, in light of all of that, it would seem that the most compatible general change would be to set:
Good work.
infixr 6 <>
+1 -- Nicolas Pouillard http://nicolaspouillard.fr

On Fri, Sep 18, 2009 at 9:21 AM, Nicolas Pouillard < nicolas.pouillard@gmail.com> wrote:
Good work.
infixr 6 <>
+1
I've updated the ticket: http://hackage.haskell.org/trac/ghc/ticket/3339

On Fri, 2009-09-18 at 10:04 -0400, Edward Kmett wrote:
I'ved chewed on the associativity and precedence issue for <> a little bit. Here are my thoughts.
Thanks for the analysis. There's just one bit I don't quite follow.
Ross's infixr 5 >< in Data.Sequence is the same precedence and fixity as ++, which also seems like a good answer at first, but infixr 5 <> would change the behavior of programs that use Text.PrettyPrint.HughesPJ, which relies on the fixity of <> and <+> being higher than $$ and $+$ which are infixl 5.
The original proposed infixr/l 4 is low enough that you couldn't even mix the use of <> with the various comparators from Eq and Ord, and it exacerbates all of the above issues -- by inverting the precedence of $$ and <> -- so I think it should be off the table. For similar reasons I don't like lowering the fixity off $$ and $+$ in HughesPJ to 4 to permit infixr 5 <>.
It's not clear to me why changing the fixity of $$ and $+$ would be bad. I see that using infixl/r for <> would be bad because we cannot mix >= etc with <> and there are obviously many types that can be in Monoid and Ord. On the other hand Doc is not in any type classes except Show. So I don't see that the point applies to the HughesPJ lib.
So, in light of all of that, it would seem that the most compatible general change would be to set:
infixr 6 <>
Of course one could argue that you might want a type in Monoid and Ord and have a spare precedence level between <> and >=. But I don't see how we can claim it's necessary for compatibility reasons. If we do need a spare precedence level between <> and >= then fine, but all things being equal it seems preferable to go with the same precedence as ++. Duncan

On Fri, Sep 18, 2009 at 5:28 PM, Duncan Coutts
On Fri, 2009-09-18 at 10:04 -0400, Edward Kmett wrote:
I'ved chewed on the associativity and precedence issue for <> a little bit. Here are my thoughts.
Thanks for the analysis. There's just one bit I don't quite follow.
Ross's infixr 5 >< in Data.Sequence is the same precedence and fixity as ++, which also seems like a good answer at first, but infixr 5 <> would change the behavior of programs that use Text.PrettyPrint.HughesPJ, which relies on the fixity of <> and <+> being higher than $$ and $+$ which are infixl 5.
The original proposed infixr/l 4 is low enough that you couldn't even mix the use of <> with the various comparators from Eq and Ord, and it exacerbates all of the above issues -- by inverting the precedence of $$ and <> -- so I think it should be off the table. For similar reasons I don't like lowering the fixity off $$ and $+$ in HughesPJ to 4 to permit infixr 5 <>.
It's not clear to me why changing the fixity of $$ and $+$ would be bad. I see that using infixl/r for <> would be bad because we cannot mix >= etc with <> and there are obviously many types that can be in Monoid and Ord. On the other hand Doc is not in any type classes except Show. So I don't see that the point applies to the HughesPJ lib.
So, in light of all of that, it would seem that the most compatible general change would be to set:
infixr 6 <>
Of course one could argue that you might want a type in Monoid and Ord and have a spare precedence level between <> and >=. But I don't see how
we can claim it's necessary for compatibility reasons. Sorry, I didn't mean to imply that the extra level between <> and == was purely for compatibility with Eq and Ord. Perhaps those were the wrong example, but there is a case to be made for wanting to keep the number of hard-to-predict consequences of precedence changes to a minimum. If we do need a spare precedence level between <> and >= then fine, but
all things being equal it seems preferable to go with the same precedence as ++.
I don't know, and I don't know that anyone can know what other operators people have used in code that uses HughesPJ or any of the other pretty printer combinator libraries. Most compelling, is that there is an implicit 'infixr 5 :' in the Prelude and the pretty printer combinator libraries use [Doc] all over the place. So moving one level down would break a lot of pretty printer client code. As a happy side note Text.PrettyPrint.Leijen already contains infixr 6 <> and requires no changes other than the optional cleanup of using the new operator. ;) -Edward Kmett

On Fri, 2009-09-18 at 20:33 -0400, Edward Kmett wrote:
I don't know, and I don't know that anyone can know what other operators people have used in code that uses HughesPJ or any of the other pretty printer combinator libraries. Most compelling, is that there is an implicit 'infixr 5 :' in the Prelude and the pretty printer combinator libraries use [Doc] all over the place. So moving one level down would break a lot of pretty printer client code.
Yep, fair enough. infixr 6 <> it is then :-) Sadly it looks like we're too late to change base before ghc-6.12.1, so this will probably only make it into a released base version in a year's time. :-( Duncan

On Thu, 17 Sep 2009, Ross Paterson wrote:
This proposal seems to have got stuck. Everyone wants an infix operator, but we can't agree what it should be.
I prefer using a new operator instead of generalizing ++ (or +, *, && or ||), because I think that a monoid operation is so abstract that it needs a name that doesn't suggest one of the special cases. (I like <>)
'<>' looks like "inequality" in other languages. Apart from that, the symbol looks fine to me, too.

On Fri, Sep 25, 2009 at 12:16 AM, Henning Thielemann
On Thu, 17 Sep 2009, Ross Paterson wrote:
This proposal seems to have got stuck. Everyone wants an infix operator, but we can't agree what it should be.
This proposal seems to have got stuck *again*. This is a call for consensus. Do we agree to add infixr 6 <> (<>) :: Monoid m => m -> m -> m (<>) = mappend If so I have a patch for base and GHC ready. -- Johan

On 14 August 2011 21:32, Johan Tibell
On Fri, Sep 25, 2009 at 12:16 AM, Henning Thielemann
wrote: On Thu, 17 Sep 2009, Ross Paterson wrote:
This proposal seems to have got stuck. Everyone wants an infix operator, but we can't agree what it should be.
This proposal seems to have got stuck *again*.
This is a call for consensus. Do we agree to add
infixr 6 <>
(<>) :: Monoid m => m -> m -> m (<>) = mappend
I agree with this, though the subject doesn't ;-) -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Hi,
On Sun, Aug 14, 2011 at 1:32 PM, Johan Tibell
On Fri, Sep 25, 2009 at 12:16 AM, Henning Thielemann
wrote: On Thu, 17 Sep 2009, Ross Paterson wrote:
This proposal seems to have got stuck. Everyone wants an infix
operator,
but we can't agree what it should be.
This proposal seems to have got stuck *again*.
This is a call for consensus. Do we agree to add
infixr 6 <>
(<>) :: Monoid m => m -> m -> m (<>) = mappend
If so I have a patch for base and GHC ready.
-- Johan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
I already use this synonym a lot, but I currently have to define it each time. So, I agree in accept this proposal. -- Daniel Díaz

Johan Tibell writes:
This is a call for consensus. Do we agree to add
infixr 6 <>
(<>) :: Monoid m => m -> m -> m (<>) = mappend
As I recall, the only remaining issue is that this operator is declared as infixl 6 in the pretty package. Someone needs to investigate the impact of changing its fixity there.

On Sun, Aug 14, 2011 at 1:52 PM, Paterson, Ross
Johan Tibell writes:
This is a call for consensus. Do we agree to add
infixr 6 <>
(<>) :: Monoid m => m -> m -> m (<>) = mappend
As I recall, the only remaining issue is that this operator is declared as infixl 6 in the pretty package. Someone needs to investigate the impact of changing its fixity there.
Already done here: http://hackage.haskell.org/trac/ghc/ticket/3339#comment:22 Seems to be a slight improvement actually.

On Sun, 2011-08-14 at 14:22 +0100, Johan Tibell wrote:
On Sun, Aug 14, 2011 at 1:52 PM, Paterson, Ross
wrote: Johan Tibell writes:
This is a call for consensus. Do we agree to add
infixr 6 <>
(<>) :: Monoid m => m -> m -> m (<>) = mappend
As I recall, the only remaining issue is that this operator is declared as infixl 6 in the pretty package. Someone needs to investigate the impact of changing its fixity there.
Already done here: http://hackage.haskell.org/trac/ghc/ticket/3339#comment:22
Seems to be a slight improvement actually.
So I was preparing to commit this change in base and validating ghc when I discovered a more subtle issue in the pretty package: Consider a <> empty <+> b The fixity of <> and <+> is critical: (a <> empty) <+> b = { empty is unit of <> } (a ) <+> b a <> (empty <+> b) = { empty is unit of <+> } a <> ( b) Currently Text.Pretty declares infixl 5 <>, <+>. If we change them to be infixr then we get the latter meaning of a <> empty <+> b. Existing code relies on the former meaning and produces different output with the latter (e.g. ghc producing error messages like "instancefor" when it should have been "instance for"). Suggestions? Duncan

On Sun, Nov 6, 2011 at 8:37 AM, Duncan Coutts
On Sun, 2011-08-14 at 14:22 +0100, Johan Tibell wrote:
On Sun, Aug 14, 2011 at 1:52 PM, Paterson, Ross
wrote: Johan Tibell writes:
This is a call for consensus. Do we agree to add
infixr 6 <>
(<>) :: Monoid m => m -> m -> m (<>) = mappend
As I recall, the only remaining issue is that this operator is declared as infixl 6 in the pretty package. Someone needs to investigate the impact of changing its fixity there.
Already done here: http://hackage.haskell.org/trac/ghc/ticket/3339#comment:22
Seems to be a slight improvement actually.
So I was preparing to commit this change in base and validating ghc when I discovered a more subtle issue in the pretty package:
Consider
a <> empty <+> b
The fixity of <> and <+> is critical:
(a <> empty) <+> b = { empty is unit of <> } (a ) <+> b
a <> (empty <+> b) = { empty is unit of <+> } a <> ( b)
Currently Text.Pretty declares infixl 5 <>, <+>. If we change them to be infixr then we get the latter meaning of a <> empty <+> b. Existing code relies on the former meaning and produces different output with the latter (e.g. ghc producing error messages like "instancefor" when it should have been "instance for").
Suggestions?
Don't use Monoid.(<>) in pretty for now, until someone has time to think about how pretty fits into a world with Monoid exporting <>. -- Johan

On Sun, 2011-11-06 at 16:37 +0000, Duncan Coutts wrote:
So I was preparing to commit this change in base and validating ghc when I discovered a more subtle issue in the pretty package:
Consider
a <> empty <+> b
The fixity of <> and <+> is critical:
(a <> empty) <+> b = { empty is unit of <> } (a ) <+> b
a <> (empty <+> b) = { empty is unit of <+> } a <> ( b)
Currently Text.Pretty declares infixl 5 <>, <+>. If we change them to be infixr then we get the latter meaning of a <> empty <+> b. Existing code relies on the former meaning and produces different output with the latter (e.g. ghc producing error messages like "instancefor" when it should have been "instance for").
Suggestions?
Ian suggests making <> bind tighter than <+>. Initially it seems to me slightly odd for <+> to have a different precedence to <>, but I can't see any practical problems. So specifically that'd be: infixr 6 <> -- from Data.Monoid infixr 7 <+> -- in Text.Pretty Can anyone see any problems with this? Note that I'm not proposing to change Text.Pretty right now. That can be done by the maintainer later. Right now I'm just making the change in Data.Monoid in base. But I wanted to check if anything did go wrong with Text.Pretty before changing Data.Monoid. Duncan

On Sun, Nov 06, 2011 at 05:39:38PM +0000, Duncan Coutts wrote:
Note that I'm not proposing to change Text.Pretty right now.
I don't think we should change Monoid but not pretty. We'll end up with one GHC release in which Data.Monoid and Text.Pretty export conflicting definitions of <>, so people using both will need to disambiguate. I don't have a strong opinion about whether both or neither are changed. Thanks Ian

On Sun, 2011-11-06 at 17:39 +0000, Duncan Coutts wrote:
Ian suggests making <> bind tighter than <+>.
Initially it seems to me slightly odd for <+> to have a different precedence to <>, but I can't see any practical problems. So specifically that'd be:
infixr 6 <> -- from Data.Monoid infixr 7 <+> -- in Text.Pretty
Can anyone see any problems with this?
Sigh, getting my precedence direction confused. I mean: infixr 6 <> -- from Data.Monoid infixr 5 <+> -- in Text.Pretty The point is <> binds tighter than <+>, so that: a <> empty <+> b = (a <> empty) <+> b a <+> empty <> b = a <+> (empty <> b)
Note that I'm not proposing to change Text.Pretty right now. That can be done by the maintainer later. Right now I'm just making the change in Data.Monoid in base. But I wanted to check if anything did go wrong with Text.Pretty before changing Data.Monoid.
And I take Ian's point that we should adjust the 'pretty' package before we release ghc-7.4. Duncan

On 6 Nov 2011, at 16:37, Duncan Coutts wrote:
On Sun, 2011-08-14 at 14:22 +0100, Johan Tibell wrote:
On Sun, Aug 14, 2011 at 1:52 PM, Paterson, Ross
wrote: Johan Tibell writes:
This is a call for consensus. Do we agree to add
infixr 6 <>
(<>) :: Monoid m => m -> m -> m (<>) = mappend
Currently Text.Pretty declares infixl 5 <>, <+>.
So what is the rationale for the new Monoidal operator <> to be declared infixr 6? Why can it not simply preserve the same fixity as already used by Pretty's <> ? Regards, Malcolm

That was discussed previously (also in the ticket). Using infixl
would cause performance problems with, e.g., lists and other list-like
structures such as things that translate to CPS.
On 6 November 2011 17:40, Malcolm Wallace
On 6 Nov 2011, at 16:37, Duncan Coutts wrote:
On Sun, 2011-08-14 at 14:22 +0100, Johan Tibell wrote:
On Sun, Aug 14, 2011 at 1:52 PM, Paterson, Ross
wrote: Johan Tibell writes:
This is a call for consensus. Do we agree to add
infixr 6 <>
(<>) :: Monoid m => m -> m -> m (<>) = mappend
Currently Text.Pretty declares infixl 5 <>, <+>.
So what is the rationale for the new Monoidal operator <> to be declared infixr 6? Why can it not simply preserve the same fixity as already used by Pretty's <> ?
Regards, Malcolm
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Push the envelope. Watch it bend.

On Sun, Nov 6, 2011 at 9:40 AM, Malcolm Wallace
So what is the rationale for the new Monoidal operator <> to be declared infixr 6? Why can it not simply preserve the same fixity as already used by Pretty's <> ?
Could someone put together a list of the operators in base and their precedence. Does making <> have precedence 6 change anything? It has right associativity because it's the right thing for "stream like" uses of <> (lists, builders, CPS). Aside: I don't think we should try to avoid collisions with downstream symbols when growing the base libraries. It's just not a scalable approach engineering wise. We should use namespaces to distinguish symbols from different packages. -- Johan

Aside: I don't think we should try to avoid collisions with downstream symbols when growing the base libraries. It's just not a scalable approach engineering wise. We should use namespaces to distinguish symbols from different packages.
Agreed. But in this particular case we should remember that pretty was once part of base, and remains a ghc boot package. Regards, Malcolm

Whichever way you go on this someone might get (slightly) annoyed, since:
Text.PrettyPrint.Leijen
infixr 6 <>,<+>
Text.PrettyPrint.HughesPJ
infixl 6 <>,<+>
So ultimately someone is getting their associativity changed!
However, the motivation for infixr <> is quite simple, it is better for the
list like concatenation and even for the pretty printing scenario you cite.
It was odd to me that the HughesPJ combinators chose to associate to the
left given that the code has lots of hacks to reassociate everything to the
right. There is a discussion of the hacks they introduced in version 3 in
the source code to fix the asymptotics of foldl (<>). However, the code
there operates just fine with either associativity, and even becomes a bit
more efficient when associated to the right a priori. This was the
substance of the discussion back in September of 09 when the final
associativity and fixity were chosen.
It needs to be at least 6 to avoid conflict with (:) and (++). (See the
original analysis for more)
On a more selfish note, when this was proposed a few weeks ago, and the
issue of compatibility with Data.Semigroup was raised, I went through and
changed the associativity of (<>) in Data.Semigroup and its use in all of
its dependents to match the proposed infixr associativity.
I'm loathe to revert a half of those changes and to recolor this bikeshed
again.
Ultimately no code breaks, after all it is changing the associativity of an
operator that is by definition *associative*. ;)
-Edward
On Sun, Nov 6, 2011 at 2:59 PM, Johan Tibell
On Sun, Nov 6, 2011 at 9:40 AM, Malcolm Wallace
wrote: So what is the rationale for the new Monoidal operator <> to be declared infixr 6? Why can it not simply preserve the same fixity as already used by Pretty's <> ?
Could someone put together a list of the operators in base and their precedence. Does making <> have precedence 6 change anything? It has right associativity because it's the right thing for "stream like" uses of <> (lists, builders, CPS).
Aside: I don't think we should try to avoid collisions with downstream symbols when growing the base libraries. It's just not a scalable approach engineering wise. We should use namespaces to distinguish symbols from different packages.
-- Johan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 6 November 2011 20:52, Edward Kmett
Ultimately no code breaks, after all it is changing the associativity of an operator that is by definition associative. ;)
Well, as Duncan pointed out, some code *does* break due to the interaction of <> and <+>. HughesPJ pretty has the rule: empty <+> d = d so (using current assocativity) (foo <> empty) <+> bar == foo <+> bar or (using new associativity): foo <> (empty <+> bar) == foo <> bar As Duncan mentioned, that problem occurs in GHC if you change its pretty printer to use right-assocative <>/<+>. I think that's a design problem, because the same unintuitive problem could happen with the current assocativity: foo <+> empty <> bar The better way to avoid this is to make sure <> binds more tightly than <+>, as proposed in another mail. / Thomas

On Sun, 2011-11-06 at 15:52 -0500, Edward Kmett wrote:
Whichever way you go on this someone might get (slightly) annoyed, since:
Text.PrettyPrint.Leijen infixr 6 <>,<+>
That turns out to be ok because in that module the property is: empty <+> text "foo" = text " foo" whereas for Text.PrettyPrint.HughesPJ, empty is a unit of <+>.
Text.PrettyPrint.HughesPJ infixl 6 <>,<+>
Actually currently all the fixity declarations have been removed, but yes that's what they were in previous released versions. David: presumably this is a mistake? You didn't really mean to remove: infixl 6 <> infixl 6 <+> infixl 5 $$, $+$ when merging with ghc's variant of the pretty print module.
Ultimately no code breaks, after all it is changing the associativity of an operator that is by definition *associative*. ;)
That's what I thought too, but I already gave an example: a <> empty <+> b This means different things depending on whether we use infixl or infixr. And as I noted, this doesn't bite Text.PrettyPrint.Leijen because it lacks the <+> unit law. So my tentative suggestion is: infixr 6 <> infixr 5 <+> infixr 4 $$, $+$ So <> binds tighter than <+> and $$ and $+$ are still lower precedence than <> and <+>, but switched round to being right associative. Duncan

On Sun, Nov 6, 2011 at 4:46 PM, Duncan Coutts
Ultimately no code breaks, after all it is changing the associativity of an operator that is by definition *associative*. ;)
That's what I thought too, but I already gave an example:
a <> empty <+> b
This means different things depending on whether we use infixl or infixr. And as I noted, this doesn't bite Text.PrettyPrint.Leijen because it lacks the <+> unit law.
Bah. Good point.
So my tentative suggestion is:
infixr 6 <> infixr 5 <+> infixr 4 $$, $+$
So <> binds tighter than <+> and $$ and $+$ are still lower precedence than <> and <+>, but switched round to being right associative.
Reasonable, but there is the caveat that causes another problem, which is that now <+>, : and ++ conflict, which was why we had to raise <> to 6 in the first place. We could adopt your proposed fix one level up though with: infixr 7 <> infixr 6 <+> -Edward

On Sun, 2011-11-06 at 16:37 +0000, Duncan Coutts wrote:
So I was preparing to commit this change in base and validating ghc when I discovered a more subtle issue in the pretty package:
Consider
a <> empty <+> b
So having tried to fix this by setting <> higher precedence than <+>, we simply run into the reverse problem a <+> empty <> b The concrete example is in ghc: ptext (sLit "In module") <+> quotes (ppr (is_mod decl_spec)) <+> source_import <> colon This produces strings like "In module `foo':" with the old/current fixities and produces "In module `foo' :" with my suggested fixities. The reason is that source_import is usually empty: source_import | mi_boot iface = ptext (sLit "(hi-boot interface)") | otherwise = empty so if we simplify, it's something like: test "foo" <+> empty <> colon which is "foo:" if it's all infixl, but becomes "foo :" if <> binds more tightly than <+>, since: a <+> empty <> b = a <+> (empty <> b) = a <+> b So maybe we should just conclude that pretty printing should be left associative, building from the left. Either that or we go and track down all the places that use empty in mixed <> <+> contexts. Or any other suggestions for fixes for the pretty package that'd let it use the proposed Data.Monoid.<> with infixr <> ? Could the behaviour of <+> be altered to work in a right associative world? Should we reconsider Data.Monoid.<> if we can't make it work with the pretty package? Duncan

On Mon, 2011-11-07 at 01:13 +0000, Duncan Coutts wrote:
On Sun, 2011-11-06 at 16:37 +0000, Duncan Coutts wrote:
So I was preparing to commit this change in base and validating ghc when I discovered a more subtle issue in the pretty package:
Consider
a <> empty <+> b
So having tried to fix this by setting <> higher precedence than <+>, we simply run into the reverse problem
a <+> empty <> b
The concrete example is in ghc:
ptext (sLit "In module") <+> quotes (ppr (is_mod decl_spec)) <+> source_import <> colon
BTW, I should note that it looks like this is the only instance of this problem in the whole of ghc (based on an analysis of failures in the ghc testsuite), and ghc uses pretty printing combinators pretty heavily. So one argument would be to say it's not that bad, just fix the few places. Still, it'd be nice to have a more principled explanation for the meanings of a <> empty <+> b and a <+> empty <> b Duncan

On 7 Nov 2011, at 01:19, Duncan Coutts wrote:
The concrete example is in ghc:
ptext (sLit "In module") <+> quotes (ppr (is_mod decl_spec)) <+> source_import <> colon
BTW, I should note that it looks like this is the only instance of this problem in the whole of ghc
So let's just fix ghc here. It looks to me like whoever wrote that code was relying on a non-obvious consequence of the precedence. At a glance, it looks like there is intended to be a space before the source_import and colon. And that is exactly what the proposed fixities for <> and <+> will give. I find it hard to believe that many people would consciously have relied on the older behaviour. Regards, Malcolm

| >> ptext (sLit "In module") | >> <+> quotes (ppr (is_mod decl_spec)) | >> <+> source_import <> colon | > | > BTW, I should note that it looks like this is the only instance of this | > problem in the whole of ghc | | So let's just fix ghc here. It looks to me like whoever wrote that code was relying | on a non-obvious consequence of the precedence. At a glance, it looks like there is | intended to be a space before the source_import and colon. And that is exactly what | the proposed fixities for <> and <+> will give. I find it hard to believe that many | people would consciously have relied on the older behaviour. If there's a bug in GHC, or a feature request, can someone make a ticket with a standalone reproducible test case, please? I have not been following the twists and turns of this discussion. Simon

On Mon, Nov 7, 2011 at 05:14, Simon Peyton-Jones
If there's a bug in GHC, or a feature request, can someone make a ticket with a standalone reproducible test case, please? I have not been following the twists and turns of this discussion.
It's not so much a bug as it is code that is less than clear; while in this case cleaning it up is a good idea for other reasons, I suspect if we used that as a general metric most of GHC would have to be rewritten :) -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

On 7 November 2011 14:55, Brandon Allbery
On Mon, Nov 7, 2011 at 05:14, Simon Peyton-Jones
wrote: If there's a bug in GHC, or a feature request, can someone make a ticket with a standalone reproducible test case, please? I have not been following the twists and turns of this discussion.
It's not so much a bug as it is code that is less than clear; while in this case cleaning it up is a good idea for other reasons, I suspect if we used that as a general metric most of GHC would have to be rewritten :) -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
Once we have (<>) = mappend we could make two nice refactorings in GHC
similarly to what I did in these unapplied patches:
http://hackage.haskell.org/trac/ghc/attachment/ticket/4834/ghc_new_monad_hie...
Wed Dec 8 15:54:57 CET 2010 Bas van Dijk

On Mon, 2011-11-07 at 18:51 +0100, Bas van Dijk wrote:
Once we have (<>) = mappend we could make two nice refactorings in GHC similarly to what I did in these unapplied patches:
http://hackage.haskell.org/trac/ghc/attachment/ticket/4834/ghc_new_monad_hie...
Wed Dec 8 15:54:57 CET 2010 Bas van Dijk
* Make SDoc an abstract newtype and add a Monoid instance for it The (<>) combinator of SDocs is removed and replaced by the more general (<>) = mappend combinator from Util.
That's more or less what I did (though SDoc had previously been changed to a newtype), and ran into the issues I described to do with changing the meaning of a <> empty <+> b and a <+> empty <> b Since SDoc mirrors the Pretty.Doc type, then changing the pretty package faces the same issues. As other people have pointed out, the meaning of these constructs is pretty suspect anyway. We have two associative operators with the same precedence which do not associate with each other. Duncan

It's not so much a bug as it is code that is less than clear; while in this case cleaning it up is a good idea for other reasons, I suspect if we used that as a general metric most of GHC would have to be rewritten :)
Great. I’d be delighted to look at it if anyone is motivated to give a brief standalone summary of the problem (and ideally a proposed solution)
Simon
From: Brandon Allbery [mailto:allbery.b@gmail.com]
Sent: 07 November 2011 13:56
To: Simon Peyton-Jones
Cc: Malcolm Wallace; libraries Mailing List
Subject: Re: Proposal #3339: Add (+>) as a synonym for mappend
On Mon, Nov 7, 2011 at 05:14, Simon Peyton-Jones

On Mon, Nov 07, 2011 at 01:13:23AM +0000, Duncan Coutts wrote:
So maybe we should just conclude that pretty printing should be left associative, building from the left.
To clarify, Duncan and I are now thinking that as pretty builds left-to-right strings, perhaps it is natural that the operators in a <+> b <> c <+> d <> e <+> ... should be left-infix, as it is natural to read this as "a then b, then c, ...". [Hmm, I don't know if that was actually any clearer, but a second phrasing can't hurt]
Should we reconsider Data.Monoid.<> if we can't make it work with the pretty package?
And if we do decide that pretty should have an infixl operator and Monoid an infixr operator, then I think there will be fewer headaches if they don't both use the same name. Thanks Ian

On Sun, Nov 6, 2011 at 8:33 PM, Ian Lynagh
On Mon, Nov 07, 2011 at 01:13:23AM +0000, Duncan Coutts wrote:
So maybe we should just conclude that pretty printing should be left associative, building from the left.
To clarify, Duncan and I are now thinking that as pretty builds left-to-right strings, perhaps it is natural that the operators in
a <+> b <> c <+> d <> e <+> ...
should be left-infix, as it is natural to read this as "a then b, then c, ..."
I'm not sure I follow. It would seem that accessing a then (b then ...) would require me to have it associated to the right, otherwise I have (((((...(a then b) then c) and I can't even start figuring out what I'm going to do until I crawl my way down to the bottom. -Edward

On Sun, Nov 06, 2011 at 11:58:10PM -0500, Edward Kmett wrote:
On Sun, Nov 6, 2011 at 8:33 PM, Ian Lynagh
wrote: On Mon, Nov 07, 2011 at 01:13:23AM +0000, Duncan Coutts wrote:
So maybe we should just conclude that pretty printing should be left associative, building from the left.
To clarify, Duncan and I are now thinking that as pretty builds left-to-right strings, perhaps it is natural that the operators in
a <+> b <> c <+> d <> e <+> ...
should be left-infix, as it is natural to read this as "a then b, then c, ..."
I'm not sure I follow.
It would seem that accessing a then (b then ...) would require me to have it associated to the right, otherwise I have
(((((...(a then b) then c) and I can't even start figuring out what I'm going to do until I crawl my way down to the bottom.
You're talking about the relative performance of the two options. I'm talking about the semantics you would expect if you didn't think about performance. Thanks Ian

On Sun, Nov 6, 2011 at 5:13 PM, Duncan Coutts
Should we reconsider Data.Monoid.<> if we can't make it work with the pretty package?
I don't think so. Monoid is much more important then pretty. I also think we need to stop trying to make globally unique identifiers. It doesn't scale. Stop it. :) -- Johan

On Mon, Nov 7, 2011 at 1:17 AM, Johan Tibell
On Sun, Nov 6, 2011 at 5:13 PM, Duncan Coutts < duncan.coutts@googlemail.com> wrote:
Should we reconsider Data.Monoid.<> if we can't make it work with the pretty package?
I don't think so. Monoid is much more important then pretty. I also think we need to stop trying to make globally unique identifiers. It doesn't scale. Stop it. :)
That and any other name we pick is just as likely to be fraught with similar issues. If we really do insist on re-bikeshedding this, I think the only other viable contender is the existing infixr 5 >< from Data.Sequence. Then you could encourage people to switch but not break anyone who imports both Data.Monoid and pretty. (and it becomes easier for me to push for the inclusion of Data.Semigroup later, since the name wouldn't conflict). Personally, I would be fine with either moving to >< or going with infixr 6 <> and just bumping the major version on pretty and sending out a warning about the behavior change, just so long as we actually do it. We've been talking about this for *2 and a half years* now. I'd just as soon be done with it one way or the other. -Edward

Johan Tibell wrote:
This is a call for consensus. Do we agree to add infixr 6 <> (<>) :: Monoid m => m -> m -> m (<>) = mappend
If so I have a patch for base and GHC ready.
NO please don't do that. It would break all packages that do, or soon will, use the semigroups package. That proposal is no longer relevant. Every Monoid instance should now be made an instance of Semigroup. Anyone who wants to use <> should import it from there. Thanks, Yitz

On 14 August 2011 23:43, Yitzchak Gale
Johan Tibell wrote:
This is a call for consensus. Do we agree to add infixr 6 <> (<>) :: Monoid m => m -> m -> m (<>) = mappend
If so I have a patch for base and GHC ready.
NO please don't do that. It would break all packages that do, or soon will, use the semigroups package.
That proposal is no longer relevant. Every Monoid instance should now be made an instance of Semigroup. Anyone who wants to use <> should import it from there.
Which would require that pretty depends on semigroup and thus semigroup becomes a boot library, does it not? -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On 14 August 2011 14:43, Yitzchak Gale
Johan Tibell wrote:
This is a call for consensus. Do we agree to add infixr 6 <> (<>) :: Monoid m => m -> m -> m (<>) = mappend
If so I have a patch for base and GHC ready.
NO please don't do that. It would break all packages that do, or soon will, use the semigroups package.
That proposal is no longer relevant. Every Monoid instance should now be made an instance of Semigroup. Anyone who wants to use <> should import it from there.
So, NOTHING would break if you made made SemiGroup a superclass of Monoid? -- Push the envelope. Watch it bend.

Thomas Schilling wrote:
So, NOTHING would break if you made made SemiGroup a superclass of Monoid?
Right, I didn't propose that. Really, in hindsight, it should be. But as you say, it would break things. Sorry if I was not clear. Rather, each library author should add the superclass. Unfortunately, this is similar to the situation with Functor and Monad. Thanks, Yitz

On 14 August 2011 14:53, Yitzchak Gale
Thomas Schilling wrote:
So, NOTHING would break if you made made SemiGroup a superclass of Monoid?
Right, I didn't propose that. Really, in hindsight, it should be. But as you say, it would break things. Sorry if I was not clear.
Rather, each library author should add the superclass.
Unfortunately, this is similar to the situation with Functor and Monad.
Right. My argument would be that since Monoid is used more commonly, it should get the nice and short name (<>). Of course, SemiGroup as a superclass of Monoid would be nicer. I wonder, how hard it would be to provide an automatic rewriting tool that would rewrite your source code. (This tool would use the GHC API.) -- Push the envelope. Watch it bend.

Thomas Schilling wrote:
My argument would be that since Monoid is used more commonly, it should get the nice and short name (<>).
If it is defined in Data.Semigroup, then it can be used for both. The only reason Monoid is currently so much more common is because the semigroups package is fairly new. Semigroups are simple and quite ubiquitous. We should be strongly encouraging their use, not discouraging it by creating an awkward namespace clash. Thanks, Yitz

On 14 Aug 2011, at 15:25, Yitzchak Gale wrote:
Thomas Schilling wrote:
My argument would be that since Monoid is used more commonly, it should get the nice and short name (<>).
If it is defined in Data.Semigroup, then it can be used for both.
I am in favour of <> for Monoid mappend, indeed I thought this had already been decided a long time ago. I oppose any dependency (at this stage) on Semigroup. For one thing, I don't know what a semigroup is. There is next to no Haddock documentation for the semigroup package, so I am not further enlightened by looking there. As a consequence, I have no idea how to make my types which are currently Monoids into SemiGroups. For instance, although I can guess at "sconcat", what semantics is "replicate1p" supposed to have? What algebraic laws am I supposed to be respecting? Regards, Malcolm

From a quick look at Wikipedia, a semigroup = Monoid - mempty.
I.e., A semigroup only contains (what's currently called) mappend and
obeys all mappend laws (i.e., associativity). A monoid is simple a
semigroup + left and right identy.
Given how simple it is, I would generally be in favour of moving it
into base (with documentation). But there is the issue of backwards
compatibility. It's exactly the same issue as with Applicative and
Functor.
On 14 August 2011 15:50, Malcolm Wallace
On 14 Aug 2011, at 15:25, Yitzchak Gale wrote:
Thomas Schilling wrote:
My argument would be that since Monoid is used more commonly, it should get the nice and short name (<>).
If it is defined in Data.Semigroup, then it can be used for both.
I am in favour of <> for Monoid mappend, indeed I thought this had already been decided a long time ago.
I oppose any dependency (at this stage) on Semigroup. For one thing, I don't know what a semigroup is. There is next to no Haddock documentation for the semigroup package, so I am not further enlightened by looking there. As a consequence, I have no idea how to make my types which are currently Monoids into SemiGroups. For instance, although I can guess at "sconcat", what semantics is "replicate1p" supposed to have? What algebraic laws am I supposed to be respecting?
Regards, Malcolm
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Push the envelope. Watch it bend.

Malcolm Wallace wrote:
For instance, although I can guess at "sconcat", what semantics is "replicate1p" supposed to have?
These are both optional methods, provided only as an opportunity for optimization, analogous to mconcat in Monoid. I have found that to be of great use for sconcat. I agree that replicate1p is a bit strange. But, yes, your point is well taken, the package documentation needs improvement. Thanks, Yitz

On Sun, Aug 14, 2011 at 12:44 PM, Yitzchak Gale
Malcolm Wallace wrote:
For instance, although I can guess at "sconcat", what semantics is "replicate1p" supposed to have?
A semigroup is just an associative operator. sconcat is analogous to mconcat, providing a potentially optimized traversal over a non-empty list. Not necessarily in theory, but in practice quite useful. replicate1p needs to be renamed, but it repeats an element (n + 1) times using peasant multiplication, taking advantage of the associativity to get away with using (<>) only log n times. replicate1p 0 a = a replicate1p 1 a = a <> a replicate1p 3 a = (a <> a) <> (a <> a) etc. I am happy to spend some time working on the documentation. -Edward

On 14 August 2011 15:25, Yitzchak Gale
Thomas Schilling wrote:
The only reason Monoid is currently so much more common is because the semigroups package is fairly new. Semigroups are simple and quite ubiquitous. We should be strongly encouraging their use, not discouraging it by creating an awkward namespace clash.
Semigroups seem a lot less useful than monoids. They might be more ubiquitous, but there seems to be less you can do with them - e.g. sconcat in the Semigroup class is quite convoluted to avoid emptiness; a Writer-like thing without zero would be very strange (presumably it would actually have to be a state monad?). If semigroups don't support an operationally useful API, are they worth having from the documentary perspective - is it valuable to identify that you have semigroup "things" in your program when you have to use type specific operations to do anything useful on them?

Stephen Tetley wrote:
Semigroups seem a lot less useful than monoids. They might be more ubiquitous, but there seems to be less you can do with them
My experience has not been so. For me they are extremely useful, and come up all the time. Here are some concrete examples: The fundamental example of a semigroup is a non-empty list, which comes up all the time. Besides that, many of the "monoids" that come up are really semigroups. One tends to force them to be monoids by artificially adjoining an abstract unit element, resulting in superfluous Maybe wrappers, unsafe pattern matches, convoluted and harder-to-read code, etc. Here is another example that I had, much less trivial: in a large image-recognition application I wrote, there is a type representing graphical objects recognized on the canvas. Each object has its rectangular bounding box as one of its properties. The objects combine to form more and more complex objects as higher-order structure is recognized. There is no natural unit element - even an empty bounding box must exist at some specific location on the canvas. So this is really a semigroup, not a monoid. A vast improvement to my code resulted from porting it from Monoid to Semigroup.
e.g. sconcat in the Semigroup class is quite convoluted to avoid emptiness
It avoids emptiness once, rather than you doing it over and over again in your own code. I don't think that's convoluted at all.
a Writer-like thing without zero would be very strange (presumably it would actually have to be a state monad?).
No. The run function would start with a seed, or a non-empty list, or some other non-empty type. That would be natural, since those are exactly the cases in which you would use it. Thanks, Yitz

Hi,
On Sun, Aug 14, 2011 at 2:43 PM, Yitzchak Gale
NO please don't do that. It would break all packages that do, or soon will, use the semigroups package.
They shouldn't unless they use unqualified implicit imports. Using imports this way is asking for trouble as any time a new identifier is added to a package you depend on, your code might break. If you do use unqualified implicit imports you need to be prepared to fix breakages by adding import lists or qualified imports as needed.
That proposal is no longer relevant. Every Monoid instance should now be made an instance of Semigroup. Anyone who wants to use <> should import it from there.
This doesn't work well unless SemiGroup is a superclass of Monoid. For example, class constraints would have to include redundant information: f :: (Monoid a, SemiGroup a) => a -> ... SemiGroup is redundant here. All monoids are semigroups. Making SemiGroup a superclass of Monoid is not feasible at the moment, as we don't have a way (e.g. class aliases) to do so without breaking lots of code. I don't know of anyone who's actually working on solving this problem at the moment. In addition, I don't want to depend on the semigroup package. It needs more work. For example why does depending on the semigroups package give me a new type for natural numbers and for non-empty lists? I don't object to have a class for semigroups in the future, but we're far from where that is possible in a nice way. Cheers, Johan

On Sun, Aug 14, 2011 at 09:43, Yitzchak Gale
NO please don't do that. It would break all packages that do, or soon will, use the semigroups package.
Umm, I think the semigroups package will break everything that creates Monoid instances anyway. -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

Johan Tibell wrote:
This is a call for consensus. Do we agree to add infixr 6 <> (<>) :: Monoid m => m -> m -> m (<>) = mappend
If so I have a patch for base and GHC ready.
NO please don't do that. It would break all packages that do, or soon will, use the semigroups package.
That proposal is no longer relevant. Every Monoid instance should now be made an instance of Semigroup. Anyone who wants to use <> should import it from there.
+1 for the original Johan's suggestion, ie. <> = Monoid.mappend. Cheers, Milan

+1. this proposal passed last time. it just never happened.
On Sun, Aug 14, 2011 at 7:32 AM, Johan Tibell
On Fri, Sep 25, 2009 at 12:16 AM, Henning Thielemann
wrote: On Thu, 17 Sep 2009, Ross Paterson wrote:
This proposal seems to have got stuck. Everyone wants an infix
operator,
but we can't agree what it should be.
This proposal seems to have got stuck *again*.
This is a call for consensus. Do we agree to add
infixr 6 <>
(<>) :: Monoid m => m -> m -> m (<>) = mappend
If so I have a patch for base and GHC ready.
-- Johan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
participants (30)
-
Alexander Dunlap
-
Bas van Dijk
-
Brandon Allbery
-
Bryan O'Sullivan
-
Conor McBride
-
Daniel Díaz Casanueva
-
Daniel Fischer
-
Duncan Coutts
-
Duncan Coutts
-
Edward Kmett
-
Ganesh Sittampalam
-
Heinrich Apfelmus
-
Henning Thielemann
-
Ian Lynagh
-
Ivan Lazar Miljenovic
-
Jean-Philippe Bernardy
-
Johan Tibell
-
Krasimir Angelov
-
Malcolm Wallace
-
Malcolm Wallace
-
Milan Straka
-
Nicolas Pouillard
-
Paterson, Ross
-
Ross Paterson
-
Samuel Bronson
-
Simon Peyton-Jones
-
Stephen Tetley
-
Thomas Schilling
-
Wolfgang Jeltsch
-
Yitzchak Gale