[Haskell-beginners] how to skip pattern match error when applying a mapM_

Francesco Ariis fa-ml at ariis.it
Tue Jan 17 14:19:46 UTC 2017


On Tue, Jan 17, 2017 at 02:03:02PM +0000, PICCA Frederic-Emmanuel wrote:
> Hello,
> 
> Here a reduction of my problem
> 
> values :: IO [IO (Maybe Int)]
> values = do
>   let v = [Just 1, Just 2, Just 3, Nothing, Just 5, Nothing, Just 7] :: [Maybe Int]
>   return $ map return v
> 
> main :: IO ()
> main = do
>   vs <- values
>   nvs <- mapM_ go vs
>   print nvs
>     where
>       go :: IO (Maybe Int) -> IO Int
>       go v' = do
>          Just v <- v'
>          return v

Hello Frédéric,
    `Just v <- v'` doesn't silently skip Nothing values, but it's
a full fledged pattern match (and one reason why I dislike `do
notation` as a syntactic sugar).

A way to solve the problem is to take advantage of `sequence`
and `catMaybes` (from `Data.Maybe`).

    λ> :t sequence
    sequence :: (Monad m) => [m a] -> m [a]
        -- I cheated a bit on the signature, but the gist
        -- of it is: from a list of monadic actions, to
        -- one monadic action returning a list of results.

    λ> :t catMaybes
    catMaybes :: [Maybe a] -> [a]

With that your main gets simpler:

    main :: IO ()
    main = do vs <- values           -- vs :: [IO (Maybe Int)]
              sv <- sequence vs      -- sequence vs :: IO [Maybe Int]
                                     -- sv :: [Maybe Int]
              print (M.catMaybes sv)

Does this help?


More information about the Beginners mailing list