
Hi, I don't understand what's taking place here.
From Hoogle:
================= liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r Promote a function to a monad, scanning the monadic arguments from left to right. For example, liftM2 (+) [0,1] [0,2] = [0,2,1,3] liftM2 (+) (Just 1) Nothing = Nothing ================= 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]? Michael

On 10-07-23 02:43 PM, michael rice wrote:
liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r [...] What does it mean to "promote a function to a monad?"
liftM2 f m1 m2 is canned code for do a1 <- m1 a2 <- m2 return (f a1 a2) for example liftM2 f [s,t] [x,y] is [f s x, f s y, f t x, f t y] liftM2 (++) getLine getLine reads two lines and concatenates them.

On 11:43 Fri 23 Jul , michael rice wrote:
Hi,
I don't understand what's taking place here.
From Hoogle:
=================
liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
Promote a function to a monad, scanning the monadic arguments from left to right. For example,
liftM2 (+) [0,1] [0,2] = [0,2,1,3] liftM2 (+) (Just 1) Nothing = Nothing
=================
What does it mean to "promote a function to a monad?"
Consider fmap, which 'promotes a function to a functor': fmap :: Functor f => (a -> b) -> f a -> f b This might be easier to understand if you fully parenthesise this: fmap :: Functor f => (a -> b) -> (f a -> f b) In other words, fmap takes a function on ordinary values as input, and outputs a function on a particular Functor. Now consider liftM, which 'promotes a function to a monad': liftM :: Monad m => (a -> b) -> m a -> m b Hey, this looks almost the same as fmap (it is)! Now, monads have additional structure which allows us to promote more complicated functions, for example: liftM2 :: Monad m => (a -> b -> c) -> m a -> m b -> m c which, when fully parenthesised, looks like liftM2 :: Monad m => (a -> b -> c) -> (m a -> m b -> m c) What we have now is that we can promote a 'two argument' function to Monads (this is not possible on mere Functors, hence there's no fmap2).
It would seem that the monad values must understand the function that's being promoted, like Ints understand (+).
Yes, liftM2 (+) gives you a new function with type (Num a, Monad m) => m a -> m a -> m a
But how does one add [0,1] and [0,2] to get [0,2,1,3]?
liftM2 (+) [0,1] [0,2] gives the list [0+0, 0+2, 1+0, 1+2] (recall that (>>=) in the list monad is concatMap). -- Nick Bowler, Elliptic Technologies (http://www.elliptictech.com/)

El vie, 23-07-2010 a las 15:05 -0400, Nick Bowler escribió:
On 11:43 Fri 23 Jul , michael rice wrote: [...]
But how does one add [0,1] and [0,2] to get [0,2,1,3]?
liftM2 (+) [0,1] [0,2] gives the list
[0+0, 0+2, 1+0, 1+2]
which one could have found out by asking ghci: Prelude Control.Monad> let f a b = show a ++ " + " ++ show b Prelude Control.Monad> liftM2 f [0,1] [0,2] ["0 + 0","0 + 2","1 + 0","1 + 2"] or simpler: Prelude Control.Monad> liftM2 (,) [0,1] [2,3] [(0,2),(0,3),(1,2),(1,3)] i.e., the in the list monad, you pair each element of one list with each element of the other(s).
(recall that (>>=) in the list monad is concatMap).
(>>=) = flip concatMap, to be precise. Or, concatMap = (=<<) Now let's have some fun with equational reasoning to see what liftM2 does exactly: (Only read this if you really want to!) liftM2 f a b = { definition of liftM2 } do {x <- a; y <- b; return (f x y)} = { simplified translation of do-notation } a >>= \x -> (b >>= \y -> return (f x y)) = { change (>>=) to (=<<) and flip arguments } (\x -> ((\y -> return (f x y)) =<< b)) =<< a = { specialized to the list monad } (\x -> ((\y -> [f x y])) `concatMap` b)) `concatMap` a = { change concatMap to prefix application } concatMap (\x -> concatMap (\y -> [x+y]) b) a and indeed: Prelude> concatMap (\x -> concatMap (\y -> [x+y]) [0,2]) [0,1] [0,2,1,3] with some effort, I think one can understand what happens here. It should also be clear how this is generalized to liftM3, liftM4, etc. Oh, btw, what about liftM1? Obviously, this should be the following: liftM1 f a = { definition } do { x <- a ; return f a } = { same changes as above } concatMap (\x -> [f x]) a = { definition of concatMap } concat (map (\x -> [f x]) a = { concating singletons can be simplified } map (\x -> f x) a = { eta-reduction } map f a i.e., liftM1 = map, which is indeed just fmap for lists, as already pointed out. You can use this to simplify the last line of the concatMap derivation above: concatMap (\x -> concatMap (\y -> [x+y]) b) a = { see above } concatMap (\x -> map (\y -> x+y) b) a = { use operator section } concatMap (\x -> map (x+) b) a which is about as clear as possible a definition for liftM2 (+) Jürgen

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

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

On Fri, Jul 23, 2010 at 09:12:44PM -0500, 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]
If I have a - b where a and b are both non-deterministic, I wouldn't expect to also include in my solution set all the results of b - a. What if you have a / b? Would you try to include b / a, too, even though some values of a may be zero? Alex
participants (6)
-
aditya siram
-
Albert Y. C. Lai
-
Alex Stangl
-
Jürgen Doser
-
michael rice
-
Nick Bowler