[Haskell-beginners] Precedence of Infix Operators in Do Syntax

Brent Yorgey byorgey at seas.upenn.edu
Wed Nov 23 07:51:43 CET 2011


On Tue, Nov 22, 2011 at 11:03:51PM -0500, Avery Robinson wrote:
> Hello,
> 
> I was reading this block of code from
> http://jasani.org/2008/02/18/command-line-haskell-and-error-handling-examples/
> 
> main = do
>   m <- hGetContents stdin
>   nums <- mapM readM . lines $ m
>   print (sum nums)
>   `catch` (\e -> hPutStrLn stderr ("couldn't sum lines: " ++ show e))
> 
> readM :: (Monad m, Read a) => String -> m a
> readM s | [x] <- parse = return x
>         | otherwise    = fail $ "Failed to parse \"" ++ s ++ "\" as a
> number."
>   where
>     parse = [x | (x,_) <- reads s]
> 
> I don't understand how line 5 works. I thought that the do notation there
> would be the same as:
> 
> main = hGetContents stdin >>= \m ->
>        mapM readM . lines $ m >>= \nums ->
>        print (sum nums) >>
>        `catch` (\e -> hPutStrLn stderr ("couldn't sum lines: " ++
>        show e))

Some experimentation shows that in fact, the first argument of `catch` is the
*entire* do-block.  That is, it is the same as

main = (do
  m <- hGetContents stdin
  nums <- mapM readM . lines $ m
  print (sum nums)
  )
  `catch` (\e -> hPutStrLn stderr ("couldn't sum lines: " ++ show e))

However, I don't understand why.  I would have thought it invalid.

Perversely, indenting the `catch` by one more space results in a valid
program with different behavior (since it only applies to the print).

-Brent



More information about the Beginners mailing list