In opposition of Functor as super-class of Monad

I'd like to argue in opposition of making Functor a super-class of Monad. I would argue that superclass constraints are not the right tool for expressing mathematical relationship such that all monads are functors and applicatives. Then argument is practical. It seems that making Functor a superclass of Monad makes defining new monad instances more of a chore, leading to code duplication. To me, code duplication is a sign that an abstraction is missing or misused. For the sake of the argument, let us suppose that Functor is a superclass of Monad. Let us see how to define a new Monad instance. For the sake of a better illustration, I'll use a complex monad. I just happen to have an example of that: Iteratee. The data type Iteratee is defined as follows:
type ErrMsg = String -- simplifying data Stream el = EOF (Maybe ErrMsg) | Chunk [el] deriving Show
data Iteratee el m a = IE_done a | IE_cont (Maybe ErrMsg) (Stream el -> m (Iteratee el m a, Stream el))
We wish to define an instance for Monad (Iteratee el m). Since Functor is a superclass of Monad, we must define a functor instance:
instance Functor m => Functor (Iteratee el m) where fmap f (IE_done a) = IE_done (f a) fmap f (IE_cont e k) = IE_cont e (\s -> fmap docase (k s)) where docase (IE_done a,s) = (IE_done (f a), s) docase (i, s) = (fmap f i, s)
There are two ways to proceed with the Monad instance -- to be precise, there are two ways of defining bind. Method A: just define bind as usual
instance (Functor (Iteratee el m),Monad m) => Monad (Iteratee el m) where return = IE_done
IE_done a >>= f = f a IE_cont e k >>= f = IE_cont e (\s -> k s >>= docase) where docase (IE_done a, stream) = case f a of IE_cont Nothing k -> k stream i -> return (i,stream) docase (i, s) = return (i >>= f, s)
Although we must state the constraint (Functor (Iteratee el m)) to satisfy the super-class constraint, we have not made any use of the constraint. We defined bind without resorting to fmap. That seems like a waste. What makes it seem more like a waste is that the code for fmap and for bind is almost the same. We had to repeat essentially the same algorithm, analysing Iteratee and the continuation. Method B: define bind in terms of fmap Alas, just fmap is not sufficient to define bind. We need join:
joinIter :: Monad m => Iteratee el m (Iteratee el m a) -> Iteratee el m a joinIter (IE_done i) = i joinIter (IE_cont e k) = IE_cont e (\s -> k s >>= docase) where docase (IE_done (IE_cont Nothing k), s) = k s docase (IE_done i, s) = return (i, s) docase (i, s) = return (joinIter i, s)
Only after defining join we can write
bind m f = joinIter $ fmap f m
Again we see code duplication: the code for join resembles the code for fmap. The code for join follows the same pattern of analysing Iteratee and the continuation. In either way, Functor as a super-class of Monad leads to code duplication. That gives a bad feeling practically -- and theoretically. The experiment has led me wonder if a superclass constraint is the right way to state the relationship between Monads and Functors. It _almost_ makes me wish the constraint go the other way:
instance Monad m => Functor m where fmap f m = m >>= (return . f)
That is, we need an instance rather than a superclass constraint, and in the other direction. The instance constraint says that every monad is a functor. Moreover, \f m = m >>= (return . f) is a _proof term_ that every monad is a functor. We can state it once and for all, for all present and future monads. Alas, the instance ``instance Monad m => Functor m'' above has several drawbacks (for one, requiring overlapping instances everywhere). This makes me wonder if something is amiss. In the meanwhile, there is a practical work-around. Introduce a TemplateHaskell operation generating an instance such as
instance Monad (Iteratee el m) => Functor (Iteratee el m) where fmap f m = m >>= (return . f)
(the code for the method remains the same; only the type in the instance head varies). Alas, that requires undecidable instances. All the code before was Haskell98.

Method C: Define fmap in terms of bind
instance Monad m => Functor (Iteratee el m) where fmap = liftM
Now you need to do the inspection of Iteratee only once: in the definition of the bind. However, to use liftM as implementation of fmap the superclass constraint of the Functor instance has changed from Functor to Monad. Is this a problem? If so, method A seems the way to go: you could argue that `Functor m => fmap :: (a -> b) -> Iteratee el m a -> Iteratee el m b' is more general than the `Monad m =>' version (works for more `m's) and therefore deserves to redo the analysis of Iteratee. Martijn. On 1/4/11 11:24, oleg@okmij.org wrote:
I'd like to argue in opposition of making Functor a super-class of Monad. I would argue that superclass constraints are not the right tool for expressing mathematical relationship such that all monads are functors and applicatives.

On Tuesday 04 January 2011 5:24:21 am oleg@okmij.org wrote:
Method A: just define bind as usual
instance (Functor (Iteratee el m),Monad m) => Monad (Iteratee el m) where
return = IE_done
IE_done a >>= f = f a IE_cont e k >>= f = IE_cont e (\s -> k s >>= docase)
where docase (IE_done a, stream) = case f a of
IE_cont Nothing k -> k stream i -> return (i,stream)
docase (i, s) = return (i >>= f, s)
Although we must state the constraint (Functor (Iteratee el m)) to satisfy the super-class constraint, we have not made any use of the constraint.
This, at least, is false. If Functor is a superclass of Monad, then Monad m implies Functor m, which implies Functor (Iteratee el m). So Monad m is a sufficient constraint for the instance. As for the other concerns, I think the closest fix I've seen is to allow subclasses to specify defaults for superclasses, and allow instances for subclasses to include methods for superclasses. So: class Functor m => Monad m where return :: a -> m a (>>=) :: m a -> (a -> m b) -> m b fmap f x = x >>= return . f This has its own caveats of course. And in this case, it seems to overconstrain the functor instance, since presumably we'd end up with: instance Monad m => Monad (Iteratee el m) where ... ==> instance Monad m => Functor (Iterate el m) where ... I'm not sure what to do about that. -- Dan

Hi folks I think we should wait until we've thought about superclass methods defaults before we decide whether Functor should be a superclass of Monad, as it clearly has significant impact on the cost-benefit analysis of the change, and also the details of it. But as I mentioned in my other recent message, I'd rather hope that doesn't mean kicking the whole thing into the long grass. So, as Dan and Martijn point out: On 4 Jan 2011, at 13:29, Dan Doel wrote:
As for the other concerns, I think the closest fix I've seen is to allow subclasses to specify defaults for superclasses, and allow instances for subclasses to include methods for superclasses. So:
class Functor m => Monad m where return :: a -> m a (>>=) :: m a -> (a -> m b) -> m b
fmap f x = x >>= return . f
modulo other considerations treated elsewhere, gives
instance Monad m => Functor (Iterate el m) where ...
Now, Oleg rightly points out that one can have instance Functor m => Functor (Iteratee el m) at the cost of code duplication. However, this is not such a strong objection because either (a) the overconstrained Functor-from-Monad definition is sufficient, in which case we're talking at most a 2-line penalty, although 0 would be nice; (b) preservation of functoriality is specifically desired, in which case the duplication problem is no worse than it is at present. Oleg's example does raise a serious concern about structure-preserving *transformers* in general. There is a missing abstraction. The same issue arises with monad and applicative transformers. It's hard to say `you can get out the structure you put in'. Perhaps there's a way to express these things as arrow-transformers, working for any notion of arrow with sufficient structure. To sum up, the code duplication problem Oleg raises is a serious concern in any case, but it has little or no impact on the issue at hand. All the best Conor

On 04.01.2011 13:24, oleg@okmij.org wrote:
I'd like to argue in opposition of making Functor a super-class of Monad. I would argue that superclass constraints are not the right tool for expressing mathematical relationship such that all monads are functors and applicatives.
Then argument is practical. It seems that making Functor a superclass of Monad makes defining new monad instances more of a chore, leading to code duplication. To me, code duplication is a sign that an abstraction is missing or misused.
I think I understood your point. But it looks like that it's possible to use subclass's function in superclass instance. At very least GHC is able to do it. Following example works just fine without any language extensions in GHC6.12.3 import Prelude hiding (Monad(..), Functor(..)) class Functor f where fmap :: (a -> b) -> f a -> f b class Functor m => Monad m where return :: a -> m a (>>=) :: m a -> (a -> m b) -> m b instance Functor Maybe where fmap f m = m >>= (return . f) instance Monad Maybe where return = Just Nothing >>= _ = Nothing Just x >>= f = f x

I think you'll find a problem using do-notation with your Monad.
Tony Morris
On 04/01/2011 11:33 PM, "Alexey Khudyakov"
I'd like to argue in opposition of making Functor a...
I think I understood your point. But it looks like that it's possible to use subclass's function in superclass instance. At very least GHC is able to do it. Following example works just fine without any language extensions in GHC6.12.3 import Prelude hiding (Monad(..), Functor(..)) class Functor f where fmap :: (a -> b) -> f a -> f b class Functor m => Monad m where return :: a -> m a (>>=) :: m a -> (a -> m b) -> m b instance Functor Maybe where fmap f m = m >>= (return . f) instance Monad Maybe where return = Just Nothing >>= _ = Nothing Just x >>= f = f x _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.o...

{-# LANGUAGE GeneralizedNewtypeDeriving #-} import Prelude hiding (Monad(..), Functor(..)) class Functor f where fmap :: (a -> b) -> f a -> f b class Functor m => Monad m where return :: a -> m a (>>=) :: m a -> (a -> m b) -> m b instance Functor Maybe where fmap f m = m >>= (return . f) instance Monad Maybe where return = Just Nothing >>= _ = Nothing Just x >>= f = f x newtype MMaybe a = MMaybe (Maybe a) deriving (Functor, Monad) mjust = MMaybe . Just mnothing = MMaybe Nothing -- No instance for (GHC.Base.Monad MMaybe) f = do x <- mjust 7 return x On 04/01/11 23:46, Alexey Khudyakov wrote:
On 04.01.2011 16:38, Tony Morris wrote:
I think you'll find a problem using do-notation with your Monad.
Tony Morris
Do you mean that fail is absent? That's irrelevant here.
I tried to demonstrate that fmap could be defined in terms of monad and that definition will work.
-- Tony Morris http://tmorris.net/

Tony, you're missing the point... Alexey isn't making a complete patch to GHC/base libraries, just a hacky-looking demonstration. Alexey is saying that in a class hierarchy (such as if Functor => Monad were a hierarchy, or for that matter "XFunctor"=>"XMonad" or Eq => Ord), it is still possible to define the superclass functions (fmap) in terms of the subclass functions (return and >>=) (such as writing a functor instance in which "fmap f m = m >>= (return . f)"). This has always been true in Haskell, it just might not have been obvious.

On 06/01/11 04:58, Isaac Dupree wrote:
Tony, you're missing the point... Alexey isn't making a complete patch to GHC/base libraries, just a hacky-looking demonstration. Alexey is saying that in a class hierarchy (such as if Functor => Monad were a hierarchy, or for that matter "XFunctor"=>"XMonad" or Eq => Ord), it is still possible to define the superclass functions (fmap) in terms of the subclass functions (return and >>=) (such as writing a functor instance in which "fmap f m = m >>= (return . f)"). This has always been true in Haskell, it just might not have been obvious.
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime Oh right sorry. I thought a stronger point was being made.
Then perhaps it's also worth pointing out that (<*>) can be written using (>>=) and return: f <*> a = f >>= \ff -> a >>= \aa -> return (ff aa) -- Tony Morris http://tmorris.net/

Hi,
indeed, this is called "ap" in Control.Monad. So if we have an instance of
Monad, all that needs to be done to support the other instances is:
instance (SameContextAsTheMonadInstance) => Functor MyType where fmap =
liftM
instance (SameContextAsTheMonadInstance) => Applicative MyType where pure =
return; (<*>) = ap
Furthermore, this is only in the cases where we are defining the type from
scratch, and not using a library like monadLib or MTL, otherwise a simple
"deriving" is sufficient.
-Iavor
On Wed, Jan 5, 2011 at 12:29 PM, Tony Morris
On 06/01/11 04:58, Isaac Dupree wrote:
Tony, you're missing the point... Alexey isn't making a complete patch to GHC/base libraries, just a hacky-looking demonstration. Alexey is saying that in a class hierarchy (such as if Functor => Monad were a hierarchy, or for that matter "XFunctor"=>"XMonad" or Eq => Ord), it is still possible to define the superclass functions (fmap) in terms of the subclass functions (return and >>=) (such as writing a functor instance in which "fmap f m = m >>= (return . f)"). This has always been true in Haskell, it just might not have been obvious.
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime Oh right sorry. I thought a stronger point was being made.
Then perhaps it's also worth pointing out that (<*>) can be written using (>>=) and return: f <*> a = f >>= \ff -> a >>= \aa -> return (ff aa)
-- Tony Morris http://tmorris.net/
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 On 1/5/11 00:08 , Tony Morris wrote:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
import Prelude hiding (Monad(..), Functor(..)) (...) -- No instance for (GHC.Base.Monad MMaybe)
That's an artifact of hiding Prelude's Monad, not a problem with the proposed implementation. I think you can use RebindableSyntax to tell GHC to use your Monad definition instead of the default? - -- brandon s. allbery [linux,solaris,freebsd,perl] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.11 (Darwin) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/ iEYEARECAAYFAk0nqVgACgkQIn7hlCsL25WdsACgzsCHVXmkyej9yynCDzu9oFzQ +RwAn3xG88VpKz3jpc4UW0/Mj1Zct6eR =QAOZ -----END PGP SIGNATURE-----

On Tue, Jan 04, 2011 at 02:24:21AM -0800, oleg@okmij.org wrote:
I'd like to argue in opposition of making Functor a super-class of Monad. I would argue that superclass constraints are not the right tool for expressing mathematical relationship such that all monads are functors and applicatives.
Then argument is practical. It seems that making Functor a superclass of Monad makes defining new monad instances more of a chore, leading to code duplication. To me, code duplication is a sign that an abstraction is missing or misused.
The argument about code duplication somehow seems to assume that class member instances need to be defined as part of the instance declaration. This is not the case, and in fact I am arguing in general against putting any interesting code into instance declarations, especially into declarations of instances with constraints (since, in ML terminology, they are functors, and putting their definition inside an instance declaration constrains their applicability). In my opinion, the better approach is to define (generalised versions of) the functions mentioned in the class interface, and then just throw together the instances from those functions. This also makes it easier to adapt to the ``class hierarchy du jour''. The point for the situation here is that although we eventually need definitions of all the functions declared as class members, there is absolutely nothing that constrains the dependency relation between the definitions of these functions to be conforming in any way to the class hierarchy. For a simpler example, assume that I have some arbitrary data type
data T a = One a | Two a a
and assume that I am interested only in Ord instances, since I want to use T with Data.Set, and I am not really interested in Eq instances. Assume that the order will depend on that for |a|, so I will define a function:
compareT :: (a -> a -> Ordering) -> T a -> T a -> Ordering
Then I can thow together the necessary instances from that:
instance Ord a => Ord (T a) where compare = compareT compare
instance Ord a => Eq (T a) where (==) = eqFromCompare compare
assuming I have (preferably from the exporter of Eq and Ord):
eqFromCompare :: (a -> a -> Ordering) -> (a -> a -> Bool) eqFromCompare cmp x y = case cmp x y of EQ -> True _ -> False
The same approach works for Oleg's example:
For the sake of the argument, let us suppose that Functor is a superclass of Monad. Let us see how to define a new Monad instance. For the sake of a better illustration, I'll use a complex monad. I just happen to have an example of that: Iteratee. The data type Iteratee is defined as follows:
type ErrMsg = String -- simplifying data Stream el = EOF (Maybe ErrMsg) | Chunk [el] deriving Show
data Iteratee el m a = IE_done a | IE_cont (Maybe ErrMsg) (Stream el -> m (Iteratee el m a, Stream el))
[...]
It _almost_ makes me wish the constraint go the other way:
instance Monad m => Functor m where fmap f m = m >>= (return . f)
That is, we need an instance rather than a superclass constraint, and in the other direction. The instance constraint says that every monad is a functor. Moreover, \f m = m >>= (return . f)
is a _proof term_ that every monad is a functor. We can state it once and for all, for all present and future monads.
I would expect that proof term to exported by the package exporting Functor and Monad; let us define it here:
fmapFromBind (>>=) f m = m >>= (return . f)
Now you can write, no matter which class is a superclass of which:
bindIt return (>>=) (IE_done a) f = f a bindIt return (>>=) (IE_cont e k) f = IE_cont e (\s -> k s >>= docase) where docase (IE_done a, stream) = case f a of IE_cont Nothing k -> k stream i -> return (i,stream) docase (i, s) = return (bindIt return (>>=) i f, s)
instance Monad m => Monad (Iteratee el m) where return = IE_done (>>=) = bindIt return (>>=)
instance Monad m => Functor (Iteratee el m) where fmap = fmapFromBind (>>=)
Of course this assumes that you are not actually interested in an instance of shape: instance (Functor ...) => Functor (Iteratee el m), but this seems to be a plausible assumption. Defining the functionality really has nothing to do with declaring an instance of a type class, and it is normally better to keep the two separated. And that does not lead to any real code duplication, only extremely boring instance declarations. Wolfram

On 4 jan 2011, at 11:24, oleg@okmij.org wrote:
I'd like to argue in opposition of making Functor a super-class of Monad. I would argue that superclass constraints are not the right tool for expressing mathematical relationship such that all monads are functors and applicatives.
It _almost_ makes me wish the constraint go the other way:
instance Monad m => Functor m where fmap f m = m >>= (return . f)
That is, we need an instance rather than a superclass constraint, and in the other direction. The instance constraint says that every monad is a functor. Moreover, \f m = m >>= (return . f)
is a _proof term_ that every monad is a functor. We can state it once and for all, for all present and future monads.
Alas, the instance ``instance Monad m => Functor m'' above has several drawbacks (for one, requiring overlapping instances everywhere). This makes me wonder if something is amiss.
The only real use I have ever seen of using superclasses is to be able to give default definitions which can be overridden with more efficient versions where needed, so here I would have expected: class Monad m => Functor m where fmap f m = >>= (return . f) Doaitse
In the meanwhile, there is a practical work-around. Introduce a TemplateHaskell operation generating an instance such as
instance Monad (Iteratee el m) => Functor (Iteratee el m) where fmap f m = m >>= (return . f)
(the code for the method remains the same; only the type in the instance head varies). Alas, that requires undecidable instances. All the code before was Haskell98.
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
participants (12)
-
Alexey Khudyakov
-
Brandon S Allbery KF8NH
-
Conor McBride
-
Dan Doel
-
Iavor Diatchki
-
Isaac Dupree
-
kahl@cas.mcmaster.ca
-
Martijn van Steenbergen
-
oleg@okmij.org
-
S. Doaitse Swierstra
-
Tony Morris
-
Tony Morris