[Haskell-beginners] I don't understand mapM in mapM id (Just 1, Nothing, Just 3)

Daniel Fischer daniel.is.fischer at googlemail.com
Fri May 20 14:57:37 CEST 2011


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



More information about the Beginners mailing list