[Haskell-cafe] Polyvariadic functions operating with a monoid

oleg at okmij.org oleg at okmij.org
Fri Oct 8 23:04:40 EDT 2010


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.



More information about the Haskell-Cafe mailing list