Generalizing (++) for monoids instead of using (<>)

After asking this question: http://stackoverflow.com/questions/9963050/standard-way-of-joining-two-data-... I found out that the new infix operator for `mappend` is (<>). I'm wondering why ghc 7.4 didn't generalize (++) to work on monoids instead. To me, (++) is much more clear. (<>) means "not equal to" for me. Can anyone shed light on this decision? Adit -- adit.io

There are many reasons, but some of the more cited ones are that (<>) will
break less code than (++) would, since (++) is ubiquitous and (<>) is most
used in some pretty printers. Yes, mappend's type can be refined to that of
the current list (++), but the increased polymorphism still has the
potential to break existing code by making it harder to resolve instances.
As for (<>) meaning not equal to, do you also have a problem with Monad's
(>>) meaning a right bitwise shift, or the mutationey form of it, (>>=)? :)
I don't think anyone in Haskell has ever used (<>) to mean (/=), so the
fact that there exist a couple of languages out there that do use it that
way shouldn't affect our decision.
Dan
On Sun, Apr 1, 2012 at 4:58 PM, aditya bhargava
After asking this question:
http://stackoverflow.com/questions/9963050/standard-way-of-joining-two-data-...
I found out that the new infix operator for `mappend` is (<>). I'm wondering why ghc 7.4 didn't generalize (++) to work on monoids instead. To me, (++) is much more clear. (<>) means "not equal to" for me. Can anyone shed light on this decision?
Adit
-- adit.io
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Plus one might argue that using <> to mean different is a bad choice, as it
graphically means "strictly inferior or strictly superior" which implies
comparability, whereas equality and comparison are two different things.
(e.g. Eq and Ord are two distinct classes in Haskell).
Le 1 avril 2012 23:06, Daniel Peebles
There are many reasons, but some of the more cited ones are that (<>) will break less code than (++) would, since (++) is ubiquitous and (<>) is most used in some pretty printers. Yes, mappend's type can be refined to that of the current list (++), but the increased polymorphism still has the potential to break existing code by making it harder to resolve instances.
As for (<>) meaning not equal to, do you also have a problem with Monad's (>>) meaning a right bitwise shift, or the mutationey form of it, (>>=)? :) I don't think anyone in Haskell has ever used (<>) to mean (/=), so the fact that there exist a couple of languages out there that do use it that way shouldn't affect our decision.
Dan
On Sun, Apr 1, 2012 at 4:58 PM, aditya bhargava
wrote: After asking this question:
http://stackoverflow.com/questions/9963050/standard-way-of-joining-two-data-...
I found out that the new infix operator for `mappend` is (<>). I'm wondering why ghc 7.4 didn't generalize (++) to work on monoids instead. To me, (++) is much more clear. (<>) means "not equal to" for me. Can anyone shed light on this decision?
Adit
-- adit.io
_______________________________________________ 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

It is somewhat idiomatic to read it as TeX's \diamond symbol. Various
papers set with Lhs2TeX use it for general composition operator
(sometimes concat / mappend).
On 2 April 2012 10:05, Yves Parès
Plus one might argue that using <> to mean different is a bad choice, as it graphically means "strictly inferior or strictly superior" which implies comparability, whereas equality and comparison are two different things. (e.g. Eq and Ord are two distinct classes in Haskell).

On Sun, Apr 1, 2012 at 1:58 PM, aditya bhargava
After asking this question: http://stackoverflow.com/questions/9963050/standard-way-of-joining-two-data-...
I found out that the new infix operator for `mappend` is (<>). I'm wondering why ghc 7.4 didn't generalize (++) to work on monoids instead.
Such decisions should really be made by the Haskell Prime committee (vs GHC HQ). In Haskell there is a continuing tension between making things polymorphic and to keep the prelude functions monomorphic so they generate simple error messages (among other arguments). At the point, the additional argument of any new definition of "Haskell" remaining backwards compatible also holds weight and this slows the rate-of-change. This is not a new issue, there are a number of functions that could be defined more generally (common example: map/fmap). The problem making such changes is a matter of consensus and will to see things though. Cheers, Thomas

Thinking aloud, I dónt know if the transition to more abstract type
signatures can be aleviated using language directives.
Someting like:
Restrict (++) String -> String -> String
that locally would restrict the type within the module.
Althoug it does not avoid breaking the old code, It permits an easy fix.
Moreover, This may have applications in other contexts, for example
teaching, because the wild abstraction of the error messages is the
most difficult barrier in haskell learning.
Cheers
Alberto
2012/4/1 Thomas DuBuisson
On Sun, Apr 1, 2012 at 1:58 PM, aditya bhargava
wrote: After asking this question: http://stackoverflow.com/questions/9963050/standard-way-of-joining-two-data-...
I found out that the new infix operator for `mappend` is (<>). I'm wondering why ghc 7.4 didn't generalize (++) to work on monoids instead.
Such decisions should really be made by the Haskell Prime committee (vs GHC HQ). In Haskell there is a continuing tension between making things polymorphic and to keep the prelude functions monomorphic so they generate simple error messages (among other arguments). At the point, the additional argument of any new definition of "Haskell" remaining backwards compatible also holds weight and this slows the rate-of-change.
This is not a new issue, there are a number of functions that could be defined more generally (common example: map/fmap). The problem making such changes is a matter of consensus and will to see things though.
Cheers, Thomas
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 4 May 2012, at 10:02, Alberto G. Corona wrote:
Restrict (++) String -> String -> String
that locally would restrict the type within the module.
import qualified Prelude import Prelude hiding ((++)) (++) :: String -> String -> String (++) = Prelude.(++)

Fine ;)
So the transition should not be so problematic. An OldPrelude.hs may
be created easily with this.
Once again, thinking aloud.
2012/5/4 Malcolm Wallace
On 4 May 2012, at 10:02, Alberto G. Corona wrote:
Restrict (++) String -> String -> String
that locally would restrict the type within the module.
import qualified Prelude import Prelude hiding ((++))
(++) :: String -> String -> String (++) = Prelude.(++)
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

See the relevant trac ticket [1] and the linked mailing list thread.
Erik
[1] http://hackage.haskell.org/trac/ghc/ticket/3339
On Sun, Apr 1, 2012 at 22:58, aditya bhargava
After asking this question: http://stackoverflow.com/questions/9963050/standard-way-of-joining-two-data-...
I found out that the new infix operator for `mappend` is (<>). I'm wondering why ghc 7.4 didn't generalize (++) to work on monoids instead. To me, (++) is much more clear. (<>) means "not equal to" for me. Can anyone shed light on this decision?
Adit
-- adit.io
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

In the context of string-like types ++ seems quite sensible because the Monoid instances concat the strings. However, not all Monoid instances imply concatenation. A Monoid instance might provide choice. For example, we could define a parser,
module Main where
import Data.Monoid
newtype Parser a = Parser { parse :: [Char] -> Maybe (a, [Char]) }
and create a Monoid instance like:
instance Monoid (Parser a) where mempty = Parser $ const Nothing (Parser p1) `mappend` (Parser p2) = Parser $ \str -> case p1 str of (Just (a, cs)) -> Just (a, cs) Nothing -> p2 str
And then create some simply parser combinators:
satisfy :: (Char -> Bool) -> Parser Char satisfy p = Parser $ \str -> case str of (c:cs) | p c -> Just (c, cs) _ -> Nothing
char :: Char -> Parser Char char c = satisfy (== c)
Now, imagine we want to write a parser that parses 'a' or 'b':
ab :: Parser Char ab = char 'a' <> char 'b'
That will parse 'a' or 'b'. But what we had used ++ for mappend instead:
ab :: Parser Char ab = char 'a' ++ char 'b'
You are much more likely to assume that parses 'a' followed by 'b'.
(Even though that doesn't really make sense when you consider the
return type -- you would expect, Parser String, if that was the case).
For the same reason, many people feel that mappend was a bad choice of
name in the first place, (and that (++) = mappend just makes a bad
thing worse).
Or maybe I am totally confused and am thinking about something else..
Anyway, the subject was certainly beaten to death quite a bit over the
last couple years. I think another reason why <> was chosen is that a
number of libraries were already defining (<>) = mappend locally? (not
positive about that).
- jeremy
On Sun, Apr 1, 2012 at 3:58 PM, aditya bhargava
After asking this question: http://stackoverflow.com/questions/9963050/standard-way-of-joining-two-data-...
I found out that the new infix operator for `mappend` is (<>). I'm wondering why ghc 7.4 didn't generalize (++) to work on monoids instead. To me, (++) is much more clear. (<>) means "not equal to" for me. Can anyone shed light on this decision?
Adit
-- adit.io
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (9)
-
aditya bhargava
-
Alberto G. Corona
-
Daniel Peebles
-
Erik Hesselink
-
Jeremy Shaw
-
Malcolm Wallace
-
Stephen Tetley
-
Thomas DuBuisson
-
Yves Parès