[GHC] #11555: catch under unsafePerformIO breaks on -O1

#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

#11555: catch under unsafePerformIO breaks on -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by NeilMitchell): * cc: ndmitchell (added) Comment: I ran into this today in the Shake test suite. My reduced case doesn't rely on {{{unsafePerformIO}}}. {{{#!hs {-# LANGUAGE ScopedTypeVariables #-} module Main(main) where import Control.Exception main :: IO () main = (undefined :: IO ()) `catch` \(e :: SomeException) -> putStrLn "Success" }}} At {{{-O0}}} this program is equivalent to {{{putStrLn "Success"}}}. At {{{-O1}}} and above this program is equivalent to {{{undefined}}}. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11555: catch under unsafePerformIO breaks on -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: normal => highest * failure: None/Unknown => Incorrect result at runtime * milestone: => 8.0.1 Comment: It sounds like this may be fallout from #11222. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11555: catch _|_ breaks at -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11555: catch under unsafePerformIO breaks on -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): It is fallout from #11222, but it's not a bug. There's no guarantee that the ''pure value'' passed to `catch` will be evaluated at any particular time. `catch` catches exceptions that arise from the ''execution'' of its IO argument action. Correct versions of this program would include changing `abort` to `abort :: Stack -> IO a; abort x = throwIO $ ...` or changing `C.catch (abort "fail")` to `C.catch (evaluate (abort "fail"))`. But I'm not sure that there is any way currently to, given an (unevaluated) IO action, evaulate it and execute it, catching exceptions raised by either step. A possible attempt would be `catch (do { a <- evaluate action; a })`, but would GHC see through this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11555: catch under unsafePerformIO breaks on -O1 to catch _|_ breaks at -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11555: catch under unsafePerformIO breaks on -O1 to catch _|_ breaks at -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by NeilMitchell): The current title is inaccurate - this ticket is all about {{{catch _|_}}}, and has nothing to do with {{{unsafePerformIO}}}. The question is whether {{{catch _|_}}} should evaluate to {{{_|_}}} or {{{Left}}}. I observe that in all previous releases of GHC, and at {{{-O0}}}, it's been {{{Left}}}. In two applications that have excellent test suites and have upgraded to GHC 8.0RC2 this issue has been flagged as a breaking change, so I suspect that it might be relatively widespread. As to what it should do, it seems unfortunate to argue that {{{catch undefined}}} is itself undefined. What's the semantics of {{{catch (return () >> undefined)}}}? If it's not equivalent to {{{catch undefined}}} then it's problematic for the Monad laws. I think it's reasonable in a lazy language that a function only evaluates its arguments when it has to. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11555: catch _|_ breaks at -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): Aah, sorry, I'm just incompetent at Trac this morning. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11555: catch _|_ breaks at -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): So consider {{{ f x = catch (g x) <recovery-code> }}} where `g` is strict in `x`; perhaps {{{ g x = if x>0 then <something> else <something else> }}} Now, are we allowed to use call-by-value on `f`? If 'no' then we are forced to use lazy evaluation and thunk creation in inner loops of the I/O system (for example). This can have a very material performance impact. Being able do to this sort of code motion is what "The semantics of imprecise exceptions" was all about and, combined with `unsafePerformIO`, you can indeed get unpredictable behaviour. There certainly ought to be a way of saying "evaluate this free variable right at this point",and there is: `evaluate` is just what you need. Indeed if you replace `abort "fail"` with `evaluate (abort "fail")` then the program behaves the same no matter how you compile it. But, I grant you, this makes my head hurt, and needs a careful writeup. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11555: catch _|_ breaks at -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by NeilMitchell): Note that the second example involves no {{{unsafePerformIO}}}, so it's surprisingly semantics just with imprecise exceptions alone. My personal expectation is that yes, you would have to create a thunk for {{{g}}} - but my expectations rarely match the lazy exception semantics. If alternatively you argue that one valid interpretation is {{{catch _|_ x = _|_}}}, then why not define: {{{#!hs catch !a b = ... }}} I suspect having a lazy first argument never improves performance, and now it's always picking the same semantics at all optimisation levels. Note that in the above examples {{{evaluate}}} is a sufficient trick, but for Shake only because I reduced the example. In the real code it takes an argument of type {{{IO a}}}. I think a correct general workaround is: {{{#!hs safeCatch a b = catch (join $ evaluate a) b }}} But it would be good to get someone who fully understands the semantics to declare this a "safe" trick. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11555: catch _|_ breaks at -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): We could provide both `catch`-made-strict and `safeCatch`, and maybe discuss which should be the "default" in the sense of using the existing name `catch`. Though it's not just `catch`, there's `try` and other related functions as well. Maybe better to add a new `execute a = join (evaluate a)`. Simon, you wrote elsewhere (ticket:10712#comment:22):
`catch` is ''not'' strict in its argument. Its argument is a function; `catch` just guarantees to call that function.
But I don't understand. Really `catch` has two arguments `catch act handler` and we're talking about strictness in `act`. Isn't `catch` strict in `act` (once applied to `handler`)? If `act` itself is _|_ then we are saying (in #10712) then `catch act handler` is allowed to be _|_. The funny property of `catch` comes in the fact that even though `catch` is going to ''apply'' `act`, it is not strict in that application because of its magical turning-bottom-into-non-bottom property. So, doesn't `catch` just have the same strictness in `act` as does, say, `seq` at a function type? Similarly I don't understand this excerpt from Note [Exceptions and strictness]:
This also applies uniformly to free variables. Consider {{{ let r = \st -> raiseIO# blah st in catch# (\s -> ...(r s')..) handler st }}} If we give the first argument of catch a strict signature, we'll get a demand 'C(S)' for 'r'; that is, 'r' is definitely called with one argument, which indeed it is.
Why can't we give `catch#` a signature that says it is strict in its argument, without necessarily ''calling'' that argument? Just like `seq`. I see that 9915b6564403a6d17651e9969e9ea5d7d7e78e7f is quite a large commit, so likely I'm missing the whole picture. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11555: catch _|_ breaks at -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by NeilMitchell): I talked to Simon offline a few days ago, after that I believe his opinion was: * {{{catch#}}} should remain strict in it's first argument. * {{{catch a b = catch# (lazy a) b}}} is the correct way to express the laziness, the {{{evaluate}}} trick certainly avoids the problem for now, but it may not be robust in the future. * There are places in the IO subsystem which get a significant benefit from a strict catch, they should use a more primitive version ({{{strictCatch}}} or something). * The default exposed {{{catch}}} (and also {{{try}}}, {{{handle}}} etc) should use {{{lazy}}}. All these functions seem to share the same underlying entry point, so that shouldn't be hard. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11555: catch _|_ breaks at -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by NeilMitchell): I have tried the two suggestions for "lazy catch", namely: {{{#!hs safeCatch1 a b = join (evaluate a) `catch` b safeCatch2 a b = lazy a `catch` b }}} Both work in isolation on the tiny example. Only {{{safeCatch1}}} works in the Shake test suite, with {{{safeCatch2}}} I get the same error as before. That suggests that {{{lazy}}} is somehow insufficient to obtain the original behaviour. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11555: catch _|_ breaks at -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Neil: re comment:12, can you boil out a smaller test case that shows what goes wrong with `safeCatch2`? Thanks! Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11555: catch _|_ breaks at -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by NeilMitchell): * Attachment "Test.hs" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11555: catch _|_ breaks at -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by NeilMitchell): Given the attached Test.hs, I run: {{{ ghc --make Test.hs -outputdir old -O1 -o test_old && test_old ghc --make Test.hs -outputdir new -O1 -DNEW -o test_new && test_new }}} The first prints SUCCESS (the catch worked, using {{{safeCatch1}}}). The second prints FAILURE (the catch failed, using {{{safeCatch2}}}). All tests carried out with GHC 8.0.0.20160205 on Windows. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11555: catch _|_ breaks at -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Very helpful! I know what is happening. Everything works fine until `CorePrep`. At that point we have {{{ catch# (lazy (f x)) blah }}} Now `CorePrep` * Replaces `lazy e` by `e` * Converts to ANF, using `let` or `case` depending on whether the function is strict Unfortunately, that results in {{{ case f x of r -> catch# r blah }}} which is wrong of course. We need that `lazy` to defeat the call-by-value transformation too. So our fix is right; this is really a bug in the implementation of `lazy`. I don't have a fix for this yet, but we have some progress. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11555: catch _|_ breaks at -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: patch Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1973 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D1973 Comment: Phab:D1973 performs carries out the changes proposed in comment:11; Phab:D1972 changes a few points in the IO system to use the strict `catchException`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11555: catch _|_ breaks at -O1
-------------------------------------+-------------------------------------
Reporter: slyfox | Owner:
Type: bug | Status: patch
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 8.0.1-rc2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect result | Unknown/Multiple
at runtime | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1973
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#11555: catch _|_ breaks at -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: patch Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1973 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): OK, so pls merge the patch in comnent:17. And could you please add Neil's test in comment:14 as a regression test? Neil: I think this should work for you now. Thanks Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11555: catch _|_ breaks at -O1
-------------------------------------+-------------------------------------
Reporter: slyfox | Owner:
Type: bug | Status: patch
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 8.0.1-rc2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect result | Unknown/Multiple
at runtime | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1973
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11555: catch _|_ breaks at -O1
-------------------------------------+-------------------------------------
Reporter: slyfox | Owner:
Type: bug | Status: patch
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 8.0.1-rc2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect result | Unknown/Multiple
at runtime | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1973
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11555: catch _|_ breaks at -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: merge Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1973 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge Comment: Need to merge 4c3a0a4a, 30ee9102, c937f424e4acd61d1c558e8fe9b47e7d580fdbd8, and a1c4230e15cbf897b97903c8a1199a1cc91efd26 to `ghc-8.0`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11555: catch _|_ breaks at -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1973 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to 8.0. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11555: catch _|_ breaks at -O1
-------------------------------------+-------------------------------------
Reporter: slyfox | Owner:
Type: bug | Status: closed
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 8.0.1-rc2
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect result | Unknown/Multiple
at runtime | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1973
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11555: catch _|_ breaks at -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: fixed | Keywords: Exceptions Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1973 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => Exceptions -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11555#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC