
In my current pondering of the compose-able objects them, I was thinking it would be useful to have the follow abstractions: Monoids, which were themselves tuples of Monoids. The idea was something like so: code: -------- import Data.Monoid instance Monoid (Socket2 a b) where mempty = Socket2 (mempty, mempty) Socket2 (a, b) `mappend` Socket2 (w, x) = Socket2 (a `mappend` w, b `mappend` x) data Socket2 a b = Socket2 (a, b) -------- However, this does not compile because of errors like so: code: -------- Sockets.hs:9:21: No instance for (Monoid a) arising from a use of `mempty' In the expression: mempty In the first argument of `Socket2', namely `(mempty, mempty)' In the expression: Socket2 (mempty, mempty) -------- This makes sense, but I haven't figured out a way to rewrite this to make it work. One approach I tried was to encode Monoid constraints into the data declaration (which I heard was a bad idea) but this didn't work, even using forall. Also I tried to encode it into the instance declaration, but the compiler kept complaining about errant or illegal syntax. -- frigidcode.com

Is "Socket2 a b" any different from the pair (a,b)? Assuming Socket2 looks roughly like the following:
import Data.Monoid data Socket2 a b = Socket2 (a,b)
Then if both a and b are instances of Monoid we can make Socket2 a b into an instance of Monoid the same way we make (a,b) into a Monoid.
instance (Monoid a, Monoid b) => Monoid (Socket a b) where mempty = Socket2 (mempty, mempty) Socket2 (a, b) `mappend` Socket2 (w, x) = Socket2 (a `mappend` w, b `mappend` x)
You were only missing the restriction that both types a and b must be instances of Monoid in order to make Socket a b into an instance of Monoid. Dan Feltey On Thu, Dec 20, 2012 at 8:40 PM, Christopher Howard < christopher.howard@frigidcode.com> wrote:
In my current pondering of the compose-able objects them, I was thinking it would be useful to have the follow abstractions: Monoids, which were themselves tuples of Monoids. The idea was something like so:
code: -------- import Data.Monoid
instance Monoid (Socket2 a b) where
mempty = Socket2 (mempty, mempty)
Socket2 (a, b) `mappend` Socket2 (w, x) = Socket2 (a `mappend` w, b `mappend` x)
data Socket2 a b = Socket2 (a, b) --------
However, this does not compile because of errors like so:
code: -------- Sockets.hs:9:21: No instance for (Monoid a) arising from a use of `mempty' In the expression: mempty In the first argument of `Socket2', namely `(mempty, mempty)' In the expression: Socket2 (mempty, mempty) --------
This makes sense, but I haven't figured out a way to rewrite this to make it work. One approach I tried was to encode Monoid constraints into the data declaration (which I heard was a bad idea) but this didn't work, even using forall. Also I tried to encode it into the instance declaration, but the compiler kept complaining about errant or illegal syntax.
-- frigidcode.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 12/20/2012 08:54 PM, Daniel Feltey wrote:
You were only missing the restriction that both types a and b must be instances of Monoid in order to make Socket a b into an instance of Monoid.
Dan Feltey
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: code: -------- data Socket2 a b = Socket2 a b deriving (Show) instance (Monoid a, Monoid b) => Monoid (Socket2 a b) where mempty = Socket2 mempty mempty Socket2 a b `mappend` Socket2 w x = Socket2 (a `mappend` w) (b `mappend` x) -------- 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.) -- frigidcode.com

Hi. Christopher Howard писал 21.12.2012 14:27:
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.)
Something like data a ::: b = a ::: b infixl 5 ::: instance (Monoid a, Monoid b) => Monoid (a ::: b) where ... So, Monoid instance for, say, (a ::: b ::: c) == ((a ::: b) ::: c) will (should) be inferred automatically. WBR, Ilya Portnov

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

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... 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
participants (5)
-
Christopher Howard
-
Daniel Feltey
-
Ilya Portnov
-
Sean Leather
-
Steffen Schuldenzucker