
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