On 11/12/06, Nicola Paolucci <[EMAIL PROTECTED]> wrote:
Hi All,

I'm loving learning Haskell quite a bit.
It is stretching my brain but in a delightfull way.

I've googled, I've hoogled but I haven't found a clear explanation for
what exactly liftM2 does in the context below.

Using the cool lambdabot "pointless" utility I found out that:

> \x -> snd(x) - fst(x)

is the same as:

> liftM2 (-) snd fst

I like the elegance of this but I cannot reconcile it with its type. I
can't understand it.
I check the signature of liftM2 and I get:

Prelude> :t liftM2
Prelude> liftM2 :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r

Can someone help me understand what's happening here ?
What does a Monad have to do with a simple subtraction ?
What is actually the "m" of my example ?

I am sure if I get this I'll be another step closer to illumination ...

Thanks,
   Nick

Hi Nick!

The monad instance which is being used here is the instance for ((->)
e) -- that is, functions from a fixed type e form a monad.

So in this case:
liftM2 :: (a1 -> a2 -> r) -> (e -> a1) -> (e -> a2) -> (e -> r)
I bet you can guess what this does just by contemplating the type. (If
it's not automatic, then it's good exercise) Now, why does it do that?

Well, in general,
liftM2 f x y = do
  u <- x
  v <- y
  return (f u v)

So, it runs each of the computations you give it to get parameters for
f, and then returns the result of applying f to them.

In the ((->) e) monad, (which is often called the reader monad,
because it's isomorphic to it), running a computation just means
passing it the environment of type e. So in the reader monad, the
environment is passed to each of x and y, to get u and v respectively,
and then the value of (f u v) is returned. To translate, this is like:
liftM2 f x y e = f (x e) (y e)
of course, just for this particular monad.

Another nice example is join. In general,
join :: (Monad m) => m (m a) -> m a
join x = do
  y <- x
  z <- y
  return z

or simply,
join x = do
  y <- x
  y

In the reader monad, join has type (e -> e -> a) -> (e -> a), and it's
somewhat obvious what it must be doing -- it must take the value of
type e that it gets, and use it for both of the parameters of the
function it gets in order to produce a value of type a. You can see by
interpreting the do-notation that this is what happens in a curried
way. First x is passed the environment, then its result (the partially
applied function) is passed that environment.

So, for instance, join (*) 5 will result in 25.

The reader monad and functor instances are interesting, and worth
exploring. There are some rather interesting idioms which can be
obtained in this way. A nice one is:
ap (,) f
being the function (\x -> (x, f x)), which is handy for mapping across
lists of x-coordinates in making plots of functions.

Let us know if you need more detail about anything here. I sort of
skipped over some details in the presentation. (You might want to work
out exactly what return and bind do in this monad in order to
understand things completely -- you can work them out from the types
alone.)

- Cale
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to