
#11555: catch under unsafePerformIO breaks on -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Discovered on xmonad-0.12 test failure. Happens on today's -HEAD and ghc-8.0.1-rc1,-rc2 Short example is (needs only base): {{{#!hs -- cat F.hs module F where import qualified Control.Exception as C import System.IO.Unsafe import qualified Data.List as L abort :: String -> a abort x = error $ "xmonad: StackSet: " ++ x prop_abort x = unsafePerformIO $ C.catch (abort "fail") (\(C.SomeException e) -> return $ "xmonad: StackSet: fail" `L.isPrefixOf` show e ) where _ = x :: Int }}} Session 1 [ok]: {{{ $ ghci F.hs GHCi, version 8.0.0.20160204: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling F ( F.hs, interpreted ) Ok, modules loaded: F. *F> prop_abort 1 True }}} Session 2 [fails]: {{{ $ ghci -O1 -fobject-code F.hs GHCi, version 8.0.0.20160204: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling F ( F.hs, F.o ) Ok, modules loaded: F. Prelude F> prop_abort 1 *** Exception: xmonad: StackSet: fail CallStack (from HasCallStack): error, called at F.hs:9:11 in main:F }}} I would expect exception to be caught on both cases. Is it unreasonable expectation in light of unsafePerformIO? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler