Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-06 Thread Mattias Bengtsson
On Sun, 2009-07-05 at 22:30 +0200, Henning Thielemann wrote:
 
 (?) is also undefined in Prelude.

Which i think is a good thing. 
I think it's quite nice to use (?) as an operator in higher order
functions. 
Eg. 
foldr _ z [] =  z
foldr (?) z (x:xs) =  x ? foldr (?) z xs

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-06 Thread Ketil Malde
Mattias Bengtsson moonl...@dtek.chalmers.se writes:

 (?) is also undefined in Prelude.

 Which i think is a good thing. 
 I think it's quite nice to use (?) as an operator in higher order
 functions. 

Also, it clashes with the implicit parameters extension, and combining
the extension with a user-defined (?) operator resulted in (?) having
a whitespace-dependent meaning, IIRC. 

This is perhaps not so crucial anymore, in the time since I stumbled
into this  -fglasgow-exts has largely been replaced by more
fine-grained mechanisms, and implicit parameters has become less
fashionable. 

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-05 Thread Henning Thielemann
Robert Greayer schrieb:
 I'm sure there's some important historical reason... but why isn't ''
 used in something more prominent than the fgl package?  I understand
 why it's not used for bitwise AND in Data.Bits (I assume because the
 corresponding bitwise '|' operator isn't available), but all the other
 single-character operators** (in the ASCII range) are used in some
 core library (if not the Prelude itself).  But not ''.  Why?  It
 makes sense (to me) as a Monoid 'append'.

(?) is also undefined in Prelude.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-05 Thread Henning Thielemann


On Tue, 30 Jun 2009, Bryan O'Sullivan wrote:


I've thought for a while that it would be very nice indeed if the Monoid class 
had a more
concise operator for infix appending than a `mappend` b. I wonder if other 
people are of a
similar opinion, and if so, whether this is worth submitting a libraries@ 
proposal over.


We have the package version policy which relies on explicit or qualified 
imports, such that adding a function like (++) to Data.Monoid cannot harm 
any package that follow that policy. Thus I vote for not introducing a new 
operator, in order to keep the set of infix operators to memorize small, 
but use (++) for the generalized (List.++) aka mappend. The user would 
however need to hide (++) from Prelude.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-05 Thread Edward Kmett
While I like the idea of (++) as mappend to some extent, two objections
immediately come to mind:
1.) While I like the appeal to the PVP to export a version of (++) from
Data.Monoid and I think this has worked out well for new modules like
Control.Category, I'm not sure that with a module that has been around for
so long as Data.Monoid can be so flippant about breaking any code that
imports it unqualified that also happens to use a list. Lists are everywhere
in Haskell, and unqualified imports do exist.

2.) There is also a pretty big caveat in that the choice of which operator
should be naturally selected for (++) _is_ ambiguous. Should it be mappend
or mplus?  Recall that in Haskell 1.4 (++) worked on MonadPlus and it was
changed in the great monomorphism revolution of '98.

-Edward Kmett

On Sun, Jul 5, 2009 at 4:41 PM, Henning Thielemann 
lemm...@henning-thielemann.de wrote:


 On Tue, 30 Jun 2009, Bryan O'Sullivan wrote:

  I've thought for a while that it would be very nice indeed if the Monoid
 class had a more
 concise operator for infix appending than a `mappend` b. I wonder if
 other people are of a
 similar opinion, and if so, whether this is worth submitting a 
 librar...@proposal over.


 We have the package version policy which relies on explicit or qualified
 imports, such that adding a function like (++) to Data.Monoid cannot harm
 any package that follow that policy. Thus I vote for not introducing a new
 operator, in order to keep the set of infix operators to memorize small, but
 use (++) for the generalized (List.++) aka mappend. The user would however
 need to hide (++) from Prelude.

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-04 Thread Brandon S. Allbery KF8NH

On Jul 4, 2009, at 01:17 , Jason Dusek wrote:

 What is the proper name for the operation on functions of a
 functor, anyway? The name `fmap` seems to driven by an analogy
 with `map`.



Cale (.) /Cale

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-03 Thread George Pollard
This discussion points to a wider issue: at some stage we should look
at pulling all the nice new stuff into Haskell prelude. I'm looking
at you, Data.Foldable,Traversable.

Also, throw out `map`. ;)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-03 Thread Jason Dusek
2009/07/03 George Pollard por...@porg.es:
 This discussion points to a wider issue: at some stage we
 should look at pulling all the nice new stuff into Haskell
 prelude. I'm looking at you, Data.Foldable,Traversable.

 Also, throw out `map`. ;)

  What is the proper name for the operation on functions of a
  functor, anyway? The name `fmap` seems to driven by an analogy
  with `map`.

--
Jason Dusek
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-03 Thread Alexander Dunlap
On Fri, Jul 3, 2009 at 10:17 PM, Jason Dusekjason.du...@gmail.com wrote:
 2009/07/03 George Pollard por...@porg.es:
 This discussion points to a wider issue: at some stage we
 should look at pulling all the nice new stuff into Haskell
 prelude. I'm looking at you, Data.Foldable,Traversable.

 Also, throw out `map`. ;)

  What is the proper name for the operation on functions of a
  functor, anyway? The name `fmap` seems to driven by an analogy
  with `map`.

 --
 Jason Dusek
 ___

I think map would be the right name. IMO, what would be really nice
would be to rename fmap to map (and then fmap would become a
deprecated synonym for map), etc., and get rid of many of the special
cases for lists in the Prelude. The only backward compatibility
problem that has been brought up is monomorphism restriction stuff,
though.

Alex
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-03 Thread George Pollard
2009/7/4 Jason Dusek jason.du...@gmail.com:
 2009/07/03 George Pollard por...@porg.es:
 Also, throw out `map`. ;)

  What is the proper name for the operation on functions of a
  functor, anyway? The name `fmap` seems to driven by an analogy
  with `map`.

This is getting a little off topic, but I don't believe it has a name.
In category theory the name of the functor is used as an operation on
the function, so that given the functor F, instead of writing `fmap
f` you'd write `F(f)`. I think this is one area where Haskell wins
notationally :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-02 Thread Jules Bean

Ross Paterson wrote:

On Wed, Jul 01, 2009 at 10:55:39AM -0700, Bryan O'Sullivan wrote:

Okay, here's a tentative plan that will help to figure out the answer. I'll
build a fiddled base package that rewires the Monoid class to have (++) be the
binary operator, and mappend as a synonym for it. I'll import the Monoid (++)
into the Prelude. I'll see how much breaks. If that much builds smoothly, I'll
see how much of the rest of Hackage builds, both with and without this custom
base package. I'll follow up here with the results, along with a suggestion of
how acceptable I think the observed level of breakage is.


Generalizing (++) will break some Haskell 98 code, e.g.

  append = (++)

I think that's a show-stopper.


I agree it's an issue; and it's the reason I didn't even suggest it 
myself, favouring a new symbol.


I don't think it's a show stopper, in principle. In principle you can 
imagine a -h98 flag which you pass to compilers which choose a strictly 
h98-compliant prelude as opposed to a slightly generalised newer one.


I'm not the person who would have to maintain that arrangement. I guess 
that's a call for the people who would have to do the work. There is 
already a haskell98 package, I think, which is the first step?


Jules
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-02 Thread Alexander Dunlap
On Wed, Jul 1, 2009 at 11:26 AM, Ross Patersonr...@soi.city.ac.uk wrote:
 On Wed, Jul 01, 2009 at 10:55:39AM -0700, Bryan O'Sullivan wrote:
 Okay, here's a tentative plan that will help to figure out the answer. I'll
 build a fiddled base package that rewires the Monoid class to have (++) be 
 the
 binary operator, and mappend as a synonym for it. I'll import the Monoid (++)
 into the Prelude. I'll see how much breaks. If that much builds smoothly, 
 I'll
 see how much of the rest of Hackage builds, both with and without this custom
 base package. I'll follow up here with the results, along with a suggestion 
 of
 how acceptable I think the observed level of breakage is.

 Generalizing (++) will break some Haskell 98 code, e.g.

  append = (++)

 I think that's a show-stopper.
 ___

Could we use some default rules to keep H98 code working? I don't know
much about defaulting, but

times = (*)

works fine and defaults to type Integer. Could we not do the same
thing with monoids, having monoids default to type []?

Alex
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-02 Thread Alexander Dunlap
On Wed, Jul 1, 2009 at 10:11 PM, David Menendezd...@zednenem.com wrote:
 In Wed, Jul 1, 2009 at 3:38 PM, Thomas Schillingnomin...@googlemail.com 
 wrote:
 2009/7/1 David Leimbach leim...@gmail.com
 Just because the compiler can figure out what I mean because it has a great
 type system, I might not be able to figure out what I mean a year from now
 if I see ++ everywhere.

 Yep, had the same experience.  On the one hand, using monoids lets you
 delay some design decisions for later and lets you reuse more library
 code.  On the other hand, it sometimes makes it really hard to see
 what the code is actually doing--especially if you use more than one
 monoid.

 For this reason on of the first advanced features I implemented in the
 (yet unreleased) scion IDE library allows you to look up the
 instantiated type of an identifier.  Unfortunately, jumping to the
 definition (or documentation) of the monoid instance is a bit more
 difficult.  Haddock should allow documentation on instance
 declarations...

 I disagree. The solution is to not create instances when it isn't
 obvious what the instance does. That's why we have Sum and Prod in
 Data.Monoid instead of declaring instances directly for Int.

 With Monoid, I'd go further and say that you should not use mempty and
 mappend unless you are writing polymorphic code. If you are writing to
 a specific monoid instance, you should use a specific function.

 --
 Dave Menendez d...@zednenem.com
 http://www.eyrie.org/~zednenem/
 ___

I tend to disagree. I think that Haskell has seen a lot of syntax
bloat in the interest of monomorphism. We have List.append, Map.union,
Set.union, Sequence., etc., all with different notation, even though
these all denote the same operation: taking two of (whatever) and
combining them into one. With mappend, you know exactly what the
function is supposed to do: combine two things together, and it
doesn't matter what datatypes you're using, because that's always what
it means.

Alex
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-02 Thread Ross Paterson
On Thu, Jul 02, 2009 at 12:46:37PM +0100, Jules Bean wrote:
 I'm not the person who would have to maintain that arrangement. I guess  
 that's a call for the people who would have to do the work. There is  
 already a haskell98 package, I think, which is the first step?

The Prelude is in the base package.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-02 Thread Edward Kmett
 Wed, Jul 1, 2009 at 4:17 PM, Raynor Vliegendhart shinnon...@gmail.comwrote:

 We could use (Control.Category..) as an operator, but this would
 require an additional wrapping layer if we wish to use the existing
 Monoid instances:

  import Prelude hiding (id, (.))
  import Control.Category
  import Data.Monoid
 
  -- Category wrapper for existing Monoid instances
  newtype MonoidC m a b = MonoidC {unwrapMC :: m} deriving (Show)
 
  instance Monoid m = Category (MonoidC m) where
  id = MonoidC mempty
  MonoidC m . MonoidC n = MonoidC $ m `mappend` n

 Furthermore, writing Category instances for monoids require dummy type
 parameters:

  -- Example instance
  newtype SumC m a b = SumC {getSumC :: m} deriving (Show, Eq)
 
  instance Num a = Category (SumC a) where
  id = SumC (fromIntegral 0)
  SumC x . SumC y = SumC $ x + y

I have a monoid-as-category and category-endomorphism as monoid in:
http://comonad.com/haskell/monoids/dist/doc/html/monoids/Data-Monoid-Categorical.html

but there are issues.

1.)  these completely change the typing involved
2.) the monoid as category-with-one-object is pretty scary to someone
without a category theory background.
3.) This doesn't properly represent the category-with-one-object because at
best the two phantom types yield you something like a category like Hask,
which has been fully connected * M where M is the category of your monoid.
Even if you use GADTs to cut down the phantom types to one where the head
and tail of the arrow are the same object and |.| takes a category to its
discrete category (discarding all non-identity arrows) you are looking at a
category like |Hask| * M because of the phantom type.

data CMonoid m n o where
M :: Monoid m = m - CMonoid m a a

instance Monoid m = Category (CMonoid m) where
id = M mempty
M a . M b = M (a `mappend` b)

 Attempting to go any further and railroad that type to equal m fails when
you go to define id. So the categorical notion of a monoid is pretty much a
non-starter in Haskell.

 -Edward Kmett

On
Another disadvantage of this approach is that we cannot have a default
monoid instance for lists (kind mismatch).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-02 Thread Richard O'Keefe

It is claimed that making ++ become another name for the
Monoid mappend operation will break some Haskell 98 code
such as

append = (++)

That example can easily be fixed by adding a type signature, no?

append :: [a] - [a] - [a]
append = (++)

In ghci, at any rate, using mappend instead of (++),
the first is rejected, but the sceond works perfectly.

The nice thing about this is that the code _with_ the type
signature is perfectly legal Haskell 98, so the fix leaves
you with something that works with either reading of (++).

Do we have any other uses of ++ that would be hard to fix
by adding a type signature?


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Ketil Malde

You know, this might be the right time to start expanding our
vocabulary beyond seven bits.  Since we're likely to keep mappend
around as an alias for some time, people would have a grace period to
adjust. 

How about U+2295 (circle with plus inside it)?

Or, if we would like to stick to the 8-bit subset to keep those 8859-1
users happy, how about ¤ (funny circle over an x, U+00A4)

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Alexander Dunlap
On Tue, Jun 30, 2009 at 11:24 PM, Ketil Maldeke...@malde.org wrote:

 You know, this might be the right time to start expanding our
 vocabulary beyond seven bits.  Since we're likely to keep mappend
 around as an alias for some time, people would have a grace period to
 adjust.

 How about U+2295 (circle with plus inside it)?

 Or, if we would like to stick to the 8-bit subset to keep those 8859-1
 users happy, how about ¤ (funny circle over an x, U+00A4)

 -k
 --
 If I haven't seen further, it is by standing in the footprints of giants
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


The major disadvantage of that is that those symbols are not on my
keyboard and thus are more of a pain to type, especially on the Linux
console where compose key is not available...

Alex
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Jochem Berndsen
a...@spamcop.net wrote:
 G'day all.
 
 Quoting John Meacham j...@repetae.net:
 
 (+) seems to imply to me that the operator is non-associative. Something
 like () or (+) would be better.
 
 I tend to agree.  Moreover, and I realise this may be a losing battle,
 I want (++) to be the generic operator.

I totally agree. (+) is too asymmetric for my taste, like (=) and
(*) it suggests asymmetry between the arguments. (++) is symmetric and
suggests an associative operator to me.

-- 
Jochem Berndsen | joc...@functor.nl
GPG: 0xE6FABFAB
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread david48
On Wed, Jul 1, 2009 at 9:34 AM, Jochem Berndsenjoc...@functor.nl wrote:
 a...@spamcop.net wrote:

 I tend to agree.  Moreover, and I realise this may be a losing battle,
 I want (++) to be the generic operator.

 I totally agree.

So do I.

David.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Duncan Coutts
On Tue, 2009-06-30 at 18:31 -0700, John Meacham wrote:
 On Tue, Jun 30, 2009 at 08:02:48PM -0400, Daniel Peebles wrote:
  But we don't want to imply it's commutative either. Having something
  bidirectional like  or + feels more commutative than associative
  to me.

Of course in Text.PrettyPrint, both  and + are associative but not
commutative (with identity empty).

 Not really, think of '++', which doesn't commute but is visually
 symmetric, or Data.Sequence., or the common use of  to mean
 concatination in pretty printers. I think there is a fair amount of
 precedence for using '' actually. As it appears when it is used, it
 is also the natural mappend operator for the Monoid instance.

I agree, if we can't use ++ then  is the next best thing. As John says
it's already a monoid operator for Data.Sequence and Text.PrettyPrint.

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Jules Bean

Duncan Coutts wrote:

I agree, if we can't use ++ then  is the next best thing. As John says
it's already a monoid operator for Data.Sequence and Text.PrettyPrint.



I agree, if we can't use + and + then  is the next best thing.

;)

Jules
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread david48
On Wed, Jul 1, 2009 at 2:18 PM, Jules Beanju...@jellybean.co.uk wrote:

 Duncan Coutts wrote:

 I agree, if we can't use ++ then  is the next best thing. As John says
 it's already a monoid operator for Data.Sequence and Text.PrettyPrint.

 I agree, if we can't use + and + then  is the next best thing.

 ;)

I see what you did there :-P
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Brent Yorgey
On Wed, Jul 01, 2009 at 12:00:50AM -0400, a...@spamcop.net wrote:
 G'day all.

 On Tue, Jun 30, 2009 at 08:02:48PM -0400, Daniel Peebles wrote:

 But we don't want to imply it's commutative either. Having something
 bidirectional like  or + feels more commutative than associative
 to me.

 Quoting John Meacham j...@repetae.net:

 Not really, think of '++', which doesn't commute but is visually
 symmetric, or Data.Sequence., or the common use of  to mean
 concatination in pretty printers.

 Other good examples are  and ||.

..wha?  But those ARE commutative.  Unless you mean with respect to
strictness?

-Brent
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Edward Kmett
I'm rather fond of the () suggestion, but would be happy with anything
better than mappend! ;)

-Ed

On Wed, Jul 1, 2009 at 8:56 AM, Brent Yorgey byor...@seas.upenn.edu wrote:

 On Wed, Jul 01, 2009 at 12:00:50AM -0400, a...@spamcop.net wrote:
  G'day all.

 
  On Tue, Jun 30, 2009 at 08:02:48PM -0400, Daniel Peebles wrote:
 
  But we don't want to imply it's commutative either. Having something
  bidirectional like  or + feels more commutative than associative
  to me.
 
  Quoting John Meacham j...@repetae.net:
 
  Not really, think of '++', which doesn't commute but is visually
  symmetric, or Data.Sequence., or the common use of  to mean
  concatination in pretty printers.
 
  Other good examples are  and ||.

 ..wha?  But those ARE commutative.  Unless you mean with respect to
 strictness?

 -Brent
  ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Thomas Davie


On 1 Jul 2009, at 16:46, Edward Kmett wrote:

I'm rather fond of the () suggestion, but would be happy with  
anything better than mappend! ;)


I find it rather ugly, it has a lot of connotations of does not  
equals from other languages.  Personally I'm in favor of +, simply  
because it looks most like a circle with a plus in it.


Bob
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Jason Dagit
On Wed, Jul 1, 2009 at 7:53 AM, Thomas Davie tom.da...@gmail.com wrote:


 On 1 Jul 2009, at 16:46, Edward Kmett wrote:

  I'm rather fond of the () suggestion, but would be happy with anything
 better than mappend! ;)


 I find it rather ugly, it has a lot of connotations of does not equals
 from other languages.  Personally I'm in favor of +, simply because it
 looks most like a circle with a plus in it.


This is my favorite of the suggestions as well.  Then again, I don't mind
typing mappend.  Yay for bikesheds :)

Jason
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Martijn van Steenbergen

I suggest you all add your name and vote here:

   http://doodle.com/4yrfd7qaw5man3rm

Perhaps we'll find one of the options is clearly in favor.

Martijn.


Bryan O'Sullivan wrote:
I've thought for a while that it would be very nice indeed if the Monoid 
class had a more concise operator for infix appending than a `mappend` 
b. I wonder if other people are of a similar opinion, and if so, 
whether this is worth submitting a libraries@ proposal over.





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Robert Greayer
I'm sure there's some important historical reason... but why isn't ''
used in something more prominent than the fgl package?  I understand
why it's not used for bitwise AND in Data.Bits (I assume because the
corresponding bitwise '|' operator isn't available), but all the other
single-character operators** (in the ASCII range) are used in some
core library (if not the Prelude itself).  But not ''.  Why?  It
makes sense (to me) as a Monoid 'append'.

** - according to Hoogle

On Wed, Jul 1, 2009 at 10:46 AM, Edward Kmettekm...@gmail.com wrote:
 I'm rather fond of the () suggestion, but would be happy with anything
 better than mappend! ;)

 -Ed

 On Wed, Jul 1, 2009 at 8:56 AM, Brent Yorgey byor...@seas.upenn.edu wrote:

 On Wed, Jul 01, 2009 at 12:00:50AM -0400, a...@spamcop.net wrote:
  G'day all.

 
  On Tue, Jun 30, 2009 at 08:02:48PM -0400, Daniel Peebles wrote:
 
  But we don't want to imply it's commutative either. Having something
  bidirectional like  or + feels more commutative than associative
  to me.
 
  Quoting John Meacham j...@repetae.net:
 
  Not really, think of '++', which doesn't commute but is visually
  symmetric, or Data.Sequence., or the common use of  to mean
  concatination in pretty printers.
 
  Other good examples are  and ||.

 ..wha?  But those ARE commutative.  Unless you mean with respect to
 strictness?

 -Brent
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Ross Paterson
On Wed, Jul 01, 2009 at 04:53:05PM +0200, Thomas Davie wrote:

 On 1 Jul 2009, at 16:46, Edward Kmett wrote:

 I'm rather fond of the () suggestion, but would be happy with  
 anything better than mappend! ;)

 I find it rather ugly, it has a lot of connotations of does not equals 
 from other languages.

Forget Pascal: think of it as a diamond.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread David Leimbach
On Wed, Jul 1, 2009 at 5:18 AM, Jules Bean ju...@jellybean.co.uk wrote:

 Duncan Coutts wrote:

 I agree, if we can't use ++ then  is the next best thing. As John says
 it's already a monoid operator for Data.Sequence and Text.PrettyPrint.


 I agree, if we can't use + and + then  is the next best thing.

 ;)

 Jules

I like this thinking as well.  I kind of wish Haskell didn't overload
operators to begin with but oh well :-)

Just because the compiler can figure out what I mean because it has a great
type system, I might not be able to figure out what I mean a year from now
if I see ++ everywhere.

In some sense, I prefer misleading function names to overly overloaded
operators.

Dave



 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Bryan O'Sullivan
On Wed, Jul 1, 2009 at 3:38 AM, Duncan Coutts
duncan.cou...@worc.ox.ac.ukwrote:


 I agree, if we can't use ++ then  is the next best thing.


Okay, here's a tentative plan that will help to figure out the answer. I'll
build a fiddled base package that rewires the Monoid class to have (++) be
the binary operator, and mappend as a synonym for it. I'll import the Monoid
(++) into the Prelude. I'll see how much breaks. If that much builds
smoothly, I'll see how much of the rest of Hackage builds, both with and
without this custom base package. I'll follow up here with the results,
along with a suggestion of how acceptable I think the observed level of
breakage is.

Seem reasonable?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread David Leimbach
On Wed, Jul 1, 2009 at 10:55 AM, Bryan O'Sullivan b...@serpentine.comwrote:

 On Wed, Jul 1, 2009 at 3:38 AM, Duncan Coutts duncan.cou...@worc.ox.ac.uk
  wrote:


 I agree, if we can't use ++ then  is the next best thing.


 Okay, here's a tentative plan that will help to figure out the answer. I'll
 build a fiddled base package that rewires the Monoid class to have (++) be
 the binary operator, and mappend as a synonym for it. I'll import the Monoid
 (++) into the Prelude. I'll see how much breaks. If that much builds
 smoothly, I'll see how much of the rest of Hackage builds, both with and
 without this custom base package. I'll follow up here with the results,
 along with a suggestion of how acceptable I think the observed level of
 breakage is.

 Seem reasonable?


It's more reasonable than sitting around waxing philosophical on the
notation I suppose :-)




 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Ross Paterson
On Wed, Jul 01, 2009 at 10:55:39AM -0700, Bryan O'Sullivan wrote:
 Okay, here's a tentative plan that will help to figure out the answer. I'll
 build a fiddled base package that rewires the Monoid class to have (++) be the
 binary operator, and mappend as a synonym for it. I'll import the Monoid (++)
 into the Prelude. I'll see how much breaks. If that much builds smoothly, I'll
 see how much of the rest of Hackage builds, both with and without this custom
 base package. I'll follow up here with the results, along with a suggestion of
 how acceptable I think the observed level of breakage is.

Generalizing (++) will break some Haskell 98 code, e.g.

  append = (++)

I think that's a show-stopper.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Martijn van Steenbergen

Ross Paterson wrote:

Generalizing (++) will break some Haskell 98 code, e.g.

  append = (++)

I think that's a show-stopper.


Is the monomorphism restriction the only situation in which stuff breaks?

Martijn.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Thomas Schilling
2009/7/1 Martijn van Steenbergen mart...@van.steenbergen.nl:
 I suggest you all add your name and vote here:

   http://doodle.com/4yrfd7qaw5man3rm

 Perhaps we'll find one of the options is clearly in favor.

Doesn't doodle allow multiple choice tests?  Requiring to pick only
one is kind of skewing the results towards the possibly not backwards
compatible (++).


 Martijn.


 Bryan O'Sullivan wrote:

 I've thought for a while that it would be very nice indeed if the Monoid
 class had a more concise operator for infix appending than a `mappend` b.
 I wonder if other people are of a similar opinion, and if so, whether this
 is worth submitting a libraries@ proposal over.


 

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe




-- 
Push the envelope.  Watch it bend.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Thomas Schilling
2009/7/1 Ross Paterson r...@soi.city.ac.uk:
 I'm rather fond of the () suggestion, but would be happy with
 anything better than mappend! ;)

 I find it rather ugly, it has a lot of connotations of does not equals
 from other languages.

 Forget Pascal: think of it as a diamond.

Yep, it's definitely a diamond.
-- 
Push the envelope.  Watch it bend.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Thomas Schilling
2009/7/1 David Leimbach leim...@gmail.com
 I like this thinking as well.  I kind of wish Haskell didn't overload
 operators to begin with but oh well :-)
 Just because the compiler can figure out what I mean because it has a great
 type system, I might not be able to figure out what I mean a year from now
 if I see ++ everywhere.
 In some sense, I prefer misleading function names to overly overloaded
 operators.

Yep, had the same experience.  On the one hand, using monoids lets you
delay some design decisions for later and lets you reuse more library
code.  On the other hand, it sometimes makes it really hard to see
what the code is actually doing--especially if you use more than one
monoid.

For this reason on of the first advanced features I implemented in the
(yet unreleased) scion IDE library allows you to look up the
instantiated type of an identifier.  Unfortunately, jumping to the
definition (or documentation) of the monoid instance is a bit more
difficult.  Haddock should allow documentation on instance
declarations...


 Dave


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe





-- 
Push the envelope.  Watch it bend.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Martijn van Steenbergen

Thomas Schilling wrote:

Haddock should allow documentation on instance
declarations...


+1!

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Raynor Vliegendhart
On Tue, Jun 30, 2009 at 6:45 PM, Bryan O'Sullivanb...@serpentine.com wrote:
 I've thought for a while that it would be very nice indeed if the Monoid
 class had a more concise operator for infix appending than a `mappend` b.
 I wonder if other people are of a similar opinion, and if so, whether this
 is worth submitting a libraries@ proposal over.



We could use (Control.Category..) as an operator, but this would
require an additional wrapping layer if we wish to use the existing
Monoid instances:

 import Prelude hiding (id, (.))
 import Control.Category
 import Data.Monoid

 -- Category wrapper for existing Monoid instances
 newtype MonoidC m a b = MonoidC {unwrapMC :: m} deriving (Show)

 instance Monoid m = Category (MonoidC m) where
 id = MonoidC mempty
 MonoidC m . MonoidC n = MonoidC $ m `mappend` n

Furthermore, writing Category instances for monoids require dummy type
parameters:

 -- Example instance
 newtype SumC m a b = SumC {getSumC :: m} deriving (Show, Eq)

 instance Num a = Category (SumC a) where
 id = SumC (fromIntegral 0)
 SumC x . SumC y = SumC $ x + y

Another disadvantage of this approach is that we cannot have a default
monoid instance for lists (kind mismatch).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Geoffrey Marchant
Obviously `mappend` is good enough as it is.

Choosing (+) or () are just for prettifying code.

Generalizing (++) not only makes the code prettier, but also brings Monoid
into the Prelude.

You can either Do It Right(tm), or be conservative and try to maintain
backwards compatibility as much as possible.

I suspect most people in the community understand the trade-offs here, and
would agree on the proper solution. If that means rewriting the standard,
then so be it.


On Wed, Jul 1, 2009 at 12:26 PM, Ross Paterson r...@soi.city.ac.uk wrote:

 On Wed, Jul 01, 2009 at 10:55:39AM -0700, Bryan O'Sullivan wrote:
  Okay, here's a tentative plan that will help to figure out the answer.
 I'll
  build a fiddled base package that rewires the Monoid class to have (++)
 be the
  binary operator, and mappend as a synonym for it. I'll import the Monoid
 (++)
  into the Prelude. I'll see how much breaks. If that much builds smoothly,
 I'll
  see how much of the rest of Hackage builds, both with and without this
 custom
  base package. I'll follow up here with the results, along with a
 suggestion of
  how acceptable I think the observed level of breakage is.

 Generalizing (++) will break some Haskell 98 code, e.g.

  append = (++)

 I think that's a show-stopper.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread David Menendez
In Wed, Jul 1, 2009 at 3:38 PM, Thomas Schillingnomin...@googlemail.com wrote:
 2009/7/1 David Leimbach leim...@gmail.com
 Just because the compiler can figure out what I mean because it has a great
 type system, I might not be able to figure out what I mean a year from now
 if I see ++ everywhere.

 Yep, had the same experience.  On the one hand, using monoids lets you
 delay some design decisions for later and lets you reuse more library
 code.  On the other hand, it sometimes makes it really hard to see
 what the code is actually doing--especially if you use more than one
 monoid.

 For this reason on of the first advanced features I implemented in the
 (yet unreleased) scion IDE library allows you to look up the
 instantiated type of an identifier.  Unfortunately, jumping to the
 definition (or documentation) of the monoid instance is a bit more
 difficult.  Haddock should allow documentation on instance
 declarations...

I disagree. The solution is to not create instances when it isn't
obvious what the instance does. That's why we have Sum and Prod in
Data.Monoid instead of declaring instances directly for Int.

With Monoid, I'd go further and say that you should not use mempty and
mappend unless you are writing polymorphic code. If you are writing to
a specific monoid instance, you should use a specific function.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread Bryan O'Sullivan
I've thought for a while that it would be very nice indeed if the Monoid
class had a more concise operator for infix appending than a `mappend` b.
I wonder if other people are of a similar opinion, and if so, whether this
is worth submitting a libraries@ proposal over.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread Bryan O'Sullivan
On Tue, Jun 30, 2009 at 9:50 AM, David Leimbach leim...@gmail.com wrote:

 I actually worry that this will make people think, more incorrectly, that
 Monoids are about appending stuff only.


I think that adding a graphical operator as a synonym for mappend would
actually help to address that, since the magic word append would no longer
be nearly as common in source code, and that textual name certainly is
(unhelpfully) suggestive of a specific semantics.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread Edward Kmett
I love the idea, but its tricky to come up with one that is good that won't
break a lot of user code that imports Data.Monoid unqualified.
-Edward Kmett


On Tue, Jun 30, 2009 at 12:45 PM, Bryan O'Sullivan b...@serpentine.comwrote:

 I've thought for a while that it would be very nice indeed if the Monoid
 class had a more concise operator for infix appending than a `mappend` b.
 I wonder if other people are of a similar opinion, and if so, whether this
 is worth submitting a libraries@ proposal over.

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread Josh Lee
Isn't ++ itself the perfect Monoid operator? Lambdabot seems to think so.

On Tue, Jun 30, 2009 at 13:04, Edward Kmettekm...@gmail.com wrote:
 I love the idea, but its tricky to come up with one that is good that won't
 break a lot of user code that imports Data.Monoid unqualified.
 -Edward Kmett

 On Tue, Jun 30, 2009 at 12:45 PM, Bryan O'Sullivan b...@serpentine.com
 wrote:

 I've thought for a while that it would be very nice indeed if the Monoid
 class had a more concise operator for infix appending than a `mappend` b.
 I wonder if other people are of a similar opinion, and if so, whether this
 is worth submitting a libraries@ proposal over.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread David Leimbach
On Tue, Jun 30, 2009 at 10:04 AM, Bryan O'Sullivan b...@serpentine.comwrote:

 On Tue, Jun 30, 2009 at 9:50 AM, David Leimbach leim...@gmail.com wrote:

 I actually worry that this will make people think, more incorrectly, that
 Monoids are about appending stuff only.


 I think that adding a graphical operator as a synonym for mappend would
 actually help to address that, since the magic word append would no longer
 be nearly as common in source code, and that textual name certainly is
 (unhelpfully) suggestive of a specific semantics.


Yeah the textual name doesn't help one bit.  Much like return confuses
folks in Monads.  However, I think most people learn Haskell in stages where
++ is introduced as an append operation *before* they even
come across the term Monoid.  I feel that though this may have a
lesser degenerative impact on the newbie's ability to learn Monoids,
that it still contributes to the confusion a bit.

Then again, anyone who's had to deal with overloaded operators in any
language should learn never to assume anything about overloaded
operators...


Dave
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread Daniel Peebles
Except that in this case the operator is associative :P

On Tue, Jun 30, 2009 at 2:42 PM, David Leimbachleim...@gmail.com wrote:


 On Tue, Jun 30, 2009 at 10:04 AM, Bryan O'Sullivan b...@serpentine.com
 wrote:

 On Tue, Jun 30, 2009 at 9:50 AM, David Leimbach leim...@gmail.com wrote:

 I actually worry that this will make people think, more incorrectly, that
 Monoids are about appending stuff only.

 I think that adding a graphical operator as a synonym for mappend would
 actually help to address that, since the magic word append would no longer
 be nearly as common in source code, and that textual name certainly is
 (unhelpfully) suggestive of a specific semantics.

 Yeah the textual name doesn't help one bit.  Much like return confuses
 folks in Monads.  However, I think most people learn Haskell in stages where
 ++ is introduced as an append operation *before* they even
 come across the term Monoid.  I feel that though this may have a lesser degenerative impact on the newbie's ability to learn Monoids, that it still contributes to the confusion a bit.
 Then again, anyone who's had to deal with overloaded operators in any language should learn never to assume anything about overloaded operators...

 Dave
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread Brent Yorgey
On Tue, Jun 30, 2009 at 09:45:45AM -0700, Bryan O'Sullivan wrote:
 I've thought for a while that it would be very nice indeed if the Monoid
 class had a more concise operator for infix appending than a `mappend` b.
 I wonder if other people are of a similar opinion, and if so, whether this
 is worth submitting a libraries@ proposal over.

