[Haskell-cafe] Why Kleisli composition is not in the Monad signature?

AUGER Cédric sedrikov at gmail.com
Tue Oct 16 17:49:24 CEST 2012


Le Tue, 16 Oct 2012 11:22:08 -0400,
Daniel Peebles <pumpkingod at gmail.com> a écrit :

> Although I agree that Functor should be a superclass of Monad, the two
> methods of the Monad typeclass _are_ sufficient to make any instance
> into a Functor in a mechanical/automatic way. The language may not
> know it, but return/bind is equivalent in power to fmap/return/join.
> Apart from bind being easier to use for the things we typically do
> with monads in programs, using bind is actually more "succinct" in
> that it doesn't require three primitive operations.

Succintness is not the point for me. For me, the point is
primitiveness/elementaryness. For instance bind has type
"m a → (a → m b) → m b"
[2 type variables, one functionnal argument, one 'scalar' argument]
whereas join has type
"m (m a) → m a"
[1 type variable, one 'scalar' argument]
and fmap has type
"(a → b) → (m a → m b)"
[2 type variables, one functionnal argument, one 'scalar' argument]

So here, 'join' is definitely more simple than 'bind'.
'fmap' and 'bind' are about same complexity (although we can consider
'fmap' slightly simpler as its functionnal argument has type 'a→b' and
not 'a→m b').

Having one single powerfull function is often overkill, and you will
probably require more simple functions which you will get by feeding
your big function with dummy ones (such as 'id' or 'const'), and you
may lose some efficiency. I do not know if you have studied the S, K, I
system of combinators. It is a system which is equivalent to λ-calculus
if I well remember. There are supercombinators system which requires
only one combinator, but almost nobody bother with them as they lead to
define too ugly terms.

> 
> I'm not saying bind is a better primitive than join/fmap, but
> "mathematicians do it this way, therefore it's better" doesn't seem
> like a particularly convincing argument either.

I never said that, just that the "Monad" name is somehow not very
appropriate.

> And for a more
> philosophical question, is something not a functor just because we
> don't have a Functor instance for it? If we agree that the Monad
> class (with no Functor superclass) does implicitly form a Functor
> with liftM, then I don't really see what the problem is, apart from
> the inconvenience of not being able to use fmap.

I forgot about the liftM, so ok, the name is not that inapropriate,
although you have to wrap your stuff in the WrappedMonad…

> 
> On Tue, Oct 16, 2012 at 10:37 AM, AUGER Cédric <sedrikov at gmail.com>
> wrote:
> 
> > Le Tue, 16 Oct 2012 09:51:29 -0400,
> > Jake McArthur <jake.mcarthur at gmail.com> a écrit :
> >
> > > On Mon, Oct 15, 2012 at 11:29 PM, Dan Doel <dan.doel at gmail.com>
> > > wrote:
> > > > I'd be down with putting join in the class, but that tends to
> > > > not be terribly important for most cases, either.
> > >
> > > Join is not the most important, but I do think it's often easier
> > > to define than bind. I often find myself implementing bind by
> > > explicitly using join.
> >
> > join IS the most important from the categorical point of view.
> > In a way it is natural to define 'bind' from 'join', but in
> > Haskell, it is not always possible (see the Monad/Functor problem).
> >
> > As I said, from the mathematical point of view, join (often noted μ
> > in category theory) is the (natural) transformation which with
> > return (η that I may have erroneously written ε in some previous
> > mail) defines a monad (and requires some additionnal law). As often
> > some points it out, Haskellers are not very right in their
> > definition of Monad, not because of the bind vs join (in fact in a
> > Monad either of them can be defined from the other one), but
> > because of the functor status of a Monad. A monad, should always be
> > a functor (at least to fit its mathematical definition). And this
> > problem with the functor has probably lead to the use of
> > "bind" (which is polymorphic in two type variables) rather than
> > "join" (which has only one type variable, and thus is simpler). The
> > problem, is that when 'm' is a Haskell Monad which does not belong
> > to the Functor class, we cannot define 'bind' in general from
> > 'join'.
> >
> > That is in the context where you have:
> >
> > return:∀ a. a → (m a)
> > join:∀ a. (m (m a)) → (m a)
> > x:m a
> > f:a → (m b)
> >
> > you cannot define some term of type 'm b', since you would need to
> > use at the end, either 'f' (and you would require to produce a 'a'
> > which would be impossible), or 'return' (and you would need to
> > produce a 'b', which is impossible), or 'join' (and you would need
> > to produce a 'm (m b)', and recursively for that you cannot use
> > return which would make you go back to define a 'm b' term)
> >
> > For that, you need the 'fmap' operation of the functor.
> >
> > return:∀ a. a → (m a)
> > join:∀ a. (m (m a)) → (m a)
> > fmap:∀ a b. (a→b) → ((m a)→(m b))
> > x:m a
> > f:a → (m b)
> >
> > in this context defining a term of type 'm b' is feasible (join
> > (fmap f x)), so that you can express "bind = \ x f -> join (fmap f
> > x)".
> >
> > To sum up, mathematical monads are defined from 'return' and 'join'
> > as a mathematical monad is always a functor (so 'fmap' is defined,
> > and 'bind', which is more complex than 'join' can be defined from
> > 'join' and 'fmap'). Haskell does not use a very good definition for
> > their monads, as they may not be instance of the Functor class
> > (although most of them can easily be defined as such), and without
> > this 'fmap', 'join' and 'return' would be pretty useless, as you
> > wouldn't be able to move from a type 'm a' to a type 'm b'.
> >
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >




More information about the Haskell-Cafe mailing list