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

#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

#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: -----------------------------+---------------------------------------------- Comment(by daniel.is.fischer): Already works as expected in the HEAD, also the mentioned similar code. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7924#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7924: throwIO gets subsumed by a later imprecise exception -----------------------------------------+---------------------------------- Reporter: dmwit | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.6.1 Resolution: worksforme | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Difficulty: Unknown Testcase: simplCore/should_run/T7924 | Blockedby: Blocking: | Related: -----------------------------------------+---------------------------------- Changes (by simonpj): * status: new => closed * difficulty: => Unknown * resolution: => worksforme * testcase: => simplCore/should_run/T7924 Comment: It works for me with 7.4.2, oddly. Compiling with -O I get the "Boom" result, as expected. Also, as Daniel says, with HEAD. So I'll add the test as a regression test and close. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7924#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC