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

Raynor Vliegendhart shinnonoir at gmail.com
Wed Jul 1 16:17:13 EDT 2009


On Tue, Jun 30, 2009 at 6:45 PM, Bryan O'Sullivan<bos at 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).


More information about the Haskell-Cafe mailing list