Re: [Haskell-cafe] Cannot understand liftM2

2012-02-13 Thread Richard Adams
Dear Ivan,

A great explanation you have provided!  It is very clear.  Thank you so much!  
(You Haskell folks are so willing to help.)  Wish there was something I knew 
that would be useful to you.

Thank you.

Sincerely,

Richard E. Adams
Applications Developer
Las Vegas Valley Water District
Email: richard.ad...@lvvwd.com
Tel. (702) 856-3627

-Original Message-
From: Ivan Perez [mailto:ivanperezdoming...@gmail.com] 
Sent: Friday, February 10, 2012 12:28 PM
To: j...@repetae.net
Cc: Richard Adams; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Cannot understand liftM2

To understand how liftM2 achieves the cartesian product, I think one way is to 
find liftM2's implementation and (>>=) implementation as part of []'s 
instantiation of the Monad class.

You can find the first in Control.Monad, and the second in the standard prelude.

Lists are monads, and as John (almost) said, liftM2 f x y is equivalent to
liftM2 f m1 m2 = do
  x1 <- m1
  x2 <- m2
  return (f x1 x2)

Which is syntactic sugar (fancy Haskell) for

liftM2 f m1 m2 =
  m1 >>= (\x1 -> m2 >>= (\x2 -> return (f x1 x2)))

In the prelude, you can find
instance  Monad []  where
m >>= k = foldr ((++) . k) [] m

Fhe right-hand side of (>>=) here is roughly equivalent to concat (map k m).

The last step, which I leave as an exercise to the reader (I always wanted to 
say that), is use the right hand side of the definition of (>>=) for lists in 
the right hand side of liftM2 when applied to (,) and two lists.

You can see the type of the function (,) (yes, comma is a function!) by 
executing, in ghci:

:type (,)

Cheers,
Ivan.

On 9 February 2012 19:23, John Meacham  wrote:
> A good first step would be understanding how the other entry works:
>
> cartProd :: [a] -> [b] -> [(a,b)]
> cartProd xs ys = do
>        x <- xs
>        y <- ys
>        return (x,y)
>
> It is about halfway between the two choices.
>
>    John
>
> On Thu, Feb 9, 2012 at 9:37 AM, readams  wrote:
>> Nice explanation.  However, at
>> http://stackoverflow.com/questions/4119730/cartesian-product it was 
>> pointed out that this
>>
>> cartProd :: [a] -> [b] -> [(a, b)]
>> cartProd = liftM2 (,)
>>
>> is equivalent to the cartesian product produced using a list comprehension:
>>
>> cartProd xs ys = [(x,y) | x <- xs, y <- ys]
>>
>> I do not see how your method of explanation can be used to explain 
>> this equivalence?  Nevertheless, can you help me to understand how 
>> liftM2 (,) achieves the cartesian product?  For example,
>>
>> Prelude Control.Monad.Reader> liftM2 (,) [1,2] [3,4,5] 
>> [(1,3),(1,4),(1,5),(2,3),(2,4),(2,5)]
>>
>> Thank you!
>>
>> --
>> View this message in context: 
>> http://haskell.1045720.n5.nabble.com/Cannot-understand-liftM2-tp30856
>> 49p5470185.html Sent from the Haskell - Haskell-Cafe mailing list 
>> archive at Nabble.com.
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cannot understand liftM2

2012-02-10 Thread Ivan Perez
To understand how liftM2 achieves the cartesian product, I think
one way is to find liftM2's implementation and (>>=) implementation
as part of []'s instantiation of the Monad class.

You can find the first in Control.Monad, and the second in
the standard prelude.

Lists are monads, and as John (almost) said, liftM2 f x y is equivalent to
liftM2 f m1 m2 = do
  x1 <- m1
  x2 <- m2
  return (f x1 x2)

Which is syntactic sugar (fancy Haskell) for

liftM2 f m1 m2 =
  m1 >>= (\x1 -> m2 >>= (\x2 -> return (f x1 x2)))

In the prelude, you can find
instance  Monad []  where
m >>= k = foldr ((++) . k) [] m

Fhe right-hand side of (>>=) here is roughly equivalent to
concat (map k m).

The last step, which I leave as an exercise to the reader (I always wanted
to say that), is use the right hand side of the definition of (>>=) for lists
in the right hand side of liftM2 when applied to (,) and two lists.

You can see the type of the function (,) (yes, comma is a function!)
by executing, in ghci:

:type (,)

Cheers,
Ivan.

On 9 February 2012 19:23, John Meacham  wrote:
> A good first step would be understanding how the other entry works:
>
> cartProd :: [a] -> [b] -> [(a,b)]
> cartProd xs ys = do
>        x <- xs
>        y <- ys
>        return (x,y)
>
> It is about halfway between the two choices.
>
>    John
>
> On Thu, Feb 9, 2012 at 9:37 AM, readams  wrote:
>> Nice explanation.  However, at
>> http://stackoverflow.com/questions/4119730/cartesian-product it was pointed
>> out that this
>>
>> cartProd :: [a] -> [b] -> [(a, b)]
>> cartProd = liftM2 (,)
>>
>> is equivalent to the cartesian product produced using a list comprehension:
>>
>> cartProd xs ys = [(x,y) | x <- xs, y <- ys]
>>
>> I do not see how your method of explanation can be used to explain this
>> equivalence?  Nevertheless, can you help me to understand how liftM2 (,)
>> achieves the cartesian product?  For example,
>>
>> Prelude Control.Monad.Reader> liftM2 (,) [1,2] [3,4,5]
>> [(1,3),(1,4),(1,5),(2,3),(2,4),(2,5)]
>>
>> Thank you!
>>
>> --
>> View this message in context: 
>> http://haskell.1045720.n5.nabble.com/Cannot-understand-liftM2-tp3085649p5470185.html
>> Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Cannot understand liftM2

2012-02-09 Thread John Meacham
A good first step would be understanding how the other entry works:

cartProd :: [a] -> [b] -> [(a,b)]
cartProd xs ys = do
x <- xs
y <- ys
return (x,y)

It is about halfway between the two choices.

John

On Thu, Feb 9, 2012 at 9:37 AM, readams  wrote:
> Nice explanation.  However, at
> http://stackoverflow.com/questions/4119730/cartesian-product it was pointed
> out that this
>
> cartProd :: [a] -> [b] -> [(a, b)]
> cartProd = liftM2 (,)
>
> is equivalent to the cartesian product produced using a list comprehension:
>
> cartProd xs ys = [(x,y) | x <- xs, y <- ys]
>
> I do not see how your method of explanation can be used to explain this
> equivalence?  Nevertheless, can you help me to understand how liftM2 (,)
> achieves the cartesian product?  For example,
>
> Prelude Control.Monad.Reader> liftM2 (,) [1,2] [3,4,5]
> [(1,3),(1,4),(1,5),(2,3),(2,4),(2,5)]
>
> Thank you!
>
> --
> View this message in context: 
> http://haskell.1045720.n5.nabble.com/Cannot-understand-liftM2-tp3085649p5470185.html
> Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Cannot understand liftM2

2012-02-09 Thread readams
Nice explanation.  However, at
http://stackoverflow.com/questions/4119730/cartesian-product it was pointed
out that this

cartProd :: [a] -> [b] -> [(a, b)]
cartProd = liftM2 (,) 

is equivalent to the cartesian product produced using a list comprehension:

cartProd xs ys = [(x,y) | x <- xs, y <- ys]

I do not see how your method of explanation can be used to explain this
equivalence?  Nevertheless, can you help me to understand how liftM2 (,)
achieves the cartesian product?  For example,

Prelude Control.Monad.Reader> liftM2 (,) [1,2] [3,4,5]
[(1,3),(1,4),(1,5),(2,3),(2,4),(2,5)]

Thank you!

--
View this message in context: 
http://haskell.1045720.n5.nabble.com/Cannot-understand-liftM2-tp3085649p5470185.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Cannot understand liftM2

2006-12-12 Thread Tim Newsham

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 think the simplest way to understand liftM and liftM2 are in
terms of their do-notation:

liftM op act = do
x <- act
return (op x)

that is: perform the action, bind the result to x, compute
(op x) and return that in the monad.

Similarly for liftM2:

   liftM2 op act1 act2 = do
   x <- act1
   y <- act2
   return (x `op` y)

in your case:

   liftM2 (-) snd fst = do
   x <- snd
   y <- fst
   return (x - y)

this is in the monad of functions that require an argument.  Snd is
a function that takes an argument (a pair) and returns a value
(the 2nd member of the pair).  Similarly fst is a fnction that takes
an argument.  The whole do-block represents a function that takes
an argument (also a pair).  As usual, do-blocks combine several
actions (in this case functions of one arguments) into a new action.

The description for this one is:  the function that, when given
an argument (say "a") computes the snd item of the pair (snd a)
binds, computes the fst item of the pair (fst a) and subtracts the
two values (snd a - fst a).


 Nick


Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re: [Haskell-cafe] Cannot understand liftM2

2006-12-11 Thread Nicola Paolucci

Hi Nicolas,

On 12/11/06, Nicolas Frisby <[EMAIL PROTECTED]> wrote:

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 awhere 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 awhere 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) ->}.


Really clearly exposed.

Thanks a lot, it all starts to make perfect sense.
The main point I was missing I now realize was that m in my example
context meant a monadic computation in the (e ->) monad.

Regards,
  Nick
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cannot understand liftM2

2006-12-11 Thread Paul Moore

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

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.


Don't apologise - I, for one, am finding this discussion very
informative, and am reading the responses with interest.

Thanks for starting the thread!
Paul.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cannot understand liftM2

2006-12-11 Thread Daniel McAllansmith
On Tuesday 12 December 2006 08:57, Nicola Paolucci wrote:
> - 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 (-) ?

It's the snd that forces the interpreter to infer the ((->) e) monad.

You can guess from the type of liftM2 that the (-) won't supply any more 
information/constraints about m because m is is only mentioned in the snd and 
fst parts.

If you use different monadic values, instead of snd and fst, then the m will 
end up constrained to a different monad

Try these commands in GHCi to see what happens if you use something in the 
Maybe monad:

Prelude> :m + Control.Monad

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

Prelude Control.Monad> :t liftM2 (-)
liftM2 (-) :: (Num a1, Monad m) => m a1 -> m a1 -> m a1

Prelude Control.Monad> :t liftM2 (-) (Just 5)
liftM2 (-) (Just 5) :: (Num a1) => Maybe a1 -> Maybe a1

Prelude Control.Monad> :t liftM2 (-) (Just 5) Nothing
liftM2 (-) (Just 5) Nothing :: (Num a1) => Maybe a1

Prelude Control.Monad> liftM2 (-) (Just 5) Nothing
Nothing


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


Re: [Haskell-cafe] Cannot understand liftM2

2006-12-11 Thread Andy Georges

Hi,


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.


You can derive this yourself by assigning types to all parts of the  
expression and working things out, i.e., doing the type inference  
yourself. For example,


liftM2 :: T1 =  T2 -> T3 -> T4 -> T5 because liftM2 consumes three  
arguments. Furthermore, ghci gives you the type of liftM2, you know  
the type of (-) and the types of snd and fst. Therefore,


T2 = (a -> a -> a) (type of (-))
T3 = (b,c) -> c (type of snd)
T4 = (d,e) -> d (type of fst)

and, by the type of liftM2 :: (f -> g -> h) -> m f -> m g -> m h, we  
also have


T2 = (f -> g -> h)
T3 = m f
T4 = m g
T5 = m h

The two type expressions for T2 imply that f = g = h = a (type-wise,  
that is). And


m f = (b,c) -> c = ((->) (b,c)) c
m g = (d,e) -> d = ((-> (d,e)) d, because f = g this reduces to ((->)  
(c,c)) c

and thus : m h = (c,c) -> c, because f = g = h

This implies that the monad m = ((->) (c,c)) and h = c = a = f = g

Thus:

liftM2 (-) snd fst :: ((->) (a,a)) a = (a,a) -> a

If I made any errors, please tell me.

-- Andy








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


Re: Re: [Haskell-cafe] Cannot understand liftM2

2006-12-11 Thread Nicolas Frisby

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 awhere 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 awhere 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 <[EMAIL PROTECTED]> wrote:

Hi All, Hi Cale,

Can you tell me if I understood things right ? Please see below ...

On 12/11/06, Cale Gibbard <[EMAIL PROTECTED]> 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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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


Re: [Haskell-cafe] Cannot understand liftM2

2006-12-11 Thread Nicola Paolucci

Hi All, Hi Cale,

Can you tell me if I understood things right ? Please see below ...

On 12/11/06, Cale Gibbard <[EMAIL PROTECTED]> 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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cannot understand liftM2

2006-12-11 Thread Nicola Paolucci

Hi Cale !

On 12/11/06, Cale Gibbard <[EMAIL PROTECTED]> 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?

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.



[...]



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.)


Your answer was very thorough and very clear. I am honestly overwhelmed :D.
Mind bending and rewarding.

Thank you very much.

I will be going through all your examples again slowly and with a
console on the side so that I am sure I grok as much as I can.

Regards,
   Nick
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cannot understand liftM2

2006-12-11 Thread Cale Gibbard

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


Re: [Haskell-cafe] Cannot understand liftM2

2006-12-11 Thread Dougal Stanton

Quoth Nicola Paolucci, nevermore:


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'm honestly not sure what the actual Monad m is in this case. I'm sure 
some enlightened individual will help us out. Maybe Identity?


But I thought you might find this handy --- the interactive console will 
give you the type of whole expressions, not just bare functions. It can 
be pretty helpful when trying to decode typery.



:t liftM2
liftM2 :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
:t liftM2 (-)
liftM2 (-) :: (Num a1, Monad m) => m a1 -> m a1 -> m a1
:t liftM2 (-) snd
liftM2 (-) snd :: (Num b) => ((a, b) -> b) -> (a, b) -> b
:t liftM2 (-) snd fst
liftM2 (-) snd fst :: (Num a) => (a, a) -> a


Cheers,

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


Re: [Haskell-cafe] Cannot understand liftM2

2006-12-11 Thread Joachim Breitner
Hi Nicola,

Am Montag, den 11.12.2006, 17:15 +0100 schrieb Nicola Paolucci:
> 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 ?

You came across a very nice Monad: “((->) a)”, or the Monad of all
functions that take a parameter of type a.

Do not be confused by the arrow _before_ the a, it is actually behind
the a: A function of type “a -> b” has type “(->) a b”. The same syntax
as for infix operators applies, and can be curried to “((->) a)”.

So in your example, snd and fst are computations in the ((->) (a,b))
Monad, and liftM2 (-) get’s the type:
Num a => ((->) (a,a) a) -> ((->) (a,a) a) -> ((->) (a,a) a)
or
Num a => ((a,a) -> a) -> ((a,a) -> a) -> ((a,a) -> a)
(at least I think so...)

So if you ever feel like squaring something:
square = join (*)

Greetings,
Joachim

> 
> I am sure if I get this I'll be another step closer to illumination ...
> 
> Thanks,
>Nick
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

-- 
Joachim "nomeata" Breitner
  mail: [EMAIL PROTECTED] | ICQ# 74513189 | GPG-Key: 4743206C
  JID: [EMAIL PROTECTED] | http://www.joachim-breitner.de/
  Debian Developer: [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe