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

Haisheng Wu freizl at gmail.com
Sun Jun 5 14:40:27 CEST 2011


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 <celtic at sairyx.org> wrote:

>
>
> > 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20110605/70436352/attachment.htm>


More information about the Beginners mailing list