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

Dan Doel dan.doel at gmail.com
Tue Oct 16 05:29:17 CEST 2012


On Mon, Oct 15, 2012 at 10:05 PM, damodar kulkarni
<kdamodar2000 at gmail.com> wrote:
> @Jake
>
>
>> In my opinion, this is not as nice as the do-notation version, but at
>> least it's compositional:
>
>
> That's an important point you have made, as Haskellers value code
> composition so much.
> If code composition is the "holy grail", why not encourage the monadic code,
> too, to be compositional? Nicety can wait; some syntax sugar might take care
> of it.
>
> And as you have pointed out, arrows make a superior choice in this regard,
> but they are rather newer to monads.

I'm uncertain where this, "compositional means written as the
composition of functions," thing started. But it is not what I, and
I'm sure any others mean by the term, "compositional."

For instance, one of the key properties of denotational semantics is
that they are compositional. But this does not mean that the semantics
is written as the composition of functions. Perhaps it could be, but
that is a rather superficial criterion. What it means is that the
semantics of compound expressions are merely functions of the
semantics of the constituent pieces, so one can stick together well
understood pieces to get well understood wholes, and the whole does
not have to be analyzed as an entire unit.

Now, one can give almost anything a compositional semantics in this
sense, by denoting things by pieces that pass context along. And this
is a reason to avoid effects and whatnot. But this is true whether one
writes things as a pipeline of functions or as some other sort of
expression. Context may be threaded through a series of expressions,
or through a series of composed functions. Choosing either way of
writing makes no difference.

So I don't really care whether people write their code involving
monads as the composition of Kleisli arrows, except for which makes
the code look nicer. And the arrow option does not always do so,
especially when one must artificially extend things of type 'M a' into
constant functions. Kleisli arrows aren't the end all and be all of
monads (if you read books on the math end, the Eilenberg-Moore
category tends to be emphasized far more, and the Kleisli category
might not even be presented in the same way as it typically is amongst
Haskellers).

As for why (>>=) is a good primitive.... For one, it works very nicely
for writing statement sequences without any sugar (for when you want
to do that):

    getLine >>= \x ->
    getLine >>= \y ->
    print (x, y)

For two, it corresponds to the nice operation of substitution of an
expression for a variable (which is a large part of what monads are
actually about in category theory, but doesn't get a lot of play in
Haskell monad tutorials).

For three, I can't for the life of me think of how anyone would write
(>=>) as a primitive operation _except_ for writing (>>=) and then '(f
>=> g) x = f x >>= g'. The function cannot be inspected to get the
result except by applying it.  I suppose one _can_ write (>=>)
directly. For instance:

    data Free f a = Pure a | Roll (f (Free f a))

    (g >=> h) x = case g x of
      Pure b -> h b
      Roll f -> Roll $ fmap (id >=> h) f

But the (id >=> h) is there because we want to put (>>= h) and don't
have it. The g is sort of an illusion. We use it to get an initial
value, but all our recursive calls use g = id, so we're subsequently
defining (>>=) in disguise. (And, amusingly, we're even using
polymorphic recursion, so if this isn't in a class, or given an
explicit type signature, inference will silently get the wrong
answer.)

So, there are good reasons for making (>>=) primitive, and not really
any (that I can see) for making (>=>) more than a derived function.
I'd be down with putting join in the class, but that tends to not be
terribly important for most cases, either.

-- Dan



More information about the Haskell-Cafe mailing list