
Sorry, I'm still catching up. I'm replying to first few messages.
instance Show a => Monoidable a [String] where toMonoid a = [show a]
main = putStrLn $ unwrap $ polyToMonoid [] True () (Just (5::Int)) fails to compile.
The error message points to the first problem:
No instances for (Monoidable Bool [a], Monoidable () [a], ...
The presence of the type variable 'a' means that the type checker doesn't know list of what elements you want (in other words, the context is not specific enough to instantiate the type variable a). Thus, we need to explicitly tell that we wish a list of strings:
test3 = putStrLn $ unwrap $polyToMonoid ([]::[String]) True () (Just (5::Int))
Now we get a different error, which points to the real problem this time: the expression `unwrap ....' appears as an argument to putStrLn. That means that we are required to produce a String as a monoid. Yet we specified ([]::[String]) as mempty, which is unsuitable as mempty for the String monoid. If we desire the [String] monoid as the result, we need to change the context. For example,
test3 = mapM_ putStrLn $ unwrap $ polyToMonoid ([]::[String]) True () (Just (5::Int))
Another example that also fails to compile (but I cannot see why): main = putStrLn $ show $ unwrap $ polyToMonoid (0::Int) (1::Int) (2::Int) (3::Int) No instance for (PolyVariadic Int (WMonoid m)) arising from a use of `polyToMonoid'
The error message is informative, mentioning the type variable, m. Whenever that happens, we know that we put a bounded polymorphic expression in the context that is not specific enough. We need some type annotations. In our case, the function 'show' can show values of many types. The type checker does not know that we wish an Int monoid specifically. So, we have to specialize the show function:
test4 = putStrLn $ (show :: Int -> String) $ unwrap $ polyToMonoid (0::Int) (1::Int) (2::Int) (3::Int)
At this point one may wonder if this is all worth it. There are too many annotations. Fortunately, if you are not afraid of one more extension, the annotations can be avoided. Your example would be accepted as it was written, see test3 and test4 below.
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, TypeFamilies #-}
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', m' ~ 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
instance Show a => Monoidable a [String] where toMonoid a = [show a]
test2 = putStrLn $ unwrap $ polyToMonoid "" True () (Just (5::Int))
test3 = mapM_ putStrLn $ unwrap $ polyToMonoid [] True () (Just (5::Int))
instance Monoid Int where mappend = (+) mempty = 0
instance Monoidable Int Int where toMonoid = id
test4 = putStrLn $ show $ unwrap $ polyToMonoid (0::Int) (1::Int) (2::Int) (3::Int)
P.S. Indeed, "polyToMonoid' = unwrap . polyToMonoid" does not do what one wishes to. One should regard `unwrap' as a sort of terminator of the argument list.