
(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

Hello,
I am not sure what the process is, but this seems like a good idea to
me. I would only suggest that instead of 'runEndo' we call the
selector 'appEndo'. We could even use some sort of infix application
operator if anyone could suggest one.
-Iavor
On 9/13/05, Ross Paterson
(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@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Speaking of boring libraries,
On 9/13/05, Ross Paterson
(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
On Tue, Sep 13, 2005 at 12:04:00PM -0700, Iavor Diatchki wrote:
I am not sure what the process is, but this seems like a good idea to me.
I'm not sure either, so I'll just make the change unless someone objects convincingly. To recap: with Haskell's class system, we can have only one (->) instance, so we have to choose. The old instance is easy to use with Writer monads, and ShowS is a special case. With the new instance, one would have to wrap and unwrap the newtype. The new instance is consistent with the instances for tuples, and it's compositional, in that it builds instances for complex types out of instances for simpler ones, e.g. (first one from Conor): newtype Parser s a = P ([s] -> [(a, [s])]) instance Monoid (Parser s a) where mempty = P mempty P f `mappend` P g = P (f `mappend` g) newtype Automaton a b = A (a -> (b, Automaton a b)) instance Monoid b => Monoid (Automaton a b) where mempty = A mempty A f `mappend` A g = A (f `mappend` g) With GHC's newtype-deriving, the first one could just be newtype Parser s a = P ([s] -> [(a, [s])]) deriving (Monoid) The new instance is also Haskell 98.

Erm... Did anyone read my suggestion? No comments? I feel a little bit ignored. http://comments.gmane.org/gmane.comp.lang.haskell.libraries/3795 Excerpt (revised): [code] class Sequence m where sequence :: [m a] -> m [a] instance Monad m => Sequence m where sequence = Control.Monad.sequence instance (Arrow f) => Sequence (f a) where sequence [] = pure (const []) sequence [f] = f >>> pure (:[]) sequence (f:fr) = (f &&& sequence fr) >>> pure (uncurry (:)) --Ross Paterson's Monoid: rp_concat :: (Monoid b) => [a->b] -> a->b rp_concat = rp_concat' rp_concat' :: (Arrow f,Monoid b) => [f a b] -> f a b rp_concat' fs = sequence fs >>> pure mconcat [/code] Am Montag, 24. Oktober 2005 11:40 schrieb Ross Paterson:
Speaking of boring libraries,
On 9/13/05, Ross Paterson
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
On Tue, Sep 13, 2005 at 12:04:00PM -0700, Iavor Diatchki wrote:
I am not sure what the process is, but this seems like a good idea to me.
I'm not sure either, so I'll just make the change unless someone objects convincingly.
To recap: with Haskell's class system, we can have only one (->) instance, so we have to choose.
The old instance is easy to use with Writer monads, and ShowS is a special case. With the new instance, one would have to wrap and unwrap the newtype.
The new instance is consistent with the instances for tuples, and it's compositional, in that it builds instances for complex types out of instances for simpler ones, e.g. (first one from Conor):
newtype Parser s a = P ([s] -> [(a, [s])])
instance Monoid (Parser s a) where mempty = P mempty P f `mappend` P g = P (f `mappend` g)
newtype Automaton a b = A (a -> (b, Automaton a b))
instance Monoid b => Monoid (Automaton a b) where mempty = A mempty A f `mappend` A g = A (f `mappend` g)
With GHC's newtype-deriving, the first one could just be
newtype Parser s a = P ([s] -> [(a, [s])]) deriving (Monoid)
The new instance is also Haskell 98.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Hello,
These instances overlap, which is not allowed in Haskell.
-Iavor
On 10/24/05, Marc A. Ziegert
Excerpt (revised): [code] class Sequence m where sequence :: [m a] -> m [a]
instance Monad m => Sequence m where sequence = Control.Monad.sequence
instance (Arrow f) => Sequence (f a) where sequence [] = pure (const []) sequence [f] = f >>> pure (:[]) sequence (f:fr) = (f &&& sequence fr) >>> pure (uncurry (:))

oh. pure haskell98... i forgot that old problem. :/ well, i still miss the arrow-(&&&)-version of that monoid. but, to newtype it, may be the better solution. [code] newtype ParArrow f a b = ParArrow (f a b) -- monoid iff b is monoid newtype SerArrow f a b = SerArrow (f a b) -- monoid on endomorphisms instance (Arrow f) => Arrow (ParArrow f) where ... -- derived instance (Arrow f) => Arrow (SerArrow f) where ... -- derived instance (Arrow f, Monoid b) => Monoid (ParArrow f a b) where mempty = pure (const mempty) mappend a b = (a &&& b) >>> pure (uncurry mappend) instance (Arrow f) => Monoid (SerArrow f a a) where mempty = pure id mappend = (>>>) [/code] Am Dienstag, 25. Oktober 2005 19:05 schrieb Iavor Diatchki:
Hello, These instances overlap, which is not allowed in Haskell. -Iavor
On 10/24/05, Marc A. Ziegert
wrote: Excerpt (revised): [code] class Sequence m where sequence :: [m a] -> m [a]
instance Monad m => Sequence m where sequence = Control.Monad.sequence
instance (Arrow f) => Sequence (f a) where sequence [] = pure (const []) sequence [f] = f >>> pure (:[]) sequence (f:fr) = (f &&& sequence fr) >>> pure (uncurry (:))

In article <20051024094010.GA4888@soi.city.ac.uk>,
Ross Paterson
To recap: with Haskell's class system, we can have only one (->) instance, so we have to choose.
There are many possibilities: instance Monoid [a] where mempty = [] mappend = (++) instance Monoid (a -> a) where mempty = id mappend = (.) instance Monoid b => Monoid (a -> b) where mempty _ = mempty mappend f g x = f x `mappend` g x instance Monad m => Monoid (m ()) where mempty = return () mappend = (>>) instance MonadPlus m => Monoid (m a) where mempty = mzero mappend = mplus instance Arrow arr => Monoid (arr p p) where mempty = arr id mappend = (>>>) instance Monoid a => Monoid a where mempty = mempty mappend p q = mappend q p OK, so the last one's silly. But maybe Monoid should be a datatype rather than a class? -- Ashley Yakeley, Seattle WA

On Wed, Oct 26, 2005 at 09:55:07PM -0700, Ashley Yakeley wrote:
OK, so the last one's silly. But maybe Monoid should be a datatype rather than a class?
no reason we can't have both. I certainly would not want to see the Monoid class go away, it is perhaps one of the most useful abstractions... I would like to see it split up like class HasEmpty a where mempty :: a class HasEmpty a => Monoid a where mappend :: a -> a -> a mconcat :: [a] -> a though.. perhaps if my class alias proposal takes off.... John -- John Meacham - ⑆repetae.net⑆john⑈

On 13/09/05, Ross Paterson
(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@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

I should note that another small thing which would be desirable is a way to construct the derived instance of a class at a given type. Perhaps something along the lines of "instance Show MyType derived" or "derived instance Show MyType" which on its own would be handy sometimes. - Cale

On Tue, Sep 13, 2005 at 08:55:09PM -0400, Cale Gibbard wrote:
I should note that another small thing which would be desirable is a way to construct the derived instance of a class at a given type. Perhaps something along the lines of "instance Show MyType derived" or "derived instance Show MyType" which on its own would be handy sometimes.
this would be useful, but we must be sure that all the constructors for the type are in scope or this could be used to break encapsulation. John -- John Meacham - ⑆repetae.net⑆john⑈

On Tue, Sep 13, 2005 at 08:35:39PM -0400, Cale Gibbard wrote:
On 13/09/05, Ross Paterson
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
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.
The old instance is handy with the writer monad, but it's a dead end; the proposed (pointwise) one lets you lift through a series of function types, just as you can with tuple types. Fiddling with the Endo newtype will be some bother, but simulating the pointwise lifting by hand is much more awkward.

Forgive me but the names mempty, mappend, runEndo look horrible. See http://www.haskell.org//pipermail/haskell/2005-August/016323.html -- -- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 -- ---- http://www.imn.htwk-leipzig.de/~waldmann/ -------

On 14/09/05, Johannes Waldmann
Forgive me but the names mempty, mappend, runEndo look horrible. See http://www.haskell.org//pipermail/haskell/2005-August/016323.html -- -- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 -- ---- http://www.imn.htwk-leipzig.de/~waldmann/ -------
Well, I agree that appEndo is better, since it really is just wrapped function application. If you don't like the abbreviation, that would become applyEndofunction. I think it's reasonably obvious from the type what it does anyway. It ought to have a short name since infix application is likely. The names mempty and mappend are not too bad, even if they're a little unconventional. The analogy with the list monoid is clear enough. "unit" or "identity" and "times" or "multiply" would also work. I personally don't really see the need to change the names, they're reasonably descriptive, and it was obvious what they referred to the first time I saw them. By the way, Data.Set should perhaps be made an instance of Monoid in the obvious way. - Cale

On Wed, Sep 14, 2005 at 06:31:01AM -0400, Cale Gibbard wrote:
By the way, Data.Set should perhaps be made an instance of Monoid in the obvious way.
It already is, but the instance is in Data.Monoid to prevent the non-portability of Data.Monoid (caused by the existing -> instance) infecting Data.Set.
participants (7)
-
Ashley Yakeley
-
Cale Gibbard
-
Iavor Diatchki
-
Johannes Waldmann
-
John Meacham
-
Marc A. Ziegert
-
Ross Paterson