+1.

IIRC Jules Bean has proposed using (+) for this purpose, which I
like.  It has the advantages of (a) not clashing with any other
(common) operators, (b) making more obvious the fact that mappend is
not necessarily commutative, and (c) providing the obvious (+) for
'flip mappend' which is sometimes useful.

-Brent
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread David Leimbach
On Tue, Jun 30, 2009 at 11:54 AM, Brent Yorgey byor...@seas.upenn.eduwrote:

 On Tue, Jun 30, 2009 at 09:45:45AM -0700, Bryan O'Sullivan wrote:
  I've thought for a while that it would be very nice indeed if the Monoid
  class had a more concise operator for infix appending than a `mappend`
 b.
  I wonder if other people are of a similar opinion, and if so, whether
 this
  is worth submitting a libraries@ proposal over.

 +1.

 IIRC Jules Bean has proposed using (+) for this purpose, which I
 like.  It has the advantages of (a) not clashing with any other
 (common) operators, (b) making more obvious the fact that mappend is
 not necessarily commutative, and (c) providing the obvious (+) for
 'flip mappend' which is sometimes useful.


I actually think this proposal is pretty excellent.




 -Brent
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread Daniel Fischer
Am Dienstag 30 Juni 2009 20:56:10 schrieb David Leimbach:
 On Tue, Jun 30, 2009 at 11:54 AM, Brent Yorgey byor...@seas.upenn.eduwrote:
  On Tue, Jun 30, 2009 at 09:45:45AM -0700, Bryan O'Sullivan wrote:
   I've thought for a while that it would be very nice indeed if the
   Monoid class had a more concise operator for infix appending than a
   `mappend`
 
  b.
 
   I wonder if other people are of a similar opinion, and if so, whether
 
  this
 
   is worth submitting a libraries@ proposal over.
 
  +1.
 
  IIRC Jules Bean has proposed using (+) for this purpose, which I
  like.  It has the advantages of (a) not clashing with any other
  (common) operators, (b) making more obvious the fact that mappend is
  not necessarily commutative, and (c) providing the obvious (+) for
  'flip mappend' which is sometimes useful.

 I actually think this proposal is pretty excellent.

I actually think your assessment of the proposal is correct.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread Thomas Davie


On 30 Jun 2009, at 22:19, Daniel Fischer wrote:


Am Dienstag 30 Juni 2009 20:56:10 schrieb David Leimbach:
On Tue, Jun 30, 2009 at 11:54 AM, Brent Yorgey byor...@seas.upenn.edu 
wrote:

On Tue, Jun 30, 2009 at 09:45:45AM -0700, Bryan O'Sullivan wrote:

I've thought for a while that it would be very nice indeed if the
Monoid class had a more concise operator for infix appending than  
a

`mappend`


b.

I wonder if other people are of a similar opinion, and if so,  
whether


this


is worth submitting a libraries@ proposal over.


+1.

IIRC Jules Bean has proposed using (+) for this purpose, which I
like.  It has the advantages of (a) not clashing with any other
(common) operators, (b) making more obvious the fact that mappend is
not necessarily commutative, and (c) providing the obvious (+) for
'flip mappend' which is sometimes useful.


I actually think this proposal is pretty excellent.


I actually think your assessment of the proposal is correct.


I excellently think your proposal is a correct assessment.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread Bryan O'Sullivan
On Tue, Jun 30, 2009 at 1:33 PM, Thomas Davie tom.da...@gmail.com wrote:

 I excellently think your proposal is a correct assessment.


Well then, here's the library enhancement ticket:

http://hackage.haskell.org/trac/ghc/ticket/3339
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread John Meacham
On Tue, Jun 30, 2009 at 02:54:38PM -0400, Brent Yorgey wrote:
 On Tue, Jun 30, 2009 at 09:45:45AM -0700, Bryan O'Sullivan wrote:
  I've thought for a while that it would be very nice indeed if the Monoid
  class had a more concise operator for infix appending than a `mappend` b.
  I wonder if other people are of a similar opinion, and if so, whether this
  is worth submitting a libraries@ proposal over.
 
 +1.
 
 IIRC Jules Bean has proposed using (+) for this purpose, which I
 like.  It has the advantages of (a) not clashing with any other
 (common) operators, (b) making more obvious the fact that mappend is
 not necessarily commutative, and (c) providing the obvious (+) for
 'flip mappend' which is sometimes useful.

(+) seems to imply to me that the operator is non-associative. Something
like () or (+) would be better.


John

-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread Dougal Stanton
On Tue, Jun 30, 2009 at 11:39 PM, John Meachamj...@repetae.net wrote:


 (+) seems to imply to me that the operator is non-associative. Something
 like () or (+) would be better.


It's too similar to the applicative (*), and implies all sorts of
things like different types of the two arguments and so on.


D

-- 
Dougal Stanton
dou...@dougalstanton.net // http://www.dougalstanton.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread Bryan O'Sullivan
On Tue, Jun 30, 2009 at 3:50 PM, Dougal Stanton ith...@gmail.com wrote:

  (+) seems to imply to me that the operator is non-associative. Something
  like () or (+) would be better.

 It's too similar to the applicative (*), and implies all sorts of
 things like different types of the two arguments and so on.


If you have comments like the above, please add them to the Trac ticket.
Speaking for myself, I'll be happiest to give weight to comments that
suggest alternative operators.

Thanks,
Bryan.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread Ross Paterson
On Tue, Jun 30, 2009 at 03:39:39PM -0700, John Meacham wrote:
 (+) seems to imply to me that the operator is non-associative.

It does seem to imply some asymmetry between the arguments.

 Something like () or (+) would be better.

(+) is used in Control.Arrow.

() is used in Data.Sequence, but as the mappend for Seq a; it could
be stolen and generalized.  (So could empty, for that matter.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread Bryan O'Sullivan
On Tue, Jun 30, 2009 at 3:56 PM, Ross Paterson r...@soi.city.ac.uk wrote:

 On Tue, Jun 30, 2009 at 03:39:39PM -0700, John Meacham wrote:
  (+) seems to imply to me that the operator is non-associative.

 It does seem to imply some asymmetry between the arguments.


Well, the canonical instance of Monoid is to mappend over lists, where it
doesn't commute, so I think that the pointiness of the operator makes a
reasonable kind of sense.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread Tony Morris


David Leimbach wrote:


 On Tue, Jun 30, 2009 at 11:54 AM, Brent Yorgey byor...@seas.upenn.edu
 mailto:byor...@seas.upenn.edu wrote:

 On Tue, Jun 30, 2009 at 09:45:45AM -0700, Bryan O'Sullivan wrote:
  I've thought for a while that it would be very nice indeed if
 the Monoid
  class had a more concise operator for infix appending than a
 `mappend` b.
  I wonder if other people are of a similar opinion, and if so,
 whether this
  is worth submitting a libraries@ proposal over.

 +1.

 IIRC Jules Bean has proposed using (+) for this purpose, which I
 like.  It has the advantages of (a) not clashing with any other
 (common) operators, (b) making more obvious the fact that mappend is
 not necessarily commutative, and (c) providing the obvious (+) for
 'flip mappend' which is sometimes useful.


 I actually think this proposal is pretty excellent.  
I happen to agree.

-- 
Tony Morris
http://tmorris.net/


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread Daniel Peebles
But we don't want to imply it's commutative either. Having something
bidirectional like  or + feels more commutative than associative
to me.

On Tue, Jun 30, 2009 at 6:39 PM, John Meachamj...@repetae.net wrote:
 On Tue, Jun 30, 2009 at 02:54:38PM -0400, Brent Yorgey wrote:
 On Tue, Jun 30, 2009 at 09:45:45AM -0700, Bryan O'Sullivan wrote:
  I've thought for a while that it would be very nice indeed if the Monoid
  class had a more concise operator for infix appending than a `mappend` b.
  I wonder if other people are of a similar opinion, and if so, whether this
  is worth submitting a libraries@ proposal over.

 +1.

 IIRC Jules Bean has proposed using (+) for this purpose, which I
 like.  It has the advantages of (a) not clashing with any other
 (common) operators, (b) making more obvious the fact that mappend is
 not necessarily commutative, and (c) providing the obvious (+) for
 'flip mappend' which is sometimes useful.

 (+) seems to imply to me that the operator is non-associative. Something
 like () or (+) would be better.


        John

 --
 John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread John Meacham
On Tue, Jun 30, 2009 at 08:02:48PM -0400, Daniel Peebles wrote:
 But we don't want to imply it's commutative either. Having something
 bidirectional like  or + feels more commutative than associative
 to me.

Not really, think of '++', which doesn't commute but is visually
symmetric, or Data.Sequence., or the common use of  to mean
concatination in pretty printers. I think there is a fair amount of
precedence for using '' actually. As it appears when it is used, it
is also the natural mappend operator for the Monoid instance.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread Lanny Ripple
Ok.  When nobody can agree on a graphical operator can it be
shortened to mop and munit?  (Personally I'm for (++).  (Yeah, I
know.))

  -ljr

Daniel Peebles wrote:
 But we don't want to imply it's commutative either. Having something
 bidirectional like  or + feels more commutative than associative
 to me.
 
 On Tue, Jun 30, 2009 at 6:39 PM, John Meachamj...@repetae.net wrote:
 On Tue, Jun 30, 2009 at 02:54:38PM -0400, Brent Yorgey wrote:
 On Tue, Jun 30, 2009 at 09:45:45AM -0700, Bryan O'Sullivan wrote:
 I've thought for a while that it would be very nice indeed if the Monoid
 class had a more concise operator for infix appending than a `mappend` b.
 I wonder if other people are of a similar opinion, and if so, whether this
 is worth submitting a libraries@ proposal over.
 +1.

 IIRC Jules Bean has proposed using (+) for this purpose, which I
 like. Â It has the advantages of (a) not clashing with any other
 (common) operators, (b) making more obvious the fact that mappend is
 not necessarily commutative, and (c) providing the obvious (+) for
 'flip mappend' which is sometimes useful.
 (+) seems to imply to me that the operator is non-associative. Something
 like () or (+) would be better.


 Â  Â  Â  Â John

 --
 John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread ajb

G'day all.

Quoting John Meacham j...@repetae.net:


(+) seems to imply to me that the operator is non-associative. Something
like () or (+) would be better.


I tend to agree.  Moreover, and I realise this may be a losing battle,
I want (++) to be the generic operator.

I understand the argument.  I even agreed with it at the time.  In 1998,
academic use of Haskell (both for research and education) was the most
important imperative.

Today, Haskell is officially cool, so the good names and operators should
not be stolen by operations that are distinguished only by being less
useful (e.g. by working on lists alone).

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread ajb

G'day all.

On Tue, Jun 30, 2009 at 08:02:48PM -0400, Daniel Peebles wrote:


But we don't want to imply it's commutative either. Having something
bidirectional like  or + feels more commutative than associative
to me.


Quoting John Meacham j...@repetae.net:


Not really, think of '++', which doesn't commute but is visually
symmetric, or Data.Sequence., or the common use of  to mean
concatination in pretty printers.


Other good examples are  and ||.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe