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

Arlen Cuss celtic at sairyx.org
Sat May 21 02:25:02 CEST 2011


 
> 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
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 836 bytes
Desc: This is a digitally signed message part
URL: <http://www.haskell.org/pipermail/beginners/attachments/20110521/8647b82c/attachment.pgp>


More information about the Beginners mailing list