[Haskell-cafe] monoid pair of monoids?

Sean Leather leather at cs.uu.nl
Fri Dec 21 10:35:54 CET 2012


On Fri, Dec 21, 2012 at 9:27 AM, Christopher Howard wrote:

> Thank you for your help. An additional question, if I might: For the
> sake of elegance and simplicity, I modified the class and instances to
> avoid the "tuple" aspect:
>
> data Socket2 a b = Socket2 a b
> instance (Monoid a, Monoid b) => Monoid (Socket2 a b) where
>
> Of course, I thought it would be likely I would want other classes and
> instances with additional numbers of types:
>
> data Socket3 a b c = Socket3 a b c
> instance (Monoid a, Monoid b, Monoid c) => Monoid (Socket3 a b c) where
>
> data Socket4 a b c d = Socket4 a b c d
> instance (Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (Socket4 a b
>
> data Socket 5 a b c d e... et cetera
> --------
>
> Seeing as the pattern here is so rigid and obvious, I was wondering: is
> it possible to abstract this even more? So I could, for instance, just
> specify that I want a Socket with 8 types, and poof, it would be there?
> Or is this as meta as we get? (I.e., without going to something like
> Template Haskell.)
>

This perhaps isn't the answer you were looking for, but just in case you
weren't aware, there are already Monoid instances for tuples up to 5. You
can see this at:

http://hackage.haskell.org/packages/archive/base/latest/doc/html/Data-Monoid.html#g:1

Another possibility is a generic monoid class (using generic-deriving):

{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}

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

import GHC.Generics

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

class GMonoid' f where
  gempty'  :: f x
  gappend' :: f x -> f x -> f x

instance GMonoid' U1 where
  gempty' = U1
  gappend' U1 U1 = U1

instance GMonoid a => GMonoid' (K1 i a) where
  gempty' = K1 gempty
  gappend' (K1 x) (K1 y) = K1 (x `gappend` y)

instance GMonoid' f => GMonoid' (M1 i c f) where
  gempty' = M1 gempty'
  gappend' (M1 x) (M1 y) = M1 (x `gappend'` y)

instance (GMonoid' f, GMonoid' h) => GMonoid' (f :*: h) where
  gempty' = gempty' :*: gempty'
  gappend' (x1 :*: y1) (x2 :*: y2) = gappend' x1 x2 :*: gappend' y1 y2

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

class GMonoid a where
  gempty  :: a
  gappend :: a -> a -> a

  default gempty :: (Generic a, GMonoid' (Rep a)) => a
  gempty = to gempty'

  default gappend :: (Generic a, GMonoid' (Rep a)) => a -> a -> a
  gappend x y = to (gappend' (from x) (from y))

instance (GMonoid b, GMonoid c) => GMonoid (b,c)
-- ...

Regards,
Sean
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20121221/2893a08e/attachment.htm>


More information about the Haskell-Cafe mailing list