[Haskell-cafe] Cannot understand liftM2

Nicolas Frisby nicolas.frisby at gmail.com
Mon Dec 11 15:24:24 EST 2006


The interpreter infers that m = (e ->) because of the types of snd and fst.

When snd and fst are considered as monadic computations in the (e ->)
monad, there types are:

Prelude> :t fst
fst :: (a, b) -> a
Prelude> :t snd
snd :: (a, b) -> b

Note that: (a, b) -> a =~= m a    where m x = (a,b) -> x

So if we apply liftM2 to fst and snd, then the m of the result has to
be the same as the m of the arguments; thus the m of the result is
((a, b) ->). Now the type of (-) is:

Prelude> :t (-)
(-) :: (Num a) => a -> a -> a

Thus the interpreter knows that the a and b in the ((a, b) ->) monad
are actually the same. Finally we have:

Prelude Control.Monad.Reader> :t liftM2 (-) snd fst
liftM2 (-) snd fst :: (Num a) => (a, a) -> a

Note that: (a, a) -> a =~= m a    where m x = (a,a) -> x

So each argument to liftM2 contributes constraints to the components
of liftM2's general type:

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

snd forces m to be ((x,a2) ->)
fst forces m to be ((a1,y) ->)
(-) forces a1 and a2 to be the same

The conjunction of these contraints forces {a1:=a, a2:=a, m:=(a,a) ->}.

HTH,
Nick


On 12/11/06, Nicola Paolucci <durden at gmail.com> wrote:
> Hi All, Hi Cale,
>
> Can you tell me if I understood things right ? Please see below ...
>
> On 12/11/06, Cale Gibbard <cgibbard at gmail.com> wrote:
> > 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?
>
> So the way I have to reason on the output I get from ghci is:
>
> Prelude> :t liftM2
> liftM2 :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
>
> The m stands for ((->) e), that is like writing (e -> a1): a function
> which will take an argument of type e and will return an argument of
> type a1.
>
> And so the above line has a signature that reads something like:
> liftM2 will takes 3 arguments:
> - a function (-) that takes two arguments and returns one result of type r.
> - a function (fst) that takes one argument and returns one result.
> - a function (snd) that takes one argument and returns one result.
> - the result will be a certain function that will return the same type
> r of the (-) function.
> - Overall to this liftM2 I will actually pass two values of type a1
> and a2 and will get a result of type r.
>
> >From the type signature - correct me if I am wrong - I cannot actually
> tell that liftM2 will apply (-) to the rest of the expression, I can
> only make a guess. I mean I know it now that you showed me:
>
> > liftM2 f x y = do
> >    u <- x
> >    v <- y
> >    return (f u v)
>
> If this is correct and it all makes sense, my next question is:
> - How do I know - or how does the interpreter know - that the "m" of
> this example is an instance of type ((->) e) ?
> - Is it always like that for liftM2 ? Or is it like that only because
> I used the function (-) ?
>
> I am trying to understand this bit by bit I am sorry if this is either
> very basic and easy stuff, or if all I wrote is completely wrong and I
> did not understand anything. :D Feedback welcome.
>
> Thanks again,
> Regards,
>     Nick
> _______________________________________________
> 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