[GHC] #7924: throwIO gets subsumed by a later imprecise exception

GHC cvs-ghc at haskell.org
Wed May 22 15:40:45 CEST 2013


#7924: throwIO gets subsumed by a later imprecise exception
-----------------------------+----------------------------------------------
Reporter:  dmwit             |          Owner:                  
    Type:  bug               |         Status:  new             
Priority:  normal            |      Component:  Compiler        
 Version:  7.6.1             |       Keywords:                  
      Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
 Failure:  None/Unknown      |      Blockedby:                  
Blocking:                    |        Related:                  
-----------------------------+----------------------------------------------
 The code below exits with exception "Boom" when compiled with no options
 (the expected behavior, since throwIO should always subsume exceptions
 that come later in the IO monad), but with a head-of-empty-list exception
 when compiled with -O. Similar code has shown this problem on 7.2 and 7.4.

 {{{
 {-# LANGUAGE DeriveDataTypeable #-}
 import Control.Exception (throwIO, Exception)
 import Control.Monad (when)
 import Data.Typeable (Typeable)

 data Boom = Boom deriving (Show, Typeable)
 instance Exception Boom

 main = do
     args <- return []

     -- Should throw this exception.
     when (length args /= 1) (throwIO Boom)

     -- With -O, instead throws this one from head [].
     let n = read (head args)
     when (n < 0) (throwIO Boom)

     return (fromInteger n :: Int)
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7924>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler



More information about the ghc-tickets mailing list