[Haskell-cafe] monoid pair of monoids?
Steffen Schuldenzucker
sschuldenzucker at uni-bonn.de
Fri Dec 21 10:14:53 CET 2012
Hi Christopher,
On 12/21/2012 09:27 AM, Christopher Howard wrote:
> [...]
> Of course, I thought it would be likely I would want other classes and
> instances with additional numbers of types:
>
> code:
> --------
> data Socket3 a b c = Socket3 a b c
> deriving (Show)
>
> instance (Monoid a, Monoid b, Monoid c) => Monoid (Socket3 a b c) where
> mempty = Socket3 mempty mempty mempty
> Socket3 a b c `mappend` Socket3 w x y =
> Socket3 (a `mappend` w) (b `mappend` x) (c `mappend` y)
>
> data Socket4 a b c d = Socket4 a b c d
> deriving (Show)
>
> instance (Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (Socket4 a b
> c d) where
> mempty = Socket4 mempty mempty mempty mempty
> Socket4 a b c d `mappend` Socket4 w x y z =
> Socket4 (a `mappend` w) (b `mappend` x) (c `mappend` y) (d
> `mappend` z)
>
> 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.)
If you are willing to encode your types as "generalized tuples", i.e.
heterogeneous lists, you can do that:
import Data.Monoid
data Nil = Nil
data Cons a bs = Cons a bs
-- type Socket 3 a b c = Cons a (Cons b (Cons c Nil))
-- (feel free to use operator syntax to prettify it)
instance Monoid Nil where
mempty = Nil
mappend Nil Nil = Nil
instance (Monoid a, Monoid bs) => Monoid (Cons a bs) where
mempty = Cons mempty mempty
mappend (Cons x1 ys1) (Cons x2 ys2) = Cons (mappend x1 x2) (mappend
ys1 ys2)
-- Steffen
More information about the Haskell-Cafe
mailing list