Polyvariadic functions operating with a monoid

Kevin Jardine wrote:
instead of passing around lists of values with these related types, I created a polyvariadic function polyToString... I finally figured out how to do this, but it was a bit harder to figure this out than I expected, and I was wondering if it might be possible to create a small utility library to help other developers do this.
It seems to me that in the general case, we would be dealing with a Monoid rather than a list of strings. We could have a toMonoid function and then return
polyToMonoid value1 value2 ... valueN =
(toMonoid value1) `mappend` (toMonoid value2) 'mappend' ... (toMonoid valueN)
So I tried writing the following code but GHC said it had undecidable instances. Generally speaking, we should not be afraid of undecidable instances: it is a sufficient criterion for terminating type checking but it is not a necessary one. A longer argument can be found at http://okmij.org/ftp/Haskell/types.html#undecidable-inst-defense
However, the posted code has deeper problems, I'm afraid. First, let us look at the case of Strings:
class PolyVariadic p where polyToMonoid' :: String -> p
instance PolyVariadic String where polyToMonoid' acc = acc
instance (Show a, PolyVariadic r) => PolyVariadic (a->r) where polyToMonoid' acc = \a -> polyToMonoid' (acc ++ show a)
polyToMonoid :: PolyVariadic p => p polyToMonoid = polyToMonoid' mempty
test1 = putStrLn $ polyToMonoid True () (Just (5::Int))
*M> test1 True()Just 5 Modulo the TypeSynonymInstances extension, it is Haskell98. If we now generalize it to arbitrary monoids rather than a mere String, we face several problems. First of all, if we re-write the first instance as
instance Monoid r => PolyVariadic r where polyToMonoid' acc = acc
we make it overlap with the second instance: the type variable 'r' may be instantiated to the arrow type a->r'. Now we need a more problematic overlapping instances extension. The problem is deeper however: an arrow type could possibly be an instance of Monoid (for example, functions of the type Int->Int form a monoid with mempty=id, mappend=(.)). If polyToMonoid appears in the context requiring a function type, how could type checker choose the instance of Polyvariadic? The second problem with the posted code
class Monoidable a where toMonoid :: Monoid r => a -> r
is that toMonoid has too `strong' a signature. Suppose we have an instance
instance Monoidable String where toMonoid = \str -> ???
It means that no matter which monoid the programmer may give to us, we promise to inject a string into it. We have no idea about the details of the monoid. It means that the only thing we could do (short of divergence) is to return mempty. That is not too useful. We have little choice but to parametrise Monoidable as well as Polyvariadic with the type of the monoid. To avoid overlapping and disambiguate the contexts, we use the newtype trick. Here is the complete code. It turns out, no undecidable instances are needed.
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
module M where
import Data.Monoid
newtype WMonoid m = WMonoid{unwrap :: m}
class Monoid m => Monoidable a m where toMonoid :: a -> m
class Monoid m => PolyVariadic m p where polyToMonoid :: m -> p
instance Monoid m => PolyVariadic m (WMonoid m) where polyToMonoid acc = WMonoid acc
instance (Monoidable a m, PolyVariadic m r) => PolyVariadic m (a->r) where polyToMonoid acc = \a -> polyToMonoid (acc `mappend` toMonoid a)
instance Show a => Monoidable a String where toMonoid = show
test2 = putStrLn $ unwrap $ polyToMonoid "" True () (Just (5::Int))
The remaining problem is how to tell polyToMonoid which monoid we want. It seems simpler just to pass the appropriately specialized mempty method as the first argument, as shown in test2. Granted, a more elegant solution would be a parametrized module (functor) like those in Agda or ML: module type PolyM = functor(M:: sig type m val mempty :: m val mappend :: m -> m -> m end) = struct class Monoidable a where toMonoid :: a -> m class PolyVariadic p where polyToMonoid :: m -> p .etc end The shown solution is essentially the encoding of the above functor.

Hi Oleg, Thank you for this wonderful detailed solution! I was attempting to turn this into a small library and wanted to avoid exporting unwrap. I defined: polyToMonoid' = unwrap . polyToMonoid and then GHC told me: No instance for (PolyVariadic a (WMonoid m)) arising from a use of `polyToMonoid' at Data\PolyToMonoid.hs:27:24-36 Possible fix: add an instance declaration for (PolyVariadic a (WMonoid m)) Is there a type signature I can assign to polyToMonoid' to get this to work? Or will it always be necessary to export unwrap as well? Kevin On Oct 9, 5:04 am, o...@okmij.org wrote:
Kevin Jardine wrote:
instead of passing around lists of values with these related types, I created a polyvariadic function polyToString... I finally figured out how to do this, but it was a bit harder to figure this out than I expected, and I was wondering if it might be possible to create a small utility library to help other developers do this. It seems to me that in the general case, we would be dealing with a Monoid rather than a list of strings. We could have a toMonoid function and then return
polyToMonoid value1 value2 ... valueN =
(toMonoid value1) `mappend` (toMonoid value2) 'mappend' ... (toMonoid valueN) So I tried writing the following code but GHC said it had undecidable instances.
Generally speaking, we should not be afraid of undecidable instances: it is a sufficient criterion for terminating type checking but it is not a necessary one. A longer argument can be found at http://okmij.org/ftp/Haskell/types.html#undecidable-inst-defense
However, the posted code has deeper problems, I'm afraid. First, let us look at the case of Strings:
class PolyVariadic p where polyToMonoid' :: String -> p
instance PolyVariadic String where polyToMonoid' acc = acc
instance (Show a, PolyVariadic r) => PolyVariadic (a->r) where polyToMonoid' acc = \a -> polyToMonoid' (acc ++ show a)
polyToMonoid :: PolyVariadic p => p polyToMonoid = polyToMonoid' mempty
test1 = putStrLn $ polyToMonoid True () (Just (5::Int))
*M> test1 True()Just 5
Modulo the TypeSynonymInstances extension, it is Haskell98. If we now generalize it to arbitrary monoids rather than a mere String, we face several problems. First of all, if we re-write the first instance as
instance Monoid r => PolyVariadic r where polyToMonoid' acc = acc
we make it overlap with the second instance: the type variable 'r' may be instantiated to the arrow type a->r'. Now we need a more problematic overlapping instances extension. The problem is deeper however: an arrow type could possibly be an instance of Monoid (for example, functions of the type Int->Int form a monoid with mempty=id, mappend=(.)). If polyToMonoid appears in the context requiring a function type, how could type checker choose the instance of Polyvariadic?
The second problem with the posted code
class Monoidable a where toMonoid :: Monoid r => a -> r
is that toMonoid has too `strong' a signature. Suppose we have an instance
instance Monoidable String where toMonoid = \str -> ???
It means that no matter which monoid the programmer may give to us, we promise to inject a string into it. We have no idea about the details of the monoid. It means that the only thing we could do (short of divergence) is to return mempty. That is not too useful.
We have little choice but to parametrise Monoidable as well as Polyvariadic with the type of the monoid. To avoid overlapping and disambiguate the contexts, we use the newtype trick. Here is the complete code. It turns out, no undecidable instances are needed.
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
module M where
import Data.Monoid
newtype WMonoid m = WMonoid{unwrap :: m}
class Monoid m => Monoidable a m where toMonoid :: a -> m
class Monoid m => PolyVariadic m p where polyToMonoid :: m -> p
instance Monoid m => PolyVariadic m (WMonoid m) where polyToMonoid acc = WMonoid acc
instance (Monoidable a m, PolyVariadic m r) => PolyVariadic m (a->r) where polyToMonoid acc = \a -> polyToMonoid (acc `mappend` toMonoid a)
instance Show a => Monoidable a String where toMonoid = show
test2 = putStrLn $ unwrap $ polyToMonoid "" True () (Just (5::Int))
The remaining problem is how to tell polyToMonoid which monoid we want. It seems simpler just to pass the appropriately specialized mempty method as the first argument, as shown in test2.
Granted, a more elegant solution would be a parametrized module (functor) like those in Agda or ML:
module type PolyM = functor(M:: sig type m val mempty :: m val mappend :: m -> m -> m end) = struct class Monoidable a where toMonoid :: a -> m class PolyVariadic p where polyToMonoid :: m -> p .etc end
The shown solution is essentially the encoding of the above functor.
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

Hello Kevin,
2010/10/9 Kevin Jardine
I was attempting to turn this into a small library and wanted to avoid exporting unwrap.
I defined:
polyToMonoid' = unwrap . polyToMonoid
If you disable MonomorphismRestriction this definition typechecks just fine. Alternatively, you can ask ghci about the type of "unwrap . polyToMonoid" and paste that into the type sig. regards, Bartek Ćwikłowski

Hi Bartek,
Yes, it compiles, but when I try to use polyToMonoid', it turns out
that this function is no longer polyvariadic, unlike the original
polyToMonoid .
This may be what Luke meant when he wrote "you lose composability".
Even with the extra unwrap function I think that this is pretty cool,
but I would ideally like to hide the unwrap.
Kevin
On Oct 9, 1:50 pm, Bartek Ćwikłowski
Hello Kevin,
2010/10/9 Kevin Jardine
: I was attempting to turn this into a small library and wanted to avoid exporting unwrap.
I defined:
polyToMonoid' = unwrap . polyToMonoid
If you disable MonomorphismRestriction this definition typechecks just fine. Alternatively, you can ask ghci about the type of "unwrap . polyToMonoid" and paste that into the type sig.
regards, Bartek Ćwikłowski _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

Oleg,
Another puzzle is that:
instance Show a => Monoidable a String where
toMonoid a = show a
main = putStrLn $ unwrap $ polyToMonoid "" True () (Just (5::Int))
works just fine, but
instance Show a => Monoidable a [String] where
toMonoid a = [show a]
main = putStrLn $ unwrap $ polyToMonoid [] True () (Just (5::Int))
fails to compile.
Why would that be? My understanding is that all lists are
automatically monoids.
Kevin
On Oct 9, 2:28 pm, Kevin Jardine
Hi Bartek,
Yes, it compiles, but when I try to use polyToMonoid', it turns out that this function is no longer polyvariadic, unlike the original polyToMonoid .
This may be what Luke meant when he wrote "you lose composability".
Even with the extra unwrap function I think that this is pretty cool, but I would ideally like to hide the unwrap.
Kevin
On Oct 9, 1:50 pm, Bartek Æwik³owski
wrote: Hello Kevin,
2010/10/9 Kevin Jardine
: I was attempting to turn this into a small library and wanted to avoid exporting unwrap.
I defined:
polyToMonoid' = unwrap . polyToMonoid
If you disable MonomorphismRestriction this definition typechecks just fine. Alternatively, you can ask ghci about the type of "unwrap . polyToMonoid" and paste that into the type sig.
regards, Bartek Æwik³owski _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

Another example that also fails to compile (but I cannot see why):
import Data.PolyToMonoid
import Data.Monoid
instance Monoid Int where
mappend = (+)
mempty = 0
instance Monoidable Int Int where
toMonoid = id
main = putStrLn $ show $ unwrap $ polyToMonoid (0::Int) (1::Int)
(2::Int) (3::Int)
In this case, I was expecting a sumOf function.
This gives me:
No instance for (PolyVariadic Int (WMonoid m))
arising from a use of `polyToMonoid'
Any further suggestions?
On Oct 9, 4:25 pm, Kevin Jardine
Oleg,
Another puzzle is that:
instance Show a => Monoidable a String where toMonoid a = show a
main = putStrLn $ unwrap $ polyToMonoid "" True () (Just (5::Int))
works just fine, but
instance Show a => Monoidable a [String] where toMonoid a = [show a]
main = putStrLn $ unwrap $ polyToMonoid [] True () (Just (5::Int))
fails to compile.
Why would that be? My understanding is that all lists are automatically monoids.
Kevin
On Oct 9, 2:28 pm, Kevin Jardine
wrote: Hi Bartek,
Yes, it compiles, but when I try to use polyToMonoid', it turns out that this function is no longer polyvariadic, unlike the original polyToMonoid .
This may be what Luke meant when he wrote "you lose composability".
Even with the extra unwrap function I think that this is pretty cool, but I would ideally like to hide the unwrap.
Kevin
On Oct 9, 1:50 pm, Bartek Æwik³owski
wrote: Hello Kevin,
2010/10/9 Kevin Jardine
: I was attempting to turn this into a small library and wanted to avoid exporting unwrap.
I defined:
polyToMonoid' = unwrap . polyToMonoid
If you disable MonomorphismRestriction this definition typechecks just fine. Alternatively, you can ask ghci about the type of "unwrap . polyToMonoid" and paste that into the type sig.
regards, Bartek Æwik³owski _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 On 10/9/10 10:25 , Kevin Jardine wrote:
instance Show a => Monoidable a [String] where toMonoid a = [show a]
main = putStrLn $ unwrap $ polyToMonoid [] True () (Just (5::Int))
fails to compile.
Why would that be? My understanding is that all lists are automatically monoids.
I *think* the problem here is that Oleg specifically pointed out that the first parameter to polyToMonoid must specify the type of the monoid. [] tells you it's a list, therefore a monoid, but it doesn't say enough to allow the [String] instance to be chosen. (No, the fact that you only declared an instance for [String] isn't really enough.) - -- brandon s. allbery [linux,solaris,freebsd,perl] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.10 (Darwin) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/ iEYEARECAAYFAkyw49wACgkQIn7hlCsL25VZygCfVETk+3AZ3gKoBy4pZ7j8g4Km WXgAnjrbO9rEl2HnQtGQ31EyRuhWzI4r =YMDw -----END PGP SIGNATURE-----

Hi Brandon,
True, when I replace [] with [""], I get a different error message:
No instance for (PolyVariadic [[Char]] (WMonoid String))
which now looks a bit like the Int example. In both cases, GHC appears
to be unable to derive the appropriate instance of PolyVariadic. Why
this is so, but worked for Oleg's specific example. is still not clear
to me.
Kevin
On Oct 9, 11:51 pm, Brandon S Allbery KF8NH
-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1
On 10/9/10 10:25 , Kevin Jardine wrote:
instance Show a => Monoidable a [String] where toMonoid a = [show a]
main = putStrLn $ unwrap $ polyToMonoid [] True () (Just (5::Int))
fails to compile.
Why would that be? My understanding is that all lists are automatically monoids.
I *think* the problem here is that Oleg specifically pointed out that the first parameter to polyToMonoid must specify the type of the monoid. [] tells you it's a list, therefore a monoid, but it doesn't say enough to allow the [String] instance to be chosen. (No, the fact that you only declared an instance for [String] isn't really enough.)
- -- brandon s. allbery [linux,solaris,freebsd,perl] allb...@kf8nh.com system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.10 (Darwin) Comment: Using GnuPG with Mozilla -http://enigmail.mozdev.org/
iEYEARECAAYFAkyw49wACgkQIn7hlCsL25VZygCfVETk+3AZ3gKoBy4pZ7j8g4Km WXgAnjrbO9rEl2HnQtGQ31EyRuhWzI4r =YMDw -----END PGP SIGNATURE----- _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

And in fact in both cases, it appears that GHC is trying to derive the
*wrong* instances of PolyVariadic.
It should be deriving:
PolyVariadic Int (WMonoid Int)
not
PolyVariadic Int (WMonoid m)
and
PolyVariadic [String] (WMonoid [String])
not
PolyVariadic [String] (WMonoid String)
specifically, GHC is attempting to derive PolyVariadic with the wrong
version of WMonoid in each case.
I'm using GHC 6.12.3
Perhaps the new GHC 7 type system would work better?
Kevin
On Oct 10, 8:26 am, Kevin Jardine
Hi Brandon,
True, when I replace [] with [""], I get a different error message:
No instance for (PolyVariadic [[Char]] (WMonoid String))
which now looks a bit like the Int example. In both cases, GHC appears to be unable to derive the appropriate instance of PolyVariadic. Why this is so, but worked for Oleg's specific example. is still not clear to me.
Kevin
On Oct 9, 11:51 pm, Brandon S Allbery KF8NH
wrote: -----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1
On 10/9/10 10:25 , Kevin Jardine wrote:
instance Show a => Monoidable a [String] where toMonoid a = [show a]
main = putStrLn $ unwrap $ polyToMonoid [] True () (Just (5::Int))
fails to compile.
Why would that be? My understanding is that all lists are automatically monoids.
I *think* the problem here is that Oleg specifically pointed out that the first parameter to polyToMonoid must specify the type of the monoid. [] tells you it's a list, therefore a monoid, but it doesn't say enough to allow the [String] instance to be chosen. (No, the fact that you only declared an instance for [String] isn't really enough.)
- -- brandon s. allbery [linux,solaris,freebsd,perl] allb...@kf8nh.com system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.10 (Darwin) Comment: Using GnuPG with Mozilla -http://enigmail.mozdev.org/
iEYEARECAAYFAkyw49wACgkQIn7hlCsL25VZygCfVETk+3AZ3gKoBy4pZ7j8g4Km WXgAnjrbO9rEl2HnQtGQ31EyRuhWzI4r =YMDw -----END PGP SIGNATURE----- _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

OK, upon further investigation, the problem is that GHC cannot in
general infer the return type of polyToMonoid despite the hint it is
given (the type signature of the first parameter).
If I write:
main = putStrLn $ show $ unwrap $ ((polyToMonoid [""] True (Just
(5::Int))) :: WMonoid [String])
or
main = putStrLn $ show $ unwrap $ ((polyToMonoid (0::Int) (1::Int)
(2::Int) (3::Int)) :: WMonoid Int)
the code compiles and returns the expected result.
Kevin
On Oct 10, 8:58 am, Kevin Jardine
And in fact in both cases, it appears that GHC is trying to derive the *wrong* instances of PolyVariadic.
It should be deriving:
PolyVariadic Int (WMonoid Int)
not
PolyVariadic Int (WMonoid m)
and
PolyVariadic [String] (WMonoid [String])
not
PolyVariadic [String] (WMonoid String)
specifically, GHC is attempting to derive PolyVariadic with the wrong version of WMonoid in each case.
I'm using GHC 6.12.3
Perhaps the new GHC 7 type system would work better?
Kevin
On Oct 10, 8:26 am, Kevin Jardine
wrote: Hi Brandon,
True, when I replace [] with [""], I get a different error message:
No instance for (PolyVariadic [[Char]] (WMonoid String))
which now looks a bit like the Int example. In both cases, GHC appears to be unable to derive the appropriate instance of PolyVariadic. Why this is so, but worked for Oleg's specific example. is still not clear to me.
Kevin
On Oct 9, 11:51 pm, Brandon S Allbery KF8NH
wrote: -----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1
On 10/9/10 10:25 , Kevin Jardine wrote:
instance Show a => Monoidable a [String] where toMonoid a = [show a]
main = putStrLn $ unwrap $ polyToMonoid [] True () (Just (5::Int))
fails to compile.
Why would that be? My understanding is that all lists are automatically monoids.
I *think* the problem here is that Oleg specifically pointed out that the first parameter to polyToMonoid must specify the type of the monoid. [] tells you it's a list, therefore a monoid, but it doesn't say enough to allow the [String] instance to be chosen. (No, the fact that you only declared an instance for [String] isn't really enough.)
- -- brandon s. allbery [linux,solaris,freebsd,perl] allb...@kf8nh.com system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.10 (Darwin) Comment: Using GnuPG with Mozilla -http://enigmail.mozdev.org/
iEYEARECAAYFAkyw49wACgkQIn7hlCsL25VZygCfVETk+3AZ3gKoBy4pZ7j8g4Km WXgAnjrbO9rEl2HnQtGQ31EyRuhWzI4r =YMDw -----END PGP SIGNATURE----- _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

For anyone who's interested, the code I have now is:
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances,
MultiParamTypeClasses #-}
module PolyTest where
import Data.Monoid
class Monoid m => Monoidable a m where
toMonoid :: a -> m
squish :: Monoidable a m => m -> a -> m
squish m a = (m `mappend` (toMonoid a))
class Monoid m => PolyVariadic m r where
polyToMonoid :: m -> r
instance Monoid m => PolyVariadic m m where
polyToMonoid acc = acc
instance (Monoidable a m, PolyVariadic m r) => PolyVariadic m (a->r)
where
polyToMonoid acc = \a -> polyToMonoid (squish acc a)
and three example uses are:
-- [String] example
instance Show a => Monoidable a [String] where
toMonoid a = [show a]
testStringList = putStrLn $ show $ ((polyToMonoid [""] True () (Just
(5::Int))) :: [String])
-- String example
instance Show a => Monoidable a String where
toMonoid a = show a
testString = putStrLn $ ((polyToMonoid "" True () (Just (5::Int))) ::
String)
-- sum example
instance Monoid Int where
mappend = (+)
mempty = 0
instance Monoidable Int Int where
toMonoid = id
testSum = putStrLn $ show $ ((polyToMonoid (0::Int) (1::Int) (2::Int)
(3::Int)) :: Int)
main = do
testStringList
testString
testSum
$ runhaskell PolyTest.hs
["","True","()","Just 5"]
True()Just 5
6
This removes the unwrap and I don't mind the need for the outer type
cast.
I do wonder if there is a need for the first (dummy) parameter to
communicate the type as well as this seems redundant given the outer
type cast but I can't find a way to remove it.
It appears that GHC needs to be told the type both coming and going so
to speak for this to work consistently.
Any suggestions for improvement welcome!
Kevin
On Oct 10, 11:12 am, Kevin Jardine
OK, upon further investigation, the problem is that GHC cannot in general infer the return type of polyToMonoid despite the hint it is given (the type signature of the first parameter).
If I write:
main = putStrLn $ show $ unwrap $ ((polyToMonoid [""] True (Just (5::Int))) :: WMonoid [String])
or
main = putStrLn $ show $ unwrap $ ((polyToMonoid (0::Int) (1::Int) (2::Int) (3::Int)) :: WMonoid Int)
the code compiles and returns the expected result.
Kevin
On Oct 10, 8:58 am, Kevin Jardine
wrote: And in fact in both cases, it appears that GHC is trying to derive the *wrong* instances of PolyVariadic.
It should be deriving:
PolyVariadic Int (WMonoid Int)
not
PolyVariadic Int (WMonoid m)
and
PolyVariadic [String] (WMonoid [String])
not
PolyVariadic [String] (WMonoid String)
specifically, GHC is attempting to derive PolyVariadic with the wrong version of WMonoid in each case.
I'm using GHC 6.12.3
Perhaps the new GHC 7 type system would work better?
Kevin
On Oct 10, 8:26 am, Kevin Jardine
wrote: Hi Brandon,
True, when I replace [] with [""], I get a different error message:
No instance for (PolyVariadic [[Char]] (WMonoid String))
which now looks a bit like the Int example. In both cases, GHC appears to be unable to derive the appropriate instance of PolyVariadic. Why this is so, but worked for Oleg's specific example. is still not clear to me.
Kevin
On Oct 9, 11:51 pm, Brandon S Allbery KF8NH
wrote: -----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1
On 10/9/10 10:25 , Kevin Jardine wrote:
instance Show a => Monoidable a [String] where toMonoid a = [show a]
main = putStrLn $ unwrap $ polyToMonoid [] True () (Just (5::Int))
fails to compile.
Why would that be? My understanding is that all lists are automatically monoids.
I *think* the problem here is that Oleg specifically pointed out that the first parameter to polyToMonoid must specify the type of the monoid. [] tells you it's a list, therefore a monoid, but it doesn't say enough to allow the [String] instance to be chosen. (No, the fact that you only declared an instance for [String] isn't really enough.)
- -- brandon s. allbery [linux,solaris,freebsd,perl] allb...@kf8nh.com system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.10 (Darwin) Comment: Using GnuPG with Mozilla -http://enigmail.mozdev.org/
iEYEARECAAYFAkyw49wACgkQIn7hlCsL25VZygCfVETk+3AZ3gKoBy4pZ7j8g4Km WXgAnjrbO9rEl2HnQtGQ31EyRuhWzI4r =YMDw -----END PGP SIGNATURE----- _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

It is interesting to see that the dummy parameters can actually be
replaced by:
mempty :: [String]
mempty :: String
mempty: Int
in my three examples and the code still compiles and gives the
expected results.
This suggests that a further simplification might be possible (ideally
in straight Haskell, but if not then with CPP or Template Haskell).
Kevin
On Oct 10, 1:28 pm, Kevin Jardine
For anyone who's interested, the code I have now is:
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses #-} module PolyTest where
import Data.Monoid
class Monoid m => Monoidable a m where toMonoid :: a -> m
squish :: Monoidable a m => m -> a -> m squish m a = (m `mappend` (toMonoid a))
class Monoid m => PolyVariadic m r where polyToMonoid :: m -> r
instance Monoid m => PolyVariadic m m where polyToMonoid acc = acc
instance (Monoidable a m, PolyVariadic m r) => PolyVariadic m (a->r) where polyToMonoid acc = \a -> polyToMonoid (squish acc a)
and three example uses are:
-- [String] example instance Show a => Monoidable a [String] where toMonoid a = [show a]
testStringList = putStrLn $ show $ ((polyToMonoid [""] True () (Just (5::Int))) :: [String])
-- String example instance Show a => Monoidable a String where toMonoid a = show a
testString = putStrLn $ ((polyToMonoid "" True () (Just (5::Int))) :: String)
-- sum example
instance Monoid Int where mappend = (+) mempty = 0
instance Monoidable Int Int where toMonoid = id
testSum = putStrLn $ show $ ((polyToMonoid (0::Int) (1::Int) (2::Int) (3::Int)) :: Int)
main = do testStringList testString testSum
$ runhaskell PolyTest.hs ["","True","()","Just 5"] True()Just 5 6
This removes the unwrap and I don't mind the need for the outer type cast.
I do wonder if there is a need for the first (dummy) parameter to communicate the type as well as this seems redundant given the outer type cast but I can't find a way to remove it.
It appears that GHC needs to be told the type both coming and going so to speak for this to work consistently.
Any suggestions for improvement welcome!
Kevin
On Oct 10, 11:12 am, Kevin Jardine
wrote: OK, upon further investigation, the problem is that GHC cannot in general infer the return type of polyToMonoid despite the hint it is given (the type signature of the first parameter).
If I write:
main = putStrLn $ show $ unwrap $ ((polyToMonoid [""] True (Just (5::Int))) :: WMonoid [String])
or
main = putStrLn $ show $ unwrap $ ((polyToMonoid (0::Int) (1::Int) (2::Int) (3::Int)) :: WMonoid Int)
the code compiles and returns the expected result.
Kevin
On Oct 10, 8:58 am, Kevin Jardine
wrote: And in fact in both cases, it appears that GHC is trying to derive the *wrong* instances of PolyVariadic.
It should be deriving:
PolyVariadic Int (WMonoid Int)
not
PolyVariadic Int (WMonoid m)
and
PolyVariadic [String] (WMonoid [String])
not
PolyVariadic [String] (WMonoid String)
specifically, GHC is attempting to derive PolyVariadic with the wrong version of WMonoid in each case.
I'm using GHC 6.12.3
Perhaps the new GHC 7 type system would work better?
Kevin
On Oct 10, 8:26 am, Kevin Jardine
wrote: Hi Brandon,
True, when I replace [] with [""], I get a different error message:
No instance for (PolyVariadic [[Char]] (WMonoid String))
which now looks a bit like the Int example. In both cases, GHC appears to be unable to derive the appropriate instance of PolyVariadic. Why this is so, but worked for Oleg's specific example. is still not clear to me.
Kevin
On Oct 9, 11:51 pm, Brandon S Allbery KF8NH
wrote: -----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1
On 10/9/10 10:25 , Kevin Jardine wrote:
instance Show a => Monoidable a [String] where toMonoid a = [show a]
main = putStrLn $ unwrap $ polyToMonoid [] True () (Just (5::Int))
fails to compile.
Why would that be? My understanding is that all lists are automatically monoids.
I *think* the problem here is that Oleg specifically pointed out that the first parameter to polyToMonoid must specify the type of the monoid. [] tells you it's a list, therefore a monoid, but it doesn't say enough to allow the [String] instance to be chosen. (No, the fact that you only declared an instance for [String] isn't really enough.)
- -- brandon s. allbery [linux,solaris,freebsd,perl] allb...@kf8nh.com system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.10 (Darwin) Comment: Using GnuPG with Mozilla -http://enigmail.mozdev.org/
iEYEARECAAYFAkyw49wACgkQIn7hlCsL25VZygCfVETk+3AZ3gKoBy4pZ7j8g4Km WXgAnjrbO9rEl2HnQtGQ31EyRuhWzI4r =YMDw -----END PGP SIGNATURE----- _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

For example, the notation can be reduced to:
poly([String],True () (Just (5::Int)))
using:
#define poly(TYPE,VALUES) ((polyToMonoid (mempty :: TYPE) VALUES) ::
TYPE)
which I think is as concise as it can get.
Kevin
On Oct 10, 1:47 pm, Kevin Jardine
It is interesting to see that the dummy parameters can actually be replaced by:
mempty :: [String] mempty :: String mempty: Int
in my three examples and the code still compiles and gives the expected results.
This suggests that a further simplification might be possible (ideally in straight Haskell, but if not then with CPP or Template Haskell).
Kevin
On Oct 10, 1:28 pm, Kevin Jardine
wrote: For anyone who's interested, the code I have now is:
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses #-} module PolyTest where
import Data.Monoid
class Monoid m => Monoidable a m where toMonoid :: a -> m
squish :: Monoidable a m => m -> a -> m squish m a = (m `mappend` (toMonoid a))
class Monoid m => PolyVariadic m r where polyToMonoid :: m -> r
instance Monoid m => PolyVariadic m m where polyToMonoid acc = acc
instance (Monoidable a m, PolyVariadic m r) => PolyVariadic m (a->r) where polyToMonoid acc = \a -> polyToMonoid (squish acc a)
and three example uses are:
-- [String] example instance Show a => Monoidable a [String] where toMonoid a = [show a]
testStringList = putStrLn $ show $ ((polyToMonoid [""] True () (Just (5::Int))) :: [String])
-- String example instance Show a => Monoidable a String where toMonoid a = show a
testString = putStrLn $ ((polyToMonoid "" True () (Just (5::Int))) :: String)
-- sum example
instance Monoid Int where mappend = (+) mempty = 0
instance Monoidable Int Int where toMonoid = id
testSum = putStrLn $ show $ ((polyToMonoid (0::Int) (1::Int) (2::Int) (3::Int)) :: Int)
main = do testStringList testString testSum
$ runhaskell PolyTest.hs ["","True","()","Just 5"] True()Just 5 6
This removes the unwrap and I don't mind the need for the outer type cast.
I do wonder if there is a need for the first (dummy) parameter to communicate the type as well as this seems redundant given the outer type cast but I can't find a way to remove it.
It appears that GHC needs to be told the type both coming and going so to speak for this to work consistently.
Any suggestions for improvement welcome!
Kevin
On Oct 10, 11:12 am, Kevin Jardine
wrote: OK, upon further investigation, the problem is that GHC cannot in general infer the return type of polyToMonoid despite the hint it is given (the type signature of the first parameter).
If I write:
main = putStrLn $ show $ unwrap $ ((polyToMonoid [""] True (Just (5::Int))) :: WMonoid [String])
or
main = putStrLn $ show $ unwrap $ ((polyToMonoid (0::Int) (1::Int) (2::Int) (3::Int)) :: WMonoid Int)
the code compiles and returns the expected result.
Kevin
On Oct 10, 8:58 am, Kevin Jardine
wrote: And in fact in both cases, it appears that GHC is trying to derive the *wrong* instances of PolyVariadic.
It should be deriving:
PolyVariadic Int (WMonoid Int)
not
PolyVariadic Int (WMonoid m)
and
PolyVariadic [String] (WMonoid [String])
not
PolyVariadic [String] (WMonoid String)
specifically, GHC is attempting to derive PolyVariadic with the wrong version of WMonoid in each case.
I'm using GHC 6.12.3
Perhaps the new GHC 7 type system would work better?
Kevin
On Oct 10, 8:26 am, Kevin Jardine
wrote: Hi Brandon,
True, when I replace [] with [""], I get a different error message:
No instance for (PolyVariadic [[Char]] (WMonoid String))
which now looks a bit like the Int example. In both cases, GHC appears to be unable to derive the appropriate instance of PolyVariadic. Why this is so, but worked for Oleg's specific example. is still not clear to me.
Kevin
On Oct 9, 11:51 pm, Brandon S Allbery KF8NH
wrote: -----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1
On 10/9/10 10:25 , Kevin Jardine wrote:
> instance Show a => Monoidable a [String] where > toMonoid a = [show a]
> main = putStrLn $ unwrap $ polyToMonoid [] True () (Just (5::Int))
> fails to compile.
> Why would that be? My understanding is that all lists are > automatically monoids.
I *think* the problem here is that Oleg specifically pointed out that the first parameter to polyToMonoid must specify the type of the monoid. [] tells you it's a list, therefore a monoid, but it doesn't say enough to allow the [String] instance to be chosen. (No, the fact that you only declared an instance for [String] isn't really enough.)
- -- brandon s. allbery [linux,solaris,freebsd,perl] allb...@kf8nh.com system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.10 (Darwin) Comment: Using GnuPG with Mozilla -http://enigmail.mozdev.org/
iEYEARECAAYFAkyw49wACgkQIn7hlCsL25VZygCfVETk+3AZ3gKoBy4pZ7j8g4Km WXgAnjrbO9rEl2HnQtGQ31EyRuhWzI4r =YMDw -----END PGP SIGNATURE----- _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

One final example to end with:
-- mixed type product example
instance Monoid Double where
mappend = (*)
mempty = (1.0) :: Double
instance Monoidable Int Double where
toMonoid = fromIntegral
instance Monoidable Double Double where
toMonoid = id
#define productOf(VALUES) poly(Double,VALUES)
testProduct = putStrLn $ show $ productOf ( (5 :: Int) (2.3 :: Double)
(3 :: Int) (8 :: Int) )
If anyone has a better alternative to the CPP macros, I'd be
interested to hear it.
I think that this is interesting enough to create a
PolyvariadicFromMonoid library as it seems to be a fast way to create
a large number of polyvariadic functions - basicially, just set up
your Monoid definition and your toMonoid conversion functions and then
you get the appropriate polvariadic function for free.
Thanks for the input from everyone and Oleg especially for creating
working code!
Kevin
On Oct 10, 2:51 pm, Kevin Jardine
For example, the notation can be reduced to:
poly([String],True () (Just (5::Int)))
using:
#define poly(TYPE,VALUES) ((polyToMonoid (mempty :: TYPE) VALUES) :: TYPE)
which I think is as concise as it can get.
Kevin
On Oct 10, 1:47 pm, Kevin Jardine
wrote: It is interesting to see that the dummy parameters can actually be replaced by:
mempty :: [String] mempty :: String mempty: Int
in my three examples and the code still compiles and gives the expected results.
This suggests that a further simplification might be possible (ideally in straight Haskell, but if not then with CPP or Template Haskell).
Kevin
On Oct 10, 1:28 pm, Kevin Jardine
wrote: For anyone who's interested, the code I have now is:
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses #-} module PolyTest where
import Data.Monoid
class Monoid m => Monoidable a m where toMonoid :: a -> m
squish :: Monoidable a m => m -> a -> m squish m a = (m `mappend` (toMonoid a))
class Monoid m => PolyVariadic m r where polyToMonoid :: m -> r
instance Monoid m => PolyVariadic m m where polyToMonoid acc = acc
instance (Monoidable a m, PolyVariadic m r) => PolyVariadic m (a->r) where polyToMonoid acc = \a -> polyToMonoid (squish acc a)
and three example uses are:
-- [String] example instance Show a => Monoidable a [String] where toMonoid a = [show a]
testStringList = putStrLn $ show $ ((polyToMonoid [""] True () (Just (5::Int))) :: [String])
-- String example instance Show a => Monoidable a String where toMonoid a = show a
testString = putStrLn $ ((polyToMonoid "" True () (Just (5::Int))) :: String)
-- sum example
instance Monoid Int where mappend = (+) mempty = 0
instance Monoidable Int Int where toMonoid = id
testSum = putStrLn $ show $ ((polyToMonoid (0::Int) (1::Int) (2::Int) (3::Int)) :: Int)
main = do testStringList testString testSum
$ runhaskell PolyTest.hs ["","True","()","Just 5"] True()Just 5 6
This removes the unwrap and I don't mind the need for the outer type cast.
I do wonder if there is a need for the first (dummy) parameter to communicate the type as well as this seems redundant given the outer type cast but I can't find a way to remove it.
It appears that GHC needs to be told the type both coming and going so to speak for this to work consistently.
Any suggestions for improvement welcome!
Kevin
On Oct 10, 11:12 am, Kevin Jardine
wrote: OK, upon further investigation, the problem is that GHC cannot in general infer the return type of polyToMonoid despite the hint it is given (the type signature of the first parameter).
If I write:
main = putStrLn $ show $ unwrap $ ((polyToMonoid [""] True (Just (5::Int))) :: WMonoid [String])
or
main = putStrLn $ show $ unwrap $ ((polyToMonoid (0::Int) (1::Int) (2::Int) (3::Int)) :: WMonoid Int)
the code compiles and returns the expected result.
Kevin
On Oct 10, 8:58 am, Kevin Jardine
wrote: And in fact in both cases, it appears that GHC is trying to derive the *wrong* instances of PolyVariadic.
It should be deriving:
PolyVariadic Int (WMonoid Int)
not
PolyVariadic Int (WMonoid m)
and
PolyVariadic [String] (WMonoid [String])
not
PolyVariadic [String] (WMonoid String)
specifically, GHC is attempting to derive PolyVariadic with the wrong version of WMonoid in each case.
I'm using GHC 6.12.3
Perhaps the new GHC 7 type system would work better?
Kevin
On Oct 10, 8:26 am, Kevin Jardine
wrote: Hi Brandon,
True, when I replace [] with [""], I get a different error message:
No instance for (PolyVariadic [[Char]] (WMonoid String))
which now looks a bit like the Int example. In both cases, GHC appears to be unable to derive the appropriate instance of PolyVariadic. Why this is so, but worked for Oleg's specific example. is still not clear to me.
Kevin
On Oct 9, 11:51 pm, Brandon S Allbery KF8NH
wrote: > -----BEGIN PGP SIGNED MESSAGE----- > Hash: SHA1
> On 10/9/10 10:25 , Kevin Jardine wrote:
> > instance Show a => Monoidable a [String] where > > toMonoid a = [show a]
> > main = putStrLn $ unwrap $ polyToMonoid [] True () (Just (5::Int))
> > fails to compile.
> > Why would that be? My understanding is that all lists are > > automatically monoids.
> I *think* the problem here is that Oleg specifically pointed out that the > first parameter to polyToMonoid must specify the type of the monoid. [] > tells you it's a list, therefore a monoid, but it doesn't say enough to > allow the [String] instance to be chosen. (No, the fact that you only > declared an instance for [String] isn't really enough.)
> - -- > brandon s. allbery [linux,solaris,freebsd,perl] allb...@kf8nh.com > system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu > electrical and computer engineering, carnegie mellon university KF8NH > -----BEGIN PGP SIGNATURE----- > Version: GnuPG v2.0.10 (Darwin) > Comment: Using GnuPG with Mozilla -http://enigmail.mozdev.org/
> iEYEARECAAYFAkyw49wACgkQIn7hlCsL25VZygCfVETk+3AZ3gKoBy4pZ7j8g4Km > WXgAnjrbO9rEl2HnQtGQ31EyRuhWzI4r > =YMDw > -----END PGP SIGNATURE----- > _______________________________________________ > Haskell-Cafe mailing list > Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
-
Bartek Ćwikłowski
-
Brandon S Allbery KF8NH
-
Kevin Jardine
-
oleg@okmij.org