[Haskell-cafe] Polyvariadic functions operating with a monoid

2010-10-08 Thread oleg

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-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Polyvariadic functions operating with a monoid

2010-10-03 Thread Kevin Jardine
I had a situation where I had some related types that all had toString
functions.

Of course in Haskell, lists all have to be composed of values of
exactly the same type, so instead of passing around lists of values
with these related types, I created a polyvariadic function
polyToString so that I could write:

(polyToString value1 value2 value3 ... valueN)

which would then become a list of strings:

[toString value1, toString value2, ... , toString valueN]

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 anyone who wanted to convert a bunch of values of different types
to a Monoid  could easily pass them around using polyToMonoid so long
as they defined the appropriate toMonoid function.

Basically, a generalised list.

So I tried writing the following code but GHC said it had undecidable
instances.

Has this ever been done successfully?

class Monoidable a where
toMonoid :: Monoid r = a - r

polyToMonoid :: (Monoidable a, Monoid r) = a - r
polyToMonoid k = polyToMonoid' k mempty

class PolyVariadic p where
polyToMonoid' :: (Monoidable a, Monoid r) = a - r - p

instance Monoid r = PolyVariadic r where
polyToMonoid' k ss = (toMonoid k) `mappend` ss

instance (Monoidable a, Monoid r) = PolyVariadic (a - r) where
polyToMonoid' k ss = (\a - polyToMonoid' k (toMonoid a) `mappend`
ss)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polyvariadic functions operating with a monoid

2010-10-03 Thread Luke Palmer
On Sun, Oct 3, 2010 at 1:24 AM, Kevin Jardine kevinjard...@gmail.com wrote:
 I had a situation where I had some related types that all had toString
 functions.

 Of course in Haskell, lists all have to be composed of values of
 exactly the same type, so instead of passing around lists of values
 with these related types, I created a polyvariadic function
 polyToString so that I could write:

 (polyToString value1 value2 value3 ... valueN)

 which would then become a list of strings:

 [toString value1, toString value2, ... , toString valueN]

First of all, you are not using the monoidal structure of String at
all.  This trick ought to work for any type whatsoever -- you're just
throwing them in a list.

Other than a few brackets, commas, and a repeated identifier (which
you can let-bind to shorten), what benefit is it giving you?  I
strongly recommend against polyvariadic functions.  While you get a
little bit of notational convenience, you lose composability.  There
are pains when you try to write a function that takes a polyvariadic
function as an argument, or when you try to feed the function values
from a list, etc.  The mechanisms to create polyvariadic functions are
brittle and hacky (eg. you cannot have a polymorphic return type, as
you want in this case).

Since all your values are known statically, I would recommend biting
the bullet and doing it the way you were doing it.

[ s value1, s value2, s value3, ... ]
   where
   s x = toString x

(I had to eta expand s so that I didn't hit the monomorphism restriction)

When you want to be passing around heterogeneous lists, it usually
works to convert them before you put them in the list, like you were
doing.

 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 anyone who wanted to convert a bunch of values of different types
 to a Monoid  could easily pass them around using polyToMonoid so long
 as they defined the appropriate toMonoid function.

 Basically, a generalised list.

 So I tried writing the following code but GHC said it had undecidable
 instances.

 Has this ever been done successfully?

 class Monoidable a where
    toMonoid :: Monoid r = a - r

 polyToMonoid :: (Monoidable a, Monoid r) = a - r
 polyToMonoid k = polyToMonoid' k mempty

 class PolyVariadic p where
    polyToMonoid' :: (Monoidable a, Monoid r) = a - r - p

 instance Monoid r = PolyVariadic r where
    polyToMonoid' k ss = (toMonoid k) `mappend` ss

 instance (Monoidable a, Monoid r) = PolyVariadic (a - r) where
    polyToMonoid' k ss = (\a - polyToMonoid' k (toMonoid a) `mappend`
 ss)

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polyvariadic functions operating with a monoid

2010-10-03 Thread Luke Palmer
On Sun, Oct 3, 2010 at 1:26 PM, Luke Palmer lrpal...@gmail.com wrote:
 On Sun, Oct 3, 2010 at 1:24 AM, Kevin Jardine kevinjard...@gmail.com wrote:
 I had a situation where I had some related types that all had toString
 functions.

 Of course in Haskell, lists all have to be composed of values of
 exactly the same type, so instead of passing around lists of values
 with these related types, I created a polyvariadic function
 polyToString so that I could write:

 (polyToString value1 value2 value3 ... valueN)

 which would then become a list of strings:

 [toString value1, toString value2, ... , toString valueN]

 First of all, you are not using the monoidal structure of String at
 all.  This trick ought to work for any type whatsoever -- you're just
 throwing them in a list.

Oops, sorry for not reading your message more closely.  You were
indeed talking about the monoidal structure of list.  So... nevermind
about this comment.  :-P

 Other than a few brackets, commas, and a repeated identifier (which
 you can let-bind to shorten), what benefit is it giving you?  I
 strongly recommend against polyvariadic functions.  While you get a
 little bit of notational convenience, you lose composability.  There
 are pains when you try to write a function that takes a polyvariadic
 function as an argument, or when you try to feed the function values
 from a list, etc.  The mechanisms to create polyvariadic functions are
 brittle and hacky (eg. you cannot have a polymorphic return type, as
 you want in this case).

 Since all your values are known statically, I would recommend biting
 the bullet and doing it the way you were doing it.

    [ s value1, s value2, s value3, ... ]
       where
       s x = toString x

 (I had to eta expand s so that I didn't hit the monomorphism restriction)

 When you want to be passing around heterogeneous lists, it usually
 works to convert them before you put them in the list, like you were
 doing.

 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 anyone who wanted to convert a bunch of values of different types
 to a Monoid  could easily pass them around using polyToMonoid so long
 as they defined the appropriate toMonoid function.

 Basically, a generalised list.

 So I tried writing the following code but GHC said it had undecidable
 instances.

 Has this ever been done successfully?

 class Monoidable a where
    toMonoid :: Monoid r = a - r

 polyToMonoid :: (Monoidable a, Monoid r) = a - r
 polyToMonoid k = polyToMonoid' k mempty

 class PolyVariadic p where
    polyToMonoid' :: (Monoidable a, Monoid r) = a - r - p

 instance Monoid r = PolyVariadic r where
    polyToMonoid' k ss = (toMonoid k) `mappend` ss

 instance (Monoidable a, Monoid r) = PolyVariadic (a - r) where
    polyToMonoid' k ss = (\a - polyToMonoid' k (toMonoid a) `mappend`
 ss)

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe