I don't understand mapM in mapM id (Just 1, Nothing, Just 3)

I was playing with winghci and I tried: mapM id [Just 1, Just 2, Just 3] result: Just [1,2,3] I don't understand this answer.
From http://members.chello.nl/hjgtuyl/tourdemonad.html#mapM http://members.chello.nl/hjgtuyl/tourdemonad.html#mapM mapM mf xs takes a monadic function mf (having type Monad m => (a -> m b)) and applies it to each element in list xs; the result is a list inside a monad.
A few things I've found: mapM :: (a -> m b) -> [a] -> m [b] So in this case: a = Maybe Int (second arg in mapM id [Just1, Just 2, Just 3] and b = Int and m = Maybe. So id is :: Maybe Int -> Maybe Int mapM id [Just 1, Nothing, Just 3] result: Nothing. My first guess for the result: Just [Just 1, Nothing, Just 3] when I do: mapM id [1,2,3] I get an error (id has wrong type, which makes sense) Can somebody explain what is going on here? Kees

On Fri, May 20, 2011 at 02:31:54PM +0200, Kees Bleijenberg wrote:
I was playing with winghci and I tried:
mapM id [Just 1, Just 2, Just 3] result: Just [1,2,3]
I don't understand this answer.
From http://members.chello.nl/hjgtuyl/tourdemonad.html#mapM http://members.chello.nl/hjgtuyl/tourdemonad.html#mapM mapM mf xs takes a monadic function mf (having type Monad m => (a -> m b)) and applies it to each element in list xs; the result is a list inside a monad.
A few things I've found: mapM :: (a -> m b) -> [a] -> m [b] So in this case: a = Maybe Int (second arg in mapM id [Just1, Just 2, Just 3] and b = Int and m = Maybe. So id is :: Maybe Int -> Maybe Int
mapM id [Just 1, Nothing, Just 3] result: Nothing. My first guess for the result: Just [Just 1, Nothing, Just 3]
when I do: mapM id [1,2,3] I get an error (id has wrong type, which makes sense)
Can somebody explain what is going on here?
You have to types right: a = Maybe Int m = Maybe b = Int 'mapM' is implemented like this: mapM f as = sequence (map f as) So working through the examples: mapM id [Just 1, Just 2, Just 3] = sequence (map id [Just 1, ...]) = sequence [Just 1, ...] = Just [1, ...] mapM id [Just 1, Nothing, Just 3] = sequence (map id [Just 1, Nothing, ...]) = sequence [Just1, Nothing, ...] = Nothing /M -- Magnus Therning OpenPGP: 0xAB4DFBA4 email: magnus@therning.org jabber: magnus@therning.org twitter: magthe http://therning.org/magnus I invented the term Object-Oriented, and I can tell you I did not have C++ in mind. -- Alan Kay

On Friday 20 May 2011 14:31:54, Kees Bleijenberg wrote:
I was playing with winghci and I tried:
mapM id [Just 1, Just 2, Just 3] result: Just [1,2,3]
I don't understand this answer.
From http://members.chello.nl/hjgtuyl/tourdemonad.html#mapM http://members.chello.nl/hjgtuyl/tourdemonad.html#mapM mapM mf xs takes a monadic function mf (having type Monad m => (a -> m b)) and applies it to each element in list xs; the result is a list inside a monad.
A few things I've found: mapM :: (a -> m b) -> [a] -> m [b] So in this case: a = Maybe Int (second arg in mapM id [Just1, Just 2, Just 3] and b = Int and m = Maybe. So id is :: Maybe Int -> Maybe Int
In more detail, [Just 1, Just 2, Just 3] :: [Maybe Int] That means a = Maybe Int, in mapM id [Just 1, Just 2, Just 3] id :: t -> t (for all t) in mapM id list, id must have type (a -> m b) for some Monad m, we have to unify the type (t -> t) with (a -> m b); that gives t = a (the argument types must be the same) and t = m b (the result types must be the same) Now a = Maybe Int = t = m b, hence m = Maybe, b = Int, thus mapM id [Just 1, Just 2, Just 3] :: m [b] = Maybe [Int]
mapM id [Just 1, Nothing, Just 3] result: Nothing. My first guess for the result: Just [Just 1, Nothing, Just 3]
No, that would have type Maybe [Maybe Int], but we've seen that it must have type Maybe [Int], so it's either Just (list of some Ints) or Nothing. Now, since mapM is polymorphic (works with all Monads and all parameter types), there's not much choice for doing something sensible. mapM can only use the function it gets as first argument and the Monad methods, so mapM foo [] = return [] mapM foo (x:xs) = ? well, it could ignore x (not sensible) or it can apply foo to x and then do something with that and xs; what can it do with xs? Well, mapM foo xs. So we have to somehow sensible combine foo x :: m b mapM foo xs :: m [b] The most natural is do y <- foo x ys <- mapM foo xs return (y:ys) or, without do-notation, foo x >>= \y -> mapM foo xs >>= \ys -> return (y:ys) or, with a combinator, liftM2 (:) (foo x) (mapM foo xs) Now, in the above, mapM id [Just 1, Nothing, Just 3], the Monad instance of Maybe says Nothing >>= _ = Nothing, so we get Just 1 >>= \y -> (Nothing >>= \z -> whatever) ~> Just 1 >>= \y -> Nothing ~> (\y -> Nothing) 1 ~> Nothing
when I do: mapM id [1,2,3] I get an error (id has wrong type, which makes sense)
Can somebody explain what is going on here?
Kees

mapM id [Just 1, Just 2, Just 3] result: Just [1,2,3]
mapM :: (a -> m b) -> [a] -> m [b] So in this case: a = Maybe Int (second arg in mapM id [Just1, Just 2, Just 3] and b = Int and m = Maybe. So id is :: Maybe Int -> Maybe Int
Right! So note here that 'm' is Maybe and 'b' is 'Int', thus mapM's return value is 'm [b]', i.e. 'Maybe [Int]'. The implication is that it somehow yields a Maybe of [Int], but no Maybe Int.
mapM id [Just 1, Nothing, Just 3] result: Nothing. My first guess for the result: Just [Just 1, Nothing, Just 3]
This is contingent of the semantics of the Maybe monad. First, mapM's definition:
mapM f as = sequence (map f as)
So the list is mapped onto the (monadic!) function, then sequenced:
sequence :: Monad m => [m a] -> m [a] sequence = foldr mcons (return []) where mcons p q = p >>= \x -> q >>= \y -> return (x : y)
Note that consecutive values are bound, so seeing this example should clarify why a single Nothing causes mapM to return Nothing for the lot:
Just 1 >> Just 2 Just 2 Nothing >> Just 2 Nothing
This falls simply out of Maybe's Monad instance definition for bind:
instance Monad Maybe where (Just x) >>= k = k x Nothing >>= k = Nothing
HTH. Arlen

By looking at sequence implementation in Hugs:
sequence (c:cs) = do x <- c
xs <- sequence cs
return (x:xs)
Apply it against a list [Just 2, Nothing], we will have:
sequence [Just 2, Nothing]
= do x <- Just 2
y <- sequence [Nothing]
return (x:y)
= return (2:Nothing)
The question is
Why/How `return (2:Nothing)` eval to `Nothing` ?
-Haisheng
On Sat, May 21, 2011 at 8:25 AM, Arlen Cuss
mapM id [Just 1, Just 2, Just 3] result: Just [1,2,3]
mapM :: (a -> m b) -> [a] -> m [b] So in this case: a = Maybe Int (second arg in mapM id [Just1, Just 2, Just 3] and b = Int and m = Maybe. So id is :: Maybe Int -> Maybe Int
Right! So note here that 'm' is Maybe and 'b' is 'Int', thus mapM's return value is 'm [b]', i.e. 'Maybe [Int]'. The implication is that it somehow yields a Maybe of [Int], but no Maybe Int.
mapM id [Just 1, Nothing, Just 3] result: Nothing. My first guess for the result: Just [Just 1, Nothing, Just 3]
This is contingent of the semantics of the Maybe monad. First, mapM's definition:
mapM f as = sequence (map f as)
So the list is mapped onto the (monadic!) function, then sequenced:
sequence :: Monad m => [m a] -> m [a] sequence = foldr mcons (return []) where mcons p q = p >>= \x -> q >>= \y -> return (x : y)
Note that consecutive values are bound, so seeing this example should clarify why a single Nothing causes mapM to return Nothing for the lot:
Just 1 >> Just 2 Just 2 Nothing >> Just 2 Nothing
This falls simply out of Maybe's Monad instance definition for bind:
instance Monad Maybe where (Just x) >>= k = k x Nothing >>= k = Nothing
HTH.
Arlen
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On 05.06.2011 14:40, Haisheng Wu wrote:
By looking at sequence implementation in Hugs:
sequence (c:cs) = do x<- c xs<- sequence cs return (x:xs)
Apply it against a list [Just 2, Nothing], we will have: sequence [Just 2, Nothing] = do x<- Just 2 y<- sequence [Nothing] return (x:y) = return (2:Nothing)
The question is Why/How `return (2:Nothing)` eval to `Nothing` ?
It doesn't. You went wrong in the last equality there. y doesn't have the value Nothing, in fact it never gets a value at all. Let's first look at what sequence [Nothing] evaluates to: do x <- Nothing y <- sequence [Nothing] return (x:y) Since Nothing >>= f evaluates to Nothing this means that the above do-block evaluates to Nothing, too. So y <- sequence [Nothing] becomes y <- Nothing and again the whole expression evaluates to Nothing and return (x:y) never is evaluated.

Thanks Senastian! I would refine the equality as below: sequence [Just 2, Nothing] = do x <- Just 2 y <- sequence [Nothing] return (x:y) = Just 2 >>= \x -> sequence [Nothing] >>= \y -> return (x:y) = Nothing >>= \y -> return (2:y) = Nothing -Haisheng On Mon, Jun 6, 2011 at 12:31 AM, Sebastian Hungerecker < sepp2k@googlemail.com> wrote:
On 05.06.2011 14:40, Haisheng Wu wrote:
By looking at sequence implementation in Hugs:
sequence (c:cs) = do x<- c xs<- sequence cs return (x:xs)
Apply it against a list [Just 2, Nothing], we will have: sequence [Just 2, Nothing] = do x<- Just 2 y<- sequence [Nothing] return (x:y) = return (2:Nothing)
The question is Why/How `return (2:Nothing)` eval to `Nothing` ?
It doesn't. You went wrong in the last equality there. y doesn't have the value Nothing, in fact it never gets a value at all. Let's first look at what sequence [Nothing] evaluates to:
do x <- Nothing
y <- sequence [Nothing] return (x:y)
Since Nothing >>= f evaluates to Nothing this means that the above do-block evaluates to Nothing, too. So y <- sequence [Nothing] becomes y <- Nothing and again the whole expression evaluates to Nothing and return (x:y) never is evaluated.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Mon, Jun 06, 2011 at 09:08:40AM +0800, Haisheng Wu wrote:
Thanks Senastian!
I would refine the equality as below:
sequence [Just 2, Nothing] = do x <- Just 2 y <- sequence [Nothing] return (x:y) = Just 2 >>= \x -> sequence [Nothing] >>= \y -> return (x:y) = Nothing >>= \y -> return (2:y) = Nothing
Yes, exactly. -Brent
participants (7)
-
Arlen Cuss
-
Brent Yorgey
-
Daniel Fischer
-
Haisheng Wu
-
Kees Bleijenberg
-
Magnus Therning
-
Sebastian Hungerecker