Data.Monoid

Cale Gibbard cgibbard at gmail.com
Tue Sep 13 20:35:39 EDT 2005


On 13/09/05, Ross Paterson <ross at soi.city.ac.uk> wrote:
> (regurgitating
> http://www.haskell.org/pipermail/libraries/2005-July/004057.html)
> 
> I propose to replace the instance
> 
>         instance Monoid (a -> a) where
>                 mempty  = id
>                 mappend = (.)
> 
> with
> 
>         newtype Endo a = Endo { runEndo :: a -> a }
> 
>         instance Monoid (Endo a) where
>                 mempty = Endo id
>                 Endo f `mappend` Endo g = Endo (f . g)
> 
>         instance Monoid b => Monoid (a -> b) where
>                 mempty _ = mempty
>                 mappend f g x = f x `mappend` g x
> 
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
> 

I don't think it's clear which of the two instances is more useful. I
would actually probably consider the existing instance more
fundamental, and get more use out of it. (It's occasionally quite
handy together with WriterT), but who knows - perhaps it's best if
they're both wrapped in newtypes for the time being.

How much consideration has been given to the concept of named
instances of classes? (there's an interesting paper giving one
proposal for such a construction at
http://www.informatik.uni-bonn.de/~ralf/hw2001/4.html)

This would be quite a nice sort of thing to have, as single types are
often monoids in a number of different incompatible ways.

A similar idea to the one expressed in that paper would be to lift
class instances to being values of a specific type (say, perhaps a
type constructor Instance C for each class C which takes as type
parameters the parameters to the class), abstractly representing those
dictionaries, together with constructions to scope the application of
the dictionary -- say, allow values of type Instance C in let
expressions define the local instance to be used. Existing instance
declarations would now construct a value typed as an Instance at top
level which would be the default instance.

For example, we might have:

instance (Num a) => Monoid a where
   mempty = 0
   mappend = (+)

multMonoid :: (Num a) => Instance Monoid a
multMonoid = instance (Num a) => Monoid a where
   mempty = 1
   mappend = (*)

So that,
mconcat [1,2,3,4,5] == 15
let multMonoid in mconcat [1,2,3,4,5] == 120

or more explicitly:
let instance (Num a) => Monoid a where
        mempty = 1
        mappend = (*)
in mconcat [1,2,3,4,5]
would evaluate to 120.

let multMonoid :: Instance Monoid Integer in mconcat [1.0..5.0]
would again be 15.0, as the instance specified in the let wouldn't
apply to whatever fractional type the values in the list resolve to.

Similar errors as the current situation would apply to instances
specified in the same let expression, but as above, instances may
shadow each other.

The interaction with modules seems to need more specification, and
possibly more syntax. One solution which seems compatible with the
current interpretation of instances would be to export the specified
instances at the top level of any given module, and when they are
imported, it is exactly as if they occur at the top level of the new
module (that is, they can't be shadowed by local instances at the top
level). Another option is to provide for that possibility, treating
the imported instances as if they are being specified in a wider
scope, but making them available otherwise.

What do people think? Is there a way in which this is broken which I don't see?

 - Cale


More information about the Libraries mailing list