[GHC] #10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: base/tests/exceptionsrun001 | Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- The following program, extracted from the test exceptionsrun001, should exit with exitcode 100. Instead, when compiled with `-O1`, it never gets past the ioTest and somehow manages to exit with exitcode 0. {{{ {-# LANGUAGE ScopedTypeVariables #-} module Main where import Control.Exception import System.IO.Error import System.Exit main = do ioTest exitWith (ExitFailure 100) ioTest :: IO () ioTest = (catch (ioError (userError "wibble")) (\(e::IOException) -> return ()) }}} I think this will require a git bisect: * last known good commit: 34bb4605d4ec5b131df57ca4c91d6840b7539194 * first known bad commit: f83aab95f59ae9b29f22fc7924e050512229cb9c. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10712 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): Other tests that are failing with WAY=optasm, all dealing with exceptions of some sort: * T3279 * conc012 * conc014 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10712#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): I'll bisect and see what I find (if you aren't doing so already). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10712#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Actually I just guessed and checked, 7c0fff41789669450b02dc1db7f5d7babba5dee6 is the bad commit. {{{ catch (ioError (userError "wibble")) (\(e::IOException) -> return ()) }}} amounts to {{{ catch# (raiseIO# (toException (userError "wibble"))) ({- handler -}) st }}} but * `raiseIO#`'s strictness signature claims it returns _|_ * `catch#` is now strict in its first argument, as of the commit 7c0fff41789 so the strictness analyser concludes that `ioTest` will never return, and optimizes `main` to {{{ Main.main1 = \ (@ b_aLH) (s_X2HT [OS=OneShot] :: State# RealWorld) -> case Main.ioTest1 s_X2HT of wild_00 { } }}} and what happens then when `ioTest` really does return is undefined. There are apparently good reasons for each of the two bulleted points, but as this test shows they are incompatible. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10712#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * cc: simonmar (added) Comment: Bother. I totally missed that. I think it's reasonable that this should allow the exception to be raised somewhere else (imprecisely): {{{ catch# (\s -> (raise# blah) `seq` blah2) (...) st }}} because `raise#` is in the pure world. But `raiseIO#` is specifically intended to raise an exception precisely at the specified moment, so the new behaviour is unacceptable. Now I think about this more I'm also worried about {{{ let r = \st -> raiseIO# blah st in catch (\st -> ...(r st)..) handler st }}} Now that I'm given `catch` a more aggressive strictness, I'll get a demand `C(S)` for `r`; that is, it is definitly called with one argument. And so it is! But the danger is that we'll feed `C(S)` into `r`'s rhs as the demand of the body, and say that that whole `let` will definitely diverge (which isn't true). However, we ''really'' want this function to be strict in `x`: {{{ f x st = catch (\s -> case x of I# x' -> ...) handler st }}} Getting this strictness was the whole point of the offending commit: {{{ Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- hpg -0.4% -2.9% -0.9% -1.0% +0.0% reverse-complem -0.4% -10.9% +10.7% +10.9% +0.0% simple -0.3% -0.0% +26.2% +26.2% +3.7% sphere -0.3% -6.3% 0.09 0.09 +0.0% -------------------------------------------------------------------------------- Min -0.7% -10.9% -4.6% -4.7% -1.7% Max -0.2% +0.0% +26.2% +26.2% +6.5% Geometric Mean -0.4% -0.3% +2.1% +2.1% +0.1% }}} There's something very special about `catch`: it turns divergence into non-divergence. (The strictness analyser treats divergence and exceptions identically.) I think #8598 is relevant. Bother bother. I'm really not sure what to do. Even if we revert, we should not revert all, just the strictness signatures for the `catch` primops. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10712#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing
-------------------------------------+-------------------------------------
Reporter: thomie | Owner:
Type: bug | Status: new
Priority: high | Milestone: 7.12.1
Component: Compiler | Version: 7.11
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
| base/tests/exceptionsrun001
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Thomas Miedema

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: high => highest Old description:
The following program, extracted from the test exceptionsrun001, should exit with exitcode 100. Instead, when compiled with `-O1`, it never gets past the ioTest and somehow manages to exit with exitcode 0.
{{{ {-# LANGUAGE ScopedTypeVariables #-} module Main where
import Control.Exception import System.IO.Error import System.Exit
main = do ioTest exitWith (ExitFailure 100)
ioTest :: IO () ioTest = (catch (ioError (userError "wibble")) (\(e::IOException) -> return ()) }}}
I think this will require a git bisect: * last known good commit: 34bb4605d4ec5b131df57ca4c91d6840b7539194 * first known bad commit: f83aab95f59ae9b29f22fc7924e050512229cb9c.
New description: The following program, extracted from the test exceptionsrun001, should exit with exitcode 100. Instead, when compiled with `-O1`, it never gets past the ioTest and somehow manages to exit with exitcode 0. {{{#!hs {-# LANGUAGE ScopedTypeVariables #-} module Main where import Control.Exception import System.IO.Error import System.Exit main = do ioTest exitWith (ExitFailure 100) ioTest :: IO () ioTest = (catch (ioError (userError "wibble")) (\(e::IOException) -> return ()) }}} I think this will require a git bisect: * last known good commit: 34bb4605d4ec5b131df57ca4c91d6840b7539194 * first known bad commit: f83aab95f59ae9b29f22fc7924e050512229cb9c. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10712#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Just possibly related #7411 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10712#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: patch Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1616 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D1616 Comment: I have opened Phab:D1616 with what I believe is a fix for this. I have also opened #11222 to track the fact that currently we are forced to pessimize our strictness signatures on `catch`-like operations. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10712#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing
-------------------------------------+-------------------------------------
Reporter: thomie | Owner:
Type: bug | Status: patch
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 7.11
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
| base/tests/exceptionsrun001
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1616
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1616 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed Comment: Fixed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10712#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1616 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: closed => new * resolution: fixed => Comment: thomie correctly pointed out that this patch did not actually fix the four failing testcases marked in 3b233793. Looks like I'll need to dive a bit deeper. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10712#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing
-------------------------------------+-------------------------------------
Reporter: thomie | Owner:
Type: bug | Status: new
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 7.11
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
| base/tests/exceptionsrun001
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1616
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Thomas Miedema

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1616 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed Comment: Your patch did fix the bug, the four failing tests just had to marked as 'normal' again. All done now. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10712#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing
-------------------------------------+-------------------------------------
Reporter: thomie | Owner:
Type: bug | Status: closed
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 7.11
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
| base/tests/exceptionsrun001
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1616
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1616 Wiki Page: | -------------------------------------+------------------------------------- Changes (by rwbarton): * status: closed => new * resolution: fixed => Comment: Commit [changeset:"9915b6564403a6d17651e9969e9ea5d7d7e78e7f/ghc" 9915b656/ghc] broke the tests that had been fixed in [changeset:"28638dfe79e915f33d75a1b22c5adce9e2b62b97/ghc" 28638df/ghc] again, namely: {{{ make slowtest TEST='exceptionsrun001 T3279 conc012 conc014' }}} (Note that the ways that broke, including optasm, are not run by validate by default.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10712#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1616 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Are you sure? exceptionsrun001 seems OK to me. It turns out that the other three all relied on imprecise exceptions being precise. Eg conc012 has {{{ forkIO $ Control.Exception.catch (x `seq` putMVar result Finished) $ }}} If you want to be sure that `x` will only be evaluated under the `catch` you must use `evaluate` thus: {{{ forkIO $ Control.Exception.catch (evaluate x >> putMVar result Finished) $ }}} Similarly conc014 had {{{ error "wibble" `Control.Exception.catch` ... }}} But the `error "wibble"` is a pure bottom value and we make no guarantees about when it is evaluated. It should be more like {{{ throwIO (ErrorCall "wibble") `Control.Exception.catch` .... }}} which raises the exception in the IO monad (i.e. precisely). Same with `T3279`, which had {{{ error "foo" `catch` \(SomeException e) -> do }}} Again that `error "foo"` should be `throwIO (ErrorCall "foo")`. Incidentally, is there a function for `throwIO . ErrorCall`? I'll make a patch for these three tests. Then I claim we are done. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10712#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing
-------------------------------------+-------------------------------------
Reporter: thomie | Owner:
Type: bug | Status: new
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 7.11
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
| base/tests/exceptionsrun001
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1616
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1616 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10712#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1616 Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): `exceptionsrun001` still fails for me in the `hpc` way. Could it be OS- dependent? {{{ rwbarton@morphism:~/ghc-newest/testsuite/tests$ make TEST=exceptionsrun001 WAY=hpc [...] =====> exceptionsrun001(hpc) 1 of 1 [0, 0, 0] cd ../../libraries/base/tests && "/home/rwbarton/ghc-newest/inplace/test spaces/ghc-stage2" -o exceptionsrun001 exceptionsrun001.hs -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output -no-user-package-db -rtsopts -fno-warn-tabs -fno-warn-missed-specialisations -fno-ghci-history -O -fhpc -hpcdir .hpc.exceptionsrun001 > exceptionsrun001.comp.stderr 2>&1 cd ../../libraries/base/tests && ./exceptionsrun001 exceptionsrun001.run.stdout 2> exceptionsrun001.run.stderr Wrong exit code (expected 0 , actual 1 ) Stdout: user exception caught error call caught no method error Stderr: exceptionsrun001: exceptionsrun001.hs:38:1-13: Non-exhaustive patterns in function test1 *** unexpected failure for exceptionsrun001(hpc) Unexpected results from: TEST="exceptionsrun001" OVERALL SUMMARY for test run started at Thu Jan 28 11:30:04 2016 EST 0:00:01 spent to go through 1 total tests, which gave rise to 10 test cases, of which 9 were skipped 0 had missing libraries 0 expected passes 0 expected failures 0 caused framework failures 0 unexpected passes 1 unexpected failures 0 unexpected stat failures Unexpected failures: ../../libraries/base/tests exceptionsrun001 [bad exit code] (hpc) }}} I will try to look into why. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10712#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1616 Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): Well the test is wrong in the same way as the others. {{{ patMatchTest = catch (case test1 [1..10] of () -> return ()) (...) }}} where `test1 [1..10]` results in a pattern match failure. Maybe the best question is why the test ''doesn't'' fail with way optasm. After all why not evaluate `case test1 [1..10] of () -> return ()` first, if `catch` is strict in that argument. That argument becomes (up to a coercion) {{{ a_s2uX :: GHC.Prim.State# GHC.Prim.RealWorld -> (# GHC.Prim.State# GHC.Prim.RealWorld, () #) [LclId, Arity=1, Str=DmdType, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [0] 290 30}] a_s2uX = \ (eta_B1 [OS=OneShot] :: GHC.Prim.State# GHC.Prim.RealWorld) -> case GHC.Base.build @ Integer (\ (@ b_a2uz) (c_a2uA [OS=OneShot] :: Integer -> b_a2uz -> b_a2uz) (n_a2uB [OS=OneShot] :: b_a2uz) -> GHC.Enum.enumDeltaToInteger1FB @ b_a2uz c_a2uA n_a2uB 1 10) of _ [Occ=Dead] { [] -> (# eta_B1, GHC.Tuple.() #); : ipv_s2hb ipv_s2hc -> case lvl_s2v4 of wild_00 { } } }}} Perhaps some of the `Value=True, ConLike=True, WorkFree=True, Expandable=True` flags are causing the value not to get evaluated eagerly. Is that what GHC should be doing? (The hpc version has all those flags set to `False`, maybe because of the ticks wrapping the expression, or because the coercion was not removed yet: the hpc version of this binding has type `IO ()` still.) Anyways, GHC's behavior is correct either way, but maybe there is something to learn here before fixing the test. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10712#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1616 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): `catch` is ''not'' strict in its argument. Its argument is a function; `catch` just guarantees to call that function. So yes `build (...)` is sure to be evaluated, but GHC doesn't aggressively evaluate things as early as possible. It just uses strictness info to avoid building thunks; and none are built here. So I think it's fine. Might be wroth fixing the test though. Thanks for the accurate diagnosis. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10712#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Exceptions Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1616 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => Exceptions -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10712#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC