Re: [Haskell-cafe] Heavy lift-ing

I wouldn't-it was a bad example. My only point was that because of the
way (>>=) is implemented for lists the order of the arguments 'a' and
'b' in 'liftM2 f a b' matters.
-deech
On Sat, Jul 24, 2010 at 1:37 AM, Lennart Augustsson
Why would you expect swapped operands to (-) ?
Sent from my iPad
On Jul 23, 2010, at 20:12, aditya siram
wrote: Lists are non-deterministic, but the function taken by liftM2 does not necessarily generate all possible outcomes. In the case of (+) it does, not in the case of (-): liftM2 (-) [0,1] [2,3] => [0-1,0-2,1-2,1-3] => [-2,-3,-1,-2] if all possible cases were generated between the two lists we have to include also: [2-0,2-1,3-0,3-1]
-deech
On Fri, Jul 23, 2010 at 3:44 PM, Alex Stangl
wrote: On Fri, Jul 23, 2010 at 11:43:08AM -0700, michael rice wrote:
What does it mean to "promote a function to a monad?"
It would seem that the monad values must understand the function that's being promoted, like Ints understand (+).
Prelude Control.Monad> liftM2 (+) (Just 1) (Just 1) Just 2
But how does one add [0,1] and [0,2] to get [0,2,1,3]?
It depends upon the semantics of the particular monad. List monads represent nondeterminism. So, for example, [0,1] represents a 0 or 1, and [0,2] represents a 0 or 2.
When you add 0 or 1 to 0 or 2, your possible answers are [0,2,1,3].
Alex _______________________________________________ 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

On Sat, Jul 24, 2010 at 4:08 PM, aditya siram
I wouldn't-it was a bad example. My only point was that because of the way (>>=) is implemented for lists the order of the arguments 'a' and 'b' in 'liftM2 f a b' matters.
-deech
No, it's not. The type of liftM2 makes this clear: liftM2 :: (Monad m) => (a -> b -> r) -> m a -> m b -> m r The arguments to the function *must* come in the right order, because there is no way to match (a) with (m b) or (b) with (m a). Since liftM2 is parametrically polymorphic in (a) and (b), it can't behave differently in the case where (a = b). --Max

Perhaps I'm being unclear again. All I was trying to say was that:
liftM2 (-) [0,1] [2,3] /= liftM2 (-) [2,3] [0,1]
-deech
On Sat, Jul 24, 2010 at 9:30 AM, Max Rabkin
On Sat, Jul 24, 2010 at 4:08 PM, aditya siram
wrote: I wouldn't-it was a bad example. My only point was that because of the way (>>=) is implemented for lists the order of the arguments 'a' and 'b' in 'liftM2 f a b' matters.
-deech
No, it's not. The type of liftM2 makes this clear:
liftM2 :: (Monad m) => (a -> b -> r) -> m a -> m b -> m r
The arguments to the function *must* come in the right order, because there is no way to match (a) with (m b) or (b) with (m a). Since liftM2 is parametrically polymorphic in (a) and (b), it can't behave differently in the case where (a = b).
--Max

Prelude Control.Monad> liftM2 (\a b -> a : b : []) "abc" "123"
["a1","a2","a3","b1","b2","b3","c1","c2","c3"]
Prelude Control.Monad>
Got it!
Thanks to all.
Michael
--- On Sat, 7/24/10, aditya siram
On Sat, Jul 24, 2010 at 4:08 PM, aditya siram
wrote: I wouldn't-it was a bad example. My only point was that because of the way (>>=) is implemented for lists the order of the arguments 'a' and 'b' in 'liftM2 f a b' matters.
-deech
No, it's not. The type of liftM2 makes this clear:
liftM2 :: (Monad m) => (a -> b -> r) -> m a -> m b -> m r
The arguments to the function *must* come in the right order, because there is no way to match (a) with (m b) or (b) with (m a). Since liftM2 is parametrically polymorphic in (a) and (b), it can't behave differently in the case where (a = b).
--Max
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 24/07/2010, aditya siram
Perhaps I'm being unclear again. All I was trying to say was that: liftM2 (-) [0,1] [2,3] /= liftM2 (-) [2,3] [0,1]
-deech
I'm sorry if I'm bumping an old thread, but why should "liftM2 f" be commutative when "f" isn't? (I hope I'm not responding incorrectly)

On 17/08/10 17:13, Tilo Wiklund wrote:
On 24/07/2010, aditya siram
wrote: Perhaps I'm being unclear again. All I was trying to say was that: liftM2 (-) [0,1] [2,3] /= liftM2 (-) [2,3] [0,1]
-deech
I'm sorry if I'm bumping an old thread, but why should "liftM2 f" be commutative when "f" isn't?
(I hope I'm not responding incorrectly)
I think the point that was being made is that: liftM2 (flip f) /= flip (liftM2 f) This is because the former (well: liftM2 (flip f) a b) effectively does: do {x <- a; y <- b; return (f y x)} Whereas the latter (flip (liftM2 f) a b) effectively does: do {y <- b; x <- a; return (f y x)} That is, the order of the arguments to liftM2 matters because they are executed in that order. So lifting the flipped function has a different effect to flipping the lifted function. Thanks, Neil.

I think the point that was being made is that:
liftM2 (flip f) /= flip (liftM2 f)
This is because the former (well: liftM2 (flip f) a b) effectively does:
do {x <- a; y <- b; return (f y x)}
Whereas the latter (flip (liftM2 f) a b) effectively does:
do {y <- b; x <- a; return (f y x)}
That is, the order of the arguments to liftM2 matters because they are executed in that order. So lifting the flipped function has a different effect to flipping the lifted function.
Thanks,
Neil.
Thanks, I can see how that could lead to confusion.
participants (5)
-
aditya siram
-
Max Rabkin
-
michael rice
-
Neil Brown
-
Tilo Wiklund