
I find myself dismayed that the mathematical relationship between Monads and Functors isn't available in Haskell98; if I use fmap in a Monad m=>... typed function, I get an extra Functor m required in the context, but not only are all mathematical monads functors, any instance of Monad has fmap in the form (>>= return . f), so it's annoying. There has been discussion in the past about whether Monad should be defined as
class Functor m => Monad m where ...
(or some other means of making all Monads instances of Functor) I think the general consensus on the libraries mailing list in this thread http://thread.gmane.org/gmane.comp.lang.haskell.libraries/2815/focus=2815 which refers to this: http://www.cs.chalmers.se/~rjmh/Haskell/Messages/Display.cgi?id=444 was that it would be a good thing, but it breaks Haskell98 programmes. Surely Haskell' can get this right? On haskell prime I can find http://thread.gmane.org/gmane.comp.lang.haskell.prime/1328/focus=1427 which agrees with me, but I don't see a definite decision either there or in the Trac. I'd favour the above method as most conservative in terms of the language, but I'm not too fussed how it happens. Jón -- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk

jon.fairbairn:
I find myself dismayed that the mathematical relationship between Monads and Functors isn't available in Haskell98; if I use fmap in a Monad m=>... typed function, I get an extra Functor m required in the context, but not only are all mathematical monads functors, any instance of Monad has fmap in the form (>>= return . f), so it's annoying.
For interest. Here's the defn in the Gofer prelude from 1994: class Functor f where map :: (a -> b) -> (f a -> f b) class Functor m => Monad m where result :: a -> m a join :: m (m a) -> m a bind :: m a -> (a -> m b) -> m b join x = bind x id x `bind` f = join (map f x) class Monad m => Monad0 m where zero :: m a http://www.cse.unsw.edu.au/~dons/data/cc.prelude -- Don

If I remember right, Functor was a superclass of Monad in Haskell early on, but it was taken away. I think this was the wrong decision, but I seem to remember that the rationale was that it would be too onerous to require programmers to write a Functor instance every time they want a Monad instance. Bah! -- Lennart On Aug 13, 2006, at 21:39 , Donald Bruce Stewart wrote:
jon.fairbairn:
I find myself dismayed that the mathematical relationship between Monads and Functors isn't available in Haskell98; if I use fmap in a Monad m=>... typed function, I get an extra Functor m required in the context, but not only are all mathematical monads functors, any instance of Monad has fmap in the form (>>= return . f), so it's annoying.
For interest. Here's the defn in the Gofer prelude from 1994:
class Functor f where map :: (a -> b) -> (f a -> f b)
class Functor m => Monad m where result :: a -> m a join :: m (m a) -> m a bind :: m a -> (a -> m b) -> m b
join x = bind x id x `bind` f = join (map f x)
class Monad m => Monad0 m where zero :: m a
http://www.cse.unsw.edu.au/~dons/data/cc.prelude
-- Don _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

On 8/13/06, Lennart Augustsson
If I remember right, Functor was a superclass of Monad in Haskell early on, but it was taken away. I think this was the wrong decision, but I seem to remember that the rationale was that it would be too onerous to require programmers to write a Functor instance every time they want a Monad instance. Bah!
There was a proposal (Re: [Haskell] A collection of related proposals
regarding monads) to allow instance definitions to be combined,
allowing a more fine-grained hierarchy (Functor, PointedFunctor,
Applicative, Monad) without changing the instance definition
requirements.
In my opinion, an instance definition of a subclass should allow the
superclass's methods to be defined as if they were part of the
subclass, e.g.:
instance Monad [] where
fmap = map
return x = [x]
join = concat
It's so pretty! (But a little inefficient. You'd probably want to
define ap/lift2 in there.)
--
Taral

Hello Taral, Monday, August 14, 2006, 9:02:58 AM, you wrote:
In my opinion, an instance definition of a subclass should allow the superclass's methods to be defined as if they were part of the subclass, e.g.:
instance Monad [] where fmap = map return x = [x] join = concat
i support this idea. in my Streams library i forced now to group and order function definitions according to type classes to which they are split -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 2006-08-14 at 12:03+0400 Bulat Ziganshin wrote:
Hello Taral,
Monday, August 14, 2006, 9:02:58 AM, you wrote:
In my opinion, an instance definition of a subclass should allow the superclass's methods to be defined as if they were part of the subclass, e.g.:
instance Monad [] where fmap = map return x = [x] join = concat
i support this idea. [...]
I'm not sure it's quite right. Surely it only makes sense if it defines all the (necessary) superclass methods -- in other words, what you are doing is defining an instance, just omitting the "instance Functor []" line, which doesn't seem like a great advantage. If we are going to play around with this stuff, here's another suggestion that solves my original problem more neatly: In a class declaration, a superclass context is a requirement that instances of the class have instances of the superclass; this is similar to the type declarations of the methods. We could have had class Monad m where instance Functor m (>>=):: ... instead of class Functor m => Monad m where (>>=):: ... of course, there's no reason to do that, but what I'm proposing is that we allow default instance declarations in class declarations in much the same way as default methods:
class Functor m => Monad m where (>>=):: ... return:: ... join:: ... instance Functor m where fmap f = (>>= return . f)
This shouldn't be hard to implement: all the compiler has to do when reading an instance declaration for Monad is to generate an instance declaration for Functor, substituting the espression for m that comes from the instance declaration for Monad. I don't know whether there's anything to be gained by adding the option of overriding the default inside an instance declaration:
instance Monad [] where return x = [x] join = concat instance Functor [] where fmap = map
but clearly a top-level instance declaration would override the default anyway. -- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk

Hello Jon, Monday, August 14, 2006, 1:49:58 PM, you wrote:
instance Monad [] where fmap = map return x = [x] join = concat
i support this idea. [...]
I'm not sure it's quite right. Surely it only makes sense if it defines all the (necessary) superclass methods -- in other words, what you are doing is defining an instance, just omitting the "instance Functor []" line, which doesn't seem like a great advantage.
This shrinks size of code that is especially important when writing a lot of small instances. second, it allows me to think that all the methods belongs to the same class instead of specifying each and every class: class Show s => Stream s where sTell :: .. class Stream s => OutputStream s where sPutChar :: .. instance Show s where show = .. instance Stream s where sTell = .. instance OutputStream s where sPutChar = .. i might prefer to write just instance OutputStream s where sPutChar = .. sTell = .. show = .. - and as you can see i also changed the ordering/grouping of operations. of course it's just syntax sugar, but i like it - it will shrink class declarations and bring them closer to OOP style when derived class also "owns" all the methods of base classes
If we are going to play around with this stuff, here's another suggestion that solves my original problem more neatly:
In a class declaration, a superclass context is a requirement that instances of the class have instances of the superclass; this is similar to the type declarations of the methods. We could have had
class Monad m where instance Functor m (>>=):: ...
instead of
class Functor m => Monad m where (>>=):: ...
of course, there's no reason to do that, but what I'm proposing is that we allow default instance declarations in class declarations in much the same way as default methods:
class Functor m => Monad m where
i think, you mean:
class Monad m where instance Functor m where fmap f = (>>= return . f) (>>=):: ... return:: ... join:: ...
i support this too. but bringing these two ideas together the class declaration should look as class Functor m => Monad m where fmap f = (>>= return . f) (>>=):: ... return:: ... join:: ... and instance declaration should be: instance Monad [] where fmap = map return x = [x] join = concat instead of:
instance Monad [] where return x = [x] join = concat instance Functor [] where fmap = map
this proposal should be named as subj, independent of syntax form used -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 8/14/06, Jon Fairbairn
of course, there's no reason to do that, but what I'm proposing is that we allow default instance declarations in class declarations in much the same way as default methods:
I just realized that default superclass methods have a small problem:
module A contains instance Monad []
module B contains instance Functor []
module C imports A and B.
Do we complain about a duplicate instance declarations? If not, does
the use of fmap in A use the default definition, or the one from B?
--
Taral

Hello Taral, Monday, August 14, 2006, 3:34:29 PM, you wrote:
On 8/14/06, Jon Fairbairn
wrote: of course, there's no reason to do that, but what I'm proposing is that we allow default instance declarations in class declarations in much the same way as default methods:
I just realized that default superclass methods have a small problem:
module A contains instance Monad [] module B contains instance Functor [] module C imports A and B.
Do we complain about a duplicate instance declarations?
yes. after all, this is just syntax sugar of giving both declarations: instance Monad [] where fmap = map return = (:[]) is equivalent to instance Functor [] where fmap = map instance Monad [] where return = (:[]) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Mon, Aug 14, 2006 at 12:02:58AM -0500, Taral wrote:
In my opinion, an instance definition of a subclass should allow the superclass's methods to be defined as if they were part of the subclass, e.g.:
instance Monad [] where fmap = map return x = [x] join = concat
It's so pretty! (But a little inefficient. You'd probably want to define ap/lift2 in there.)
This is actually a big can of worms to allow despite looking simple at first. it was discussed during the class aliases thread. John -- John Meacham - ⑆repetae.net⑆john⑈

Hello, I know we have discussed this before, I am just posting this so that it does not appear that the "community" does not care. Here is a summary of why I think Functor should be a super class of Monad. The extra code that a programmer would have to write is very small:
instance Functor MyMonad where fmap f m = do { x <- m; return (f x) } (or use liftM)
Furthermore, I don't think I have defined a new monad for ages,
instead I use a library which already has all the necessary instances.
The benefit of having Functor as a super class of Monad shows up in
polymorhic code: we can reduce contexts like '(Functor m, Monad m)' to
just 'Monad m'. Currently I sometimes use 'liftM' (or the 'do' form
like above) instead of using 'fmap' just to avoid having the extra
constraints, which probably makes my code less readable.
-Iavor
On 8/13/06, Lennart Augustsson
If I remember right, Functor was a superclass of Monad in Haskell early on, but it was taken away. I think this was the wrong decision, but I seem to remember that the rationale was that it would be too onerous to require programmers to write a Functor instance every time they want a Monad instance. Bah!
-- Lennart

Jon Fairbairn wrote:
There has been discussion in the past about whether Monad should be defined as
class Functor m => Monad m where ...
It's more complicated now that we have Ross Patterson's "Applicative". http://haskell.org/ghc/dist/current/docs/libraries/base/Control-Applicative.... The correct decl I think is this: class Applicative m => Monad m where -- remove "return" ... and changing the names of the Applicative functions: class Functor f => Applicative f where return :: a -> f a ap :: f (a -> b) -> f a -> f b This would mean moving Applicative into the Prelude. I think "joining up the classes" is a good idea, and there may be other cases too. "Alternative" and "MonadPlus"? -- Ashley Yakeley

On 2006-08-25 at 19:09PDT Ashley Yakeley wrote:
Jon Fairbairn wrote:
There has been discussion in the past about whether Monad should be defined as
class Functor m => Monad m where ...
It's more complicated now that we have Ross Patterson's "Applicative".
http://haskell.org/ghc/dist/current/docs/libraries/base/Control-Applicative....
FSVO "complicated"... it looks like a Good Thing to me, although I don't like the names much. [It would be nice if there were a bit more commentary in the Haddock -- referring to a paper is fine, but in day to day programming a scan through several modules to find what one wants is hampered by having to step out to read the papers.]
The correct decl I think is this:
class Applicative m => Monad m where -- remove "return" ...
and changing the names of the Applicative functions:
class Functor f => Applicative f where return :: a -> f a ap :: f (a -> b) -> f a -> f b
Better, I think, and though I can see a case for using “unit” instead of return (as it's more neutral; “return (+1) <*> [1..10]” looks a bit odd) using “return” would be less of a shock to the system.
This would mean moving Applicative into the Prelude.
Good, though I'm still very much in favour of moving as much out of the Prelude as possible.
I think "joining up the classes" is a good idea,
Definitely -- as is slicing them into finer layers (of which this is also an example). -- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk

Jon Fairbairn wrote:
On 2006-08-25 at 19:09PDT Ashley Yakeley wrote:
Jon Fairbairn wrote:
There has been discussion in the past about whether Monad should be defined as
class Functor m => Monad m where ...
It's more complicated now that we have Ross Patterson's "Applicative".
http://haskell.org/ghc/dist/current/docs/libraries/base/Control-Applicative....
FSVO "complicated"... it looks like a Good Thing to me, although I don't like the names much.
Yes, I liked the original name 'Idiom' better. It bears some similarity to 'Monad' in that it has this mysterious quality that immediately made me curious... 8-) 'Applicative' might be somewhat more descriptive, and thus slightly better from a purely technical POV, however, it is quite an ugly name for such a beautiful concept. Cheers, Ben

Jon Fairbairn wrote:
I think "joining up the classes" is a good idea,
Definitely -- as is slicing them into finer layers (of which this is also an example).
I have added a ticket for "joined-up classes": http://hackage.haskell.org/trac/haskell-prime/ticket/113 -- Ashley Yakeley Seattle WA

Ashley Yakeley wrote:
Jon Fairbairn wrote:
I think "joining up the classes" is a good idea,
Definitely -- as is slicing them into finer layers (of which this is also an example).
I have added a ticket for "joined-up classes":
So, with this arrangement, quite a lot of library functionality is potentially affected (good!), especially if Traversable is also kicking around, allowing us crush :: (Monoid t, Traversable f) => (s -> t) -> f s -> t (1) Which library functions should just be binned? (2) Which library functions should be retained but generalised (eg, working for Applicative rather than Monad, or any Traversable f rather than just [])? In particular, what happens to mapM? Of course, there's a danger that such moves will raise the level of sophistication required to get to grips with the library (revisiting the map versus fmap debate). I'm very much in favour of "joined-up classes", but it does leave us with quite a lot to work through. How to proceed? What are the guidelines? Meanwhile, I don't suppose you'll let me have the 'idiom bracket' notation, [| .. |] or some such, with [| f a1 .. an |] expanding to the old Welsh program (ap is the Welsh patronymic prefix) return f `ap` a1 `ap` .. `ap` an Thought I might be pushing my luck. I know, it's frivolous extra syntax serving only to improve the signal-to-noise ratio of code by a constant factor, and that ain't enough. All the best Conor This message has been checked for viruses but the contents of an attachment may still contain software viruses, which could damage your computer system: you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation.

On Sat, Sep 30, 2006 at 12:41:42PM +0100, Conor McBride wrote:
So, with this arrangement, quite a lot of library functionality is potentially affected (good!), especially if Traversable is also kicking around, allowing us
crush :: (Monoid t, Traversable f) => (s -> t) -> f s -> t
(1) Which library functions should just be binned? (2) Which library functions should be retained but generalised (eg, working for Applicative rather than Monad, or any Traversable f rather than just [])? In particular, what happens to mapM?
For some possible answers, see http://www.haskell.org/ghc/dist/current/docs/libraries/base/Data-Foldable.ht... http://www.haskell.org/ghc/dist/current/docs/libraries/base/Data-Traversable... coming soon to all Haskell implementations. For crush, there's foldMap :: (Foldable f, Monoid m) => (a -> m) -> f a -> m Ashley's quite ambitious to push this refactoring of Monad for Haskell', since there is limited experience with Applicative, and class system changes that might help with fine-grained hierarchies are unlikely to be available, but I wish him luck. I've collected several such issues on the StandardClasses page.

Ross Paterson wrote:
Ashley's quite ambitious to push this refactoring of Monad for Haskell', since there is limited experience with Applicative, and class system changes that might help with fine-grained hierarchies are unlikely to be available, but I wish him luck.
I agree that a language extension for superclass defaults is not on the cards for Haskell Prime, but really, just how hard is it to write the necessary instances? Especially as we can provide helper functions. -- Ashley Yakeley Seattle WA
participants (11)
-
Ashley Yakeley
-
Benjamin Franksen
-
Bulat Ziganshin
-
Conor McBride
-
dons@cse.unsw.edu.au
-
Iavor Diatchki
-
John Meacham
-
Jon Fairbairn
-
Lennart Augustsson
-
Ross Paterson
-
Taral