
On 20 March 2005 23:30, Thomas Jäger wrote:
Aside from naming issues, there seem to be some problems with the way FunctorM is currently implemented.
First of all, `FunctorM` should be a superclass of `Functor' because there is an obvios implementation of fmap in terms of fmapM
import Data.FunctorM import Control.Monad.Identity
fmap' :: FunctorM f => (a -> b) -> f a -> f b fmap' f = runIdentity . fmapM (return . f) It is already annyoing enough that `Funtor' isn't a subclass of `Monad' although every monad must also be functor.
Now, FunctorM should be based on the simplest operations possible, which in this case is the distributive law and not a monadic version of fmap (which might be provided for efficiency reasons).
class Functor f => FunctorM' f where dist' :: Monad m => f (m a) -> m (f a) fmapM' :: Monad m => (a -> m b) -> f a -> m (f b)
dist' = fmapM' id fmapM' f = dist' . fmap f
-- for example instance FunctorM' [] where dist' = sequence fmapM' = mapM
Does anyone else have any comments on the suggestions from Iavor and Thomas in this thread? I'm happy to make changes, but only if there's a concensus. The proposals so far seems to be 1) add dist method 2a) make Functor a superclass of FunctorM 2b) make Functor a *sub*class of FunctorM 2c) make Functor a subclass of Monad 2d) make Functor a superclass of Monad 3) rename FunctorM class to ForEach 4) rename FunctorM module to Control.Monad.FunctorM(?) (1) is easy and not controversial (but is 'dist' the best name?). AFAICT, 2a, 2b, 2c, and 2d have all been suggested (eg. the quoted message above suggests 2a, 2b and 2c). Perhaps some of the suggestions were typos, but at this point I'm a bit confused! Cheers, Simon

On Wed, 23 Mar 2005 09:49:43 -0000, Simon Marlow
Does anyone else have any comments on the suggestions from Iavor and Thomas in this thread? I'm happy to make changes, but only if there's a concensus. The proposals so far seems to be
1) add dist method 2a) make Functor a superclass of FunctorM 2b) make Functor a *sub*class of FunctorM 2c) make Functor a subclass of Monad 2d) make Functor a superclass of Monad 3) rename FunctorM class to ForEach 4) rename FunctorM module to Control.Monad.FunctorM(?)
(1) is easy and not controversial (but is 'dist' the best name?).
AFAICT, 2a, 2b, 2c, and 2d have all been suggested (eg. the quoted message above suggests 2a, 2b and 2c). Perhaps some of the suggestions were typos, but at this point I'm a bit confused!
I think 2c) and 2d) are no go since they violate the Haskell Report. Apart from that I support 1). Just my 2 öre. /Josef

What about pre-monads, co-monads, and monoids? (insn't a monad just a monoid where the operators are natural transformations?)... What is the next category after monads? Wouldn't a "category" library make sense, with a larger range of categories, and with "class" constraints enforced so, if category theory says a monad must be a functor - then we should have: class CategoricalFunctor m => CategoricalMonad m ... which gets the compiler to 'proove' the relationship for all instances. Keean. Josef Svenningsson wrote:
On Wed, 23 Mar 2005 09:49:43 -0000, Simon Marlow
wrote: Does anyone else have any comments on the suggestions from Iavor and Thomas in this thread? I'm happy to make changes, but only if there's a concensus. The proposals so far seems to be
1) add dist method 2a) make Functor a superclass of FunctorM 2b) make Functor a *sub*class of FunctorM 2c) make Functor a subclass of Monad 2d) make Functor a superclass of Monad 3) rename FunctorM class to ForEach 4) rename FunctorM module to Control.Monad.FunctorM(?)
(1) is easy and not controversial (but is 'dist' the best name?).
AFAICT, 2a, 2b, 2c, and 2d have all been suggested (eg. the quoted message above suggests 2a, 2b and 2c). Perhaps some of the suggestions were typos, but at this point I'm a bit confused!
I think 2c) and 2d) are no go since they violate the Haskell Report. Apart from that I support 1).
Just my 2 öre.
/Josef _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

"Simon Marlow"
Does anyone else have any comments on the suggestions from Iavor and Thomas in this thread? I'm happy to make changes, but only if there's a concensus. The proposals so far seems to be
2d) make Functor a superclass of Monad
I like this one! -- Shae Matijs Erisson - http://www.ScannedInAvian.com/ - Sockmonster once said: You could switch out the unicycles for badgers, and the game would be the same.

On Wed, Mar 23, 2005 at 09:49:43AM -0000, Simon Marlow wrote:
Does anyone else have any comments on the suggestions from Iavor and Thomas in this thread? I'm happy to make changes, but only if there's a concensus. The proposals so far seems to be
1) add dist method 2a) make Functor a superclass of FunctorM 2b) make Functor a *sub*class of FunctorM 2c) make Functor a subclass of Monad 2d) make Functor a superclass of Monad 3) rename FunctorM class to ForEach 4) rename FunctorM module to Control.Monad.FunctorM(?)
(1) is easy and not controversial (but is 'dist' the best name?).
fsequence:sequence = fmapM:mapM = fmap:map ? As long as we remember that it's not always a distributive law (join law fails, e.g. for []), and fmapM doesn't always define a functor (doesn't preserve composition of Kleisli arrows). 2a) is needed to provide the default definition fmapM f = fsequence . fmap f 2b-d) will break Haskell 98 programs. The placement in the hierarchy is a bit wierd. Another possibility (that you suggested earlier) is Data.Functor.

I am in favor of adding fsequence :: (Monad m,FunctorM f) => f (m a) -> m (f a) fsequence_ :: (Monad m,FunctorM f) => f (m a) -> m () fsequence = fmapM id fsequence_ = fmapM_ id John -- John Meacham - ⑆repetae.net⑆john⑈

Hello,
On Wed, 23 Mar 2005 15:51:04 +0000, Ross Paterson
On Wed, Mar 23, 2005 at 09:49:43AM -0000, Simon Marlow wrote:
Does anyone else have any comments on the suggestions from Iavor and Thomas in this thread? I'm happy to make changes, but only if there's a concensus. The proposals so far seems to be
1) add dist method 2a) make Functor a superclass of FunctorM 2b) make Functor a *sub*class of FunctorM 2c) make Functor a subclass of Monad 2d) make Functor a superclass of Monad
3) rename FunctorM class to ForEach I was suggesting here that we rename the method to "forEach" and swap
Just to avoid confusion I think the suggestions were: class Functor f => Monad f where ... class Functor f => FunctorM f where ... I know the first one differs from the Haskell report, but perhaps this is a flaw in the library design that should be fixed. The practical concern is compatability with existing programs, but if a program breaks at all it should be very easy to fix --- at most one line per monad instance, and a Haskell implementation will be able to pinpoint the missing instances. the order of the arguments. The reason I suggested this is that I find myself writing code like this a lot: mapM (\x -> do ... some monadic ... ... code goes here ... ) xs this look better in this form: forEach xs (\x -> do ... some monadic ... ... code goes here ... )
As long as we remember that it's not always a distributive law (join law fails, e.g. for []),
I am not familiar with this law, what does it say?
and fmapM doesn't always define a functor (doesn't preserve composition of Kleisli arrows).
I am not sure what you mean, why should "fmapM" define a functor? The two constructors "f" and "m" should already be functors.
The placement in the hierarchy is a bit wierd. Another possibility (that you suggested earlier) is Data.Functor.
I have no strong feelings about where things are placed in the hirarchy, but lately everything seems to end up under "Data". If we want to have things that are relevant to just functors perhaps we should place them in a file (or directory) called "Functor". Same for "Monad". The good thing about using esoteric names is that they are not likely to clash with anything :-) -Iavor

On Wed, Mar 23, 2005 at 01:28:28PM -0800, Iavor Diatchki wrote:
3) rename FunctorM class to ForEach I was suggesting here that we rename the method to "forEach" and swap the order of the arguments. The reason I suggested this is that I find myself writing code like this a lot:
mapM (\x -> do ... some monadic ... ... code goes here ... ) xs
this look better in this form:
forEach xs (\x -> do ... some monadic ... ... code goes here ... )
why not just define a normal function: forEach = flip fmapM ? Calling the whole class ForEach makes the connection to Functor/Monad less clear, and renaming only the method seems rather inconsequent to me. Remi P.S. Then we can finally start a Holy War about the One True "Brace" Style. I'm usually writing: forEach xs $ \x -> do ... ;) -- Nobody can be exactly like me. Even I have trouble doing it.

On Thu, Mar 24, 2005 at 12:58:19AM +0100, Remi Turk wrote:
On Wed, Mar 23, 2005 at 01:28:28PM -0800, Iavor Diatchki wrote:
3) rename FunctorM class to ForEach I was suggesting here that we rename the method to "forEach" and swap the order of the arguments. The reason I suggested this is that I find myself writing code like this a lot:
mapM (\x -> do ... some monadic ... ... code goes here ... ) xs
this look better in this form:
forEach xs (\x -> do ... some monadic ... ... code goes here ... )
why not just define a normal function: forEach = flip fmapM ? Calling the whole class ForEach makes the connection to Functor/Monad less clear, and renaming only the method seems rather inconsequent to me.
Especially since when working on non-lists, forEach is not at all obvious. On a tangent, I was thinking that fsequence is a nice way to commute monads. of course, not all monads can universally commute with every other monad, but those that can can be made an instance of FunctorM giving us a nice reusable routine... fsequence :: f (m a) -> m (f a) Monads that are an instance of FunctorM can always be pushed inside of an arbitrary monad. Control.Monad.Identity can obviously be made an instance, can any of the other standard mtl monads? We should provide those instances. John -- John Meacham - ⑆repetae.net⑆john⑈

On Wed, 23 Mar 2005 17:11:21 -0800, John Meachamwrote: > On a tangent, I was thinking that fsequence is a nice way to commute > monads. of course, not all monads can universally commute with every > other monad, but those that can can be made an instance of FunctorM > giving us a nice reusable routine... > > fsequence :: f (m a) -> m (f a) > > Monads that are an instance of FunctorM can always be pushed > inside of an arbitrary monad. > > Control.Monad.Identity can obviously be made an instance, > can any of the other standard mtl monads? > We should provide those instances. The following distributive laws [1] might be postulated: 1) fsequence . fmap return === return 2) fsequence . return === fmap return 3) fsequence . fmap join === join . fmap fsequence . fsequence Identity, Maybe, Either e and Writer w (for monoids w) are perfect instances; the list monad doesn't obey law 3. I don't believe any of the monads that is based a function type can be made an instance of FunctorM, and if we impose additional restrictions, such as a finite domain in case of the reader monad, we lose laws 2 and 3. The laws 1 and 3 can be formulated without requiring f to be a monad (and law 2 only needs return), but Array i, the only non-monad that can be made a FunctorM I'm currently aware of, only satisfies law 1. Thomas [1] Barr, Wells: Toposes, Triples and Theories http://www.cwru.edu/artsci/math/wells/pub/ttt.html, p. 298

On Thu, Mar 24, 2005 at 10:24:50AM +0100, Thomas Jäger wrote:
The following distributive laws [1] might be postulated: 1) fsequence . fmap return === return 2) fsequence . return === fmap return 3) fsequence . fmap join === join . fmap fsequence . fsequence
also 4) fsequence . join === fmap join . fsequence . fmap fsequence These are all necessary for the composition to be a monad.
Identity, Maybe, Either e and Writer w (for monoids w) are perfect instances; the list monad doesn't obey law 3. I don't believe any of the monads that is based a function type can be made an instance of FunctorM, and if we impose additional restrictions, such as a finite domain in case of the reader monad, we lose laws 2 and 3.
M1 o M2 is a monad if M2 is one of those you mentioned, or if M1 is a reader monad.
The laws 1 and 3 can be formulated without requiring f to be a monad (and law 2 only needs return),
Yes, laws 1 and 3 are equivalent to saying that fmapM defines a functor on the Kleisli category, i.e. fmapM return = return fmapM (f >>> g) = fmapM f >>> fmapM g where (>>>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c (f >>> g) a = f a >>= g
but Array i, the only non-monad that can be made a FunctorM I'm currently aware of, only satisfies law 1.
Isn't Array i a reader monad with a finite domain? (i.e. return fills the array with copies, and join selects the diagonal)
[1] Barr, Wells: Toposes, Triples and Theories http://www.cwru.edu/artsci/math/wells/pub/ttt.html, p. 298

Iavor Diatchki wrote:
Just to avoid confusion I think the suggestions were: class Functor f => Monad f where ... class Functor f => FunctorM f where ...
I know the first one differs from the Haskell report, but perhaps this is a flaw in the library design that should be fixed.
Yes, I think this should be fixed, and perhaps it could be done in a backward compatible way? If classes were allowed to declare default methods for superclasses, then you could have class Functor f where fmap :: ... class Functor m => Monad m where ...the usual stuff... fmap = liftM Then declaring instance Monad T where ... for some T, would implicitly introduce an instance Functor T, if it is not defined explicitly... -- Thomas H

On Thursday 24 March 2005 04:14, Thomas Hallgren wrote:
Iavor Diatchki wrote:
Just to avoid confusion I think the suggestions were: class Functor f => Monad f where ... class Functor f => FunctorM f where ...
I know the first one differs from the Haskell report, but perhaps this is a flaw in the library design that should be fixed.
Yes, I think this should be fixed, and perhaps it could be done in a backward compatible way? If classes were allowed to declare default methods for superclasses, then you could have
class Functor f where fmap :: ... class Functor m => Monad m where ...the usual stuff... fmap = liftM
Then declaring
instance Monad T where ...
for some T, would implicitly introduce an instance Functor T, if it is not defined explicitly...
Robert Will has written a fully specified proposal for this. He calls it "delayed method definition", see http://www.stud.tu-ilmenau.de/~robertw/dessy/fun/, sections 4.3.1 and 4.3.2. Looks like a really good idea to me. Ben

Thomas Hallgren wrote:
If classes were allowed to declare default methods for superclasses...
Benjamin Franksen wrote:
Robert Will has written a fully specified proposal for this. He calls it "delayed method definition", see http://www.stud.tu-ilmenau.de/~robertw/dessy/fun/, sections 4.3.1 and 4.3.2.
Looks like a really good idea to me.
Me too. I find the need to define superclass default methods all the time. That is an upward-compatible change that is very intuitive. -Yitz

On Thu, Mar 24, 2005 at 12:39:40PM +0100, Benjamin Franksen wrote:
On Thursday 24 March 2005 04:14, Thomas Hallgren wrote:
Yes, I think this should be fixed, and perhaps it could be done in a backward compatible way? If classes were allowed to declare default methods for superclasses, then you could have
class Functor f where fmap :: ... class Functor m => Monad m where ...the usual stuff... fmap = liftM
Then declaring
instance Monad T where ...
for some T, would implicitly introduce an instance Functor T, if it is not defined explicitly...
Robert Will has written a fully specified proposal for this. He calls it "delayed method definition", see http://www.stud.tu-ilmenau.de/~robertw/dessy/fun/, sections 4.3.1 and 4.3.2.
I'd prefer something more modest: classes could contain default methods for their superclasses, but only for a superclass with exactly the same arguments, as in class Eq a => Ord a class Functor m => Monad m so there'd be no need for a special device to specify which class the default method is for. This would lose things like the ability to specify general equality on Collections in the class class (Eq a, Eq (coll a)) => Collection coll a but I think that's stretching subtyping a bit. It would also be simpler to keep the H98 rule for instances, namely that an instance of class C can contain only definitions of methods of class C.
participants (12)
-
Benjamin Franksen
-
Iavor Diatchki
-
John Meacham
-
Josef Svenningsson
-
Keean Schupke
-
Remi Turk
-
Ross Paterson
-
Shae Matijs Erisson
-
Simon Marlow
-
Thomas Hallgren
-
Thomas Jäger
-
Yitzchak Gale