On 04/01/2012 19:08, Johan Tibell wrote:
Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : ghc-7.4

http://hackage.haskell.org/trac/ghc/changeset/556d174a555b993176e6766017b984e7a096a327

---------------------------------------------------------------

commit 556d174a555b993176e6766017b984e7a096a327
Author: Johan Tibell<[email protected]>
Date:   Tue Aug 16 11:40:34 2011 +0200

     Add<>  as an alias for mappend

Just a note for the future: our normal workflow is to push to master first and then tell Ian that a merge to the branch is needed (I know this isn't the workflow you'd recommend, but it's what we're using).

Ian: could you merge this and the other patches up to master please?

Cheers,
        Simon



---------------------------------------------------------------

  Data/Monoid.hs |    8 ++++++++
  1 files changed, 8 insertions(+), 0 deletions(-)

diff --git a/Data/Monoid.hs b/Data/Monoid.hs
index 228e254..bb3c4ec 100644
--- a/Data/Monoid.hs
+++ b/Data/Monoid.hs
@@ -20,6 +20,7 @@
  module Data.Monoid (
          -- * Monoid typeclass
          Monoid(..),
+        (<>),
          Dual(..),
          Endo(..),
          -- * Bool wrappers
@@ -88,6 +89,13 @@ class Monoid a where

          mconcat = foldr mappend mempty

+infixr 6<>
+
+-- | An infix synonym for 'mappend'.
+(<>) :: Monoid m =>  m ->  m ->  m
+(<>) = mappend
+{-# INLINE (<>) #-}
+
  -- Monoid instances.

  instance Monoid [a] where



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries


_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to