Why the reluctance to introduce the Functor requirement on Monad?

Hi cafe! I feel a bit like I'm speaking out of turn for bringing this up -- and I'm sure it must have been brought up many times before -- but I hope there can be something fruitful had from a discussion. In my travels I've read several people with much better grasp of Haskell than I have mention -- with a sad sigh of resignation -- that functions like liftM and return abound because some Monads don't state their fulfillment of Functor (or Applicative, but that's even more recent), and thus we can't use fmap/<$> or pure. I understand a motivation might be that code would break if the former lot were removed, but surely they could shifted to the latter (and the former simply be defined as the latter). It might be a very large effort, I suppose, to comb through the standard libraries and make everything compile again, but is there something else I'm surely missing? Cheers, A

On 21 July 2011 11:10, Arlen Cuss
Hi cafe!
I feel a bit like I'm speaking out of turn for bringing this up -- and I'm sure it must have been brought up many times before -- but I hope there can be something fruitful had from a discussion.
In my travels I've read several people with much better grasp of Haskell than I have mention -- with a sad sigh of resignation -- that functions like liftM and return abound because some Monads don't state their fulfillment of Functor (or Applicative, but that's even more recent), and thus we can't use fmap/<$> or pure.
Well, for fmap vs liftM, you have that liftM is automatically defined for you rather than needing to make the Functor instance, so if you're quickly defining a Monad for internal use then you can just use liftM, etc. without needing to also make Functor and Applicative instances (note that AFAIK, return and pure are the same thing, in that return isn't automatically defined like liftM is). That said, stylistically speaking when I'm writing monadic code, I tend to prefer to use liftM rather than fmap as a personal preference. Note that if you're writing polymorphic Monad functions (i.e. you have "Monad m => ..." in your type signature rather than a specific Monad) then you have to use liftM and the like because we currently don't have that Monad implies Functor.
I understand a motivation might be that code would break if the former lot were removed, but surely they could shifted to the latter (and the former simply be defined as the latter). It might be a very large effort, I suppose, to comb through the standard libraries and make everything compile again, but is there something else I'm surely missing?
It would remove backwards-compatability if/when the typeclass hierarchy is fixed, and thus a lot of code would break; as such I believe that it _is_ on the table for a future version of Haskell' that will not be 100% backwards compatible with Haskell98 and Haskell2010. The big effort here would be with user code and packages, rather than standard libraries (as the former presumably has more LOC than the latter). -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Thu, Jul 21, 2011 at 8:31 AM, Ivan Lazar Miljenovic
Well, for fmap vs liftM, you have that liftM is automatically defined for you rather than needing to make the Functor instance, so if you're quickly defining a Monad for internal use then you can just use liftM, etc. without needing to also make Functor and Applicative instances (note that AFAIK, return and pure are the same thing, in that return isn't automatically defined like liftM is).
Note that even if we had "class Applicative m => Monad m where ...", we could say data X a = ... instance Functor X where fmap = liftM instance Applicative X where pure = return (<*>) = ap instance Monad X where return = ... x >>= f = ... So you just need five more lines of boilerplate to define both Functor and Applicative. Cheers, -- Felipe.

Would it be theoretically possible/convenient to be able to put boilerplate like this in class definitions? On Thu, Jul 21, 2011 at 5:58 AM, Felipe Almeida Lessa < felipe.lessa@gmail.com> wrote:
On Thu, Jul 21, 2011 at 8:31 AM, Ivan Lazar Miljenovic
wrote: Well, for fmap vs liftM, you have that liftM is automatically defined for you rather than needing to make the Functor instance, so if you're quickly defining a Monad for internal use then you can just use liftM, etc. without needing to also make Functor and Applicative instances (note that AFAIK, return and pure are the same thing, in that return isn't automatically defined like liftM is).
Note that even if we had "class Applicative m => Monad m where ...", we could say
data X a = ...
instance Functor X where fmap = liftM
instance Applicative X where pure = return (<*>) = ap
instance Monad X where return = ... x >>= f = ...
So you just need five more lines of boilerplate to define both Functor and Applicative.
Cheers,
-- Felipe.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 24 July 2011 00:49, Sebastien Zany
Would it be theoretically possible/convenient to be able to put boilerplate like this in class definitions?
Not really: what happens for Functors that aren't Monads? Also, for some Monads there may be a more efficient definition of fmap than using liftM, so even an automatic reverse instance wouldn't always be wanted. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

I was thinking the reverse. We can already give default implementations of class operations that can be overridden by giving them explicitly when we declare instances, so why shouldn't we be able to give default implementations of operations of more general classes, which could be overridden by a separate instance declaration for these?
Then I could say something like "a monad is also automatically a functor with fmap by default given by..." and if I wanted to give a more efficient fmap for a particular monad I would just instantiate it as a functor explicitly.
On Jul 23, 2011, at 3:19 PM, Ivan Lazar Miljenovic
On 24 July 2011 00:49, Sebastien Zany
wrote: Would it be theoretically possible/convenient to be able to put boilerplate like this in class definitions?
Not really: what happens for Functors that aren't Monads? Also, for some Monads there may be a more efficient definition of fmap than using liftM, so even an automatic reverse instance wouldn't always be wanted.
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On 25 July 2011 13:50, Sebastien Zany
I was thinking the reverse. We can already give default implementations of class operations that can be overridden by giving them explicitly when we declare instances, so why shouldn't we be able to give default implementations of operations of more general classes, which could be overridden by a separate instance declaration for these?
Then I could say something like "a monad is also automatically a functor with fmap by default given by..." and if I wanted to give a more efficient fmap for a particular monad I would just instantiate it as a functor explicitly.
I believe this has been proposed before, but a major problem is that you cannot do such overriding. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Out of (perhaps naive) curiosity, what difficulties does allowing such
overriding introduce? Wouldn't the module system prevent the ambiguity
of which implementation to use?
August Sodora
augsod@gmail.com
(201) 280-8138
On Sun, Jul 24, 2011 at 11:55 PM, Ivan Lazar Miljenovic
On 25 July 2011 13:50, Sebastien Zany
wrote: I was thinking the reverse. We can already give default implementations of class operations that can be overridden by giving them explicitly when we declare instances, so why shouldn't we be able to give default implementations of operations of more general classes, which could be overridden by a separate instance declaration for these?
Then I could say something like "a monad is also automatically a functor with fmap by default given by..." and if I wanted to give a more efficient fmap for a particular monad I would just instantiate it as a functor explicitly.
I believe this has been proposed before, but a major problem is that you cannot do such overriding.
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, 2011-07-25 at 00:11 -0400, August Sodora wrote:
Out of (perhaps naive) curiosity, what difficulties does allowing such overriding introduce? Wouldn't the module system prevent the ambiguity of which implementation to use?
August Sodora augsod@gmail.com (201) 280-8138
class A a where a :: a class A a => B b where b :: b a = b class A a => C c where c :: c a = c data BC = B | C deriving Show instance B BC where b = B instance C BC where c = C show (a :: BC) == ??? Regards

On Jul 25, 2011, at 7:38 PM, Maciej Marcin Piechotka wrote:
On Mon, 2011-07-25 at 00:11 -0400, August Sodora wrote:
Out of (perhaps naive) curiosity, what difficulties does allowing such overriding introduce? Wouldn't the module system prevent the ambiguity of which implementation to use?
August Sodora augsod@gmail.com (201) 280-8138
class A a where a :: a
class A a => B b where b :: b
a = b
class A a => C c where c :: c
a = c
data BC = B | C deriving Show
instance B BC where b = B
instance C BC where c = C
show (a :: BC) == ???
I would imagine this causing a compiler error, such as: Foo.hs:16:10: Duplicate implied instance declarations: instance A BC -- Defined at Foo.hs:16:10-13 instance A BC -- Defined at Foo.hs:19:10-13 Adding an explicit instance A BC would resolve this ambiguity.

My guess is that nobody has put forward a clear enough design that solves all the problems. In particular, orphan instances are tricky. Here's an example: module Prelude where class (Functor m, Applicative m) => Monad m where return :: a -> m a (>>=) :: m a -> (a -> m b) -> m b (>>) :: m a -> m b -> m b a >> b = a >>= const b pure = return (<*>) = ap fmap = liftM module X where data X a = ... module Y where instance Functor X where fmap = ... module Z where instance Monad X where return = ... (>>=) = ... -- default implementation of fmap brought in from Monad definition module Main where import X import Z foo :: X Int foo = ... bar :: X Int bar = fmap (+1) foo -- which implementation of fmap is used? The one from Y? -- ryan On Sun, Jul 24, 2011 at 8:55 PM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
On 25 July 2011 13:50, Sebastien Zany
wrote: I was thinking the reverse. We can already give default implementations of class operations that can be overridden by giving them explicitly when we declare instances, so why shouldn't we be able to give default implementations of operations of more general classes, which could be overridden by a separate instance declaration for these?
Then I could say something like "a monad is also automatically a functor with fmap by default given by..." and if I wanted to give a more efficient fmap for a particular monad I would just instantiate it as a functor explicitly.
I believe this has been proposed before, but a major problem is that you cannot do such overriding.
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I'll give my two cents about some design I've been thinking about. Instead
of trying to derive all instances automatically, the programmer should
explicitly tell them (so the problems about conflicting implementations
would be minimised). I attach a piece of code of what I think could be done:
instance Functor a <= Monad a where -- notice the reversed "<="
fmap = ...
from Monad MyMonad derive Functor MyMonad
With the from_derive_ clause, we are telling exactly from which "<="
declaration to pull the definition from. The part of "from" should have
already been written or derived, so we know exactly which instance the user
is speaking about.
More refinements to the syntax could be done, for example if we have:
instance Functor a <= Applicative a where
fmap = ..
instance Applicative a <= Monad a where
pure = ...
(<*>) = ...
Then, writing "from Monad MyMonad derive Functor MyMonad" would go through
the entire tree of "reverse instance declarations" and create instances for
Applicative, and from that a Functor one (of course, this should fail if we
have more than one path, then the user should write the path explicitly as
"from Monad M derive Applicative M; from Applicative M derive Functor M").
But it has the advantage of allowing later addition of classes in the path,
that would be derived when recompiling the code that uses it.
2011/7/25 Ryan Ingram
My guess is that nobody has put forward a clear enough design that solves all the problems. In particular, orphan instances are tricky.
Here's an example:
module Prelude where
class (Functor m, Applicative m) => Monad m where return :: a -> m a (>>=) :: m a -> (a -> m b) -> m b (>>) :: m a -> m b -> m b a >> b = a >>= const b
pure = return (<*>) = ap fmap = liftM
module X where data X a = ...
module Y where instance Functor X where fmap = ...
module Z where
instance Monad X where return = ... (>>=) = ... -- default implementation of fmap brought in from Monad definition
module Main where import X import Z
foo :: X Int foo = ...
bar :: X Int bar = fmap (+1) foo -- which implementation of fmap is used? The one from Y?
-- ryan
On Sun, Jul 24, 2011 at 8:55 PM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
On 25 July 2011 13:50, Sebastien Zany
wrote: I was thinking the reverse. We can already give default implementations of class operations that can be overridden by giving them explicitly when we declare instances, so why shouldn't we be able to give default implementations of operations of more general classes, which could be overridden by a separate instance declaration for these?
Then I could say something like "a monad is also automatically a functor with fmap by default given by..." and if I wanted to give a more efficient fmap for a particular monad I would just instantiate it as a functor explicitly.
I believe this has been proposed before, but a major problem is that you cannot do such overriding.
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com
_______________________________________________ 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

On Tue, Jul 26, 2011 at 1:01 PM, Alejandro Serrano Mena
I'll give my two cents about some design I've been thinking about. Instead of trying to derive all instances automatically, the programmer should explicitly tell them (so the problems about conflicting implementations would be minimised). I attach a piece of code of what I think could be done: instance Functor a <= Monad a where -- notice the reversed "<=" fmap = ... from Monad MyMonad derive Functor MyMonad With the from_derive_ clause, we are telling exactly from which "<=" declaration to pull the definition from. The part of "from" should have already been written or derived, so we know exactly which instance the user is speaking about. More refinements to the syntax could be done, for example if we have: instance Functor a <= Applicative a where fmap = .. instance Applicative a <= Monad a where pure = ... (<*>) = ... Then, writing "from Monad MyMonad derive Functor MyMonad" would go through the entire tree of "reverse instance declarations" and create instances for Applicative, and from that a Functor one (of course, this should fail if we have more than one path, then the user should write the path explicitly as "from Monad M derive Applicative M; from Applicative M derive Functor M"). But it has the advantage of allowing later addition of classes in the path, that would be derived when recompiling the code that uses it.
I want to support explicit intance derivation. But I'd like to suggest slightly less radical syntax extention: -- class definition: class Fuctor m => Monad m where return :: a -> m a (>>=) :: m a -> (a -> m b) -> m b (>>) :: m a -> m b -> m b join :: m (m a) -> m a -- default implementations: a >> b = a >>= (\_ -> b) a >>= f = join . fmap f $ a join a = a >>= id -- default instances: instance Functor m where fmap f a = a >>= (return . f) newtype Reader a b = Reader { runReader :: a -> b } -- instace declaration: instance Monad (Reader r) where return = Reader . const m >>= f = Reader $ \r -> runReader (f (runReader m r)) r deriving (Functor) So syntax changes are very minor. -- Victor Nazarov

On Jul 25, 2011, at 4:55 PM, Ryan Ingram wrote:
My guess is that nobody has put forward a clear enough design that solves all the problems. In particular, orphan instances are tricky.
Here's an example:
module Prelude where
class (Functor m, Applicative m) => Monad m where return :: a -> m a (>>=) :: m a -> (a -> m b) -> m b (>>) :: m a -> m b -> m b a >> b = a >>= const b
pure = return (<*>) = ap fmap = liftM
module X where data X a = ...
module Y where instance Functor X where fmap = ...
module Z where instance Monad X where return = ... (>>=) = ... -- default implementation of fmap brought in from Monad definition
module Main where import X import Z
foo :: X Int foo = ...
bar :: X Int bar = fmap (+1) foo -- which implementation of fmap is used? The one from Y?
I don't believe it would make orphan instances any trickier than they already are. If Functor m => Monad m, you can't have Monad m without Functor m, so module Z must introduce Functor m either implicitly or explicitly or it cannot compile. Viewed from outside a module, the problem is the same either way. I would propose that viewed from outside a module, an implicitly declared instance should be indistinguishable from an explicitly declared one, and within a module the implicit instance would be generated if and only if there is no overlapping instance in scope. An additional warning flag could be added to warn people who are worried about it that they have implicitly created an orphan instance for a superclass. The only real problem I see relating to orphans is in cases where old code declares an orphan Monad instance for a type without a Functor instances, something which I don't think happens very often (except perhaps with Either, but forcing a solution to that hornet's nest would be a Good Thing IMO). But either way, that breakage is more related to the superclass change than to any new means of declaring instances; even without the latter, the former would force those modules to introduce orphan Functor instances explicitly (or to introduce non-orphans somewhere to avoid doing so) -- James
-- ryan
On Sun, Jul 24, 2011 at 8:55 PM, Ivan Lazar Miljenovic
wrote: On 25 July 2011 13:50, Sebastien Zany wrote: I was thinking the reverse. We can already give default implementations of class operations that can be overridden by giving them explicitly when we declare instances, so why shouldn't we be able to give default implementations of operations of more general classes, which could be overridden by a separate instance declaration for these?
Then I could say something like "a monad is also automatically a functor with fmap by default given by..." and if I wanted to give a more efficient fmap for a particular monad I would just instantiate it as a functor explicitly.
I believe this has been proposed before, but a major problem is that you cannot do such overriding.
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com
_______________________________________________ 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
participants (10)
-
Alejandro Serrano Mena
-
Arlen Cuss
-
August Sodora
-
Felipe Almeida Lessa
-
Ivan Lazar Miljenovic
-
James Cook
-
Maciej Marcin Piechotka
-
Ryan Ingram
-
Sebastien Zany
-
Victor Nazarov