[GHC] #10176: Invalid core generated with GHC 7.10 RC3

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: | Owner: NeilMitchell | Status: new Type: bug | Milestone: Priority: high | Version: 7.8.4 Component: Compiler | Operating System: Unknown/Multiple Keywords: | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Using the Shake repo (https://github.com/ndmitchell/shake.git) at commit d7fa04 and GHC 7.10 RC3 or GHC HEAD, if I {{cabal test}} I get the error: {{{ ## BUILD oracle --quiet *str-int TESTS FAILED shake-test: Expected an exception but succeeded }}} Discussion about this issue can be found on the mailing list: http://osdir.com/ml/general/2015-03/msg25847.html GHC generates the Core: {{{ case (\_ -> error "here") of {} }}} This is invalid GHC Core. I intend to track down a minimal example shortly. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by hvr): Fyi, I scripted up a test and git-bisected between RC2 and RC3, and the 6f46fe15af397d448438c6b93babcdd68dd78df8 commit is the one where `shake- test oracle test` starts failing -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.10.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by hvr): * version: 7.8.4 => 7.10.1-rc3 * milestone: => 7.10.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3
-------------------------------------+-------------------------------------
Reporter: NeilMitchell | Owner:
Type: bug | Status: new
Priority: high | Milestone: 7.10.1
Component: Compiler | Version: 7.10.1-rc3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Blocked By: | Test Case:
Related Tickets: | Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by NeilMitchell):
Running {{{ghc -outputdir obj -O -ddump-simpl Buggy.hs}}} produces the
output:
{{{
case (\ _ [Occ=Dead] _ [Occ=Dead, OS=OneShot] ->
case lvl_r1lh unit_XyJ of wild2_00 { })
`cast` ((<()>_R -> Sym (GHC.Types.NTCo:IO[0]

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.10.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by hvr): Fwiw, I see GHC 7.8.4 producing similiar Core (with `-dsuppress-all -dsuppress-uniques`): {{{#!hs a = \ fun unit1 bool eta -> case bool of _ { False -> case fun unit1 of _ { False -> (# eta, () #); True -> case m of wild2 { } }; True -> case hPutStr2 stdout shows3 True eta of _ { (# ipv, ipv1 #) -> case fun unit1 of _ { False -> (# ipv, () #); True -> case m of wild2 { } } } } }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.10.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by NeilMitchell): That's quite different since (after inlining a few bits): {{{ $wlvl $wlvl = \ _ -> error "here" m = $wlvl void# }}} So {{{m}}} evaluates to {{{_|_}}} in GHC 7.8 which means a case with no alternatives is correct. However, in 7.10 the scrutinee evaluates to a lambda, not {{{_|_}}}, so no alternatives is wrong. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.10.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): After adding a lint check as suggested by SPJ, I simplified your example to {{{ module Buggy(buggy) where {-# NOINLINE error1Arg #-} error1Arg :: () -> a error1Arg _ = undefined {-# NOINLINE buggy #-} buggy :: a buggy = error1Arg () () }}} but I’m not sure if the lint check is actually correct here, as this is the core it complains about: {{{ *** Core Lint errors : in result of Simplifier *** Buggy.hs:9:10: Warning: [in body of lambda with binder a_an8 :: *] No alternatives for HNF scrutinee error1Arg @ (() -> a_an8) () *** Offending Program *** error1Arg [InlPrag=NOINLINE] :: forall a_an0. () -> a_an0 [LclId, Arity=2, CallArity=2, Str=DmdType b] error1Arg = \ (@ a_anf) _ [Occ=Dead, Dmd=] -> undefined @ a_anf buggy [InlPrag=NOINLINE] :: forall a_amZ. a_amZ [LclIdX, Str=DmdType b] buggy = \ (@ a_an8) -> case error1Arg @ (() -> a_an8) () of wild_00 { } *** End of Offense *** }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.10.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Eek. This seems to be my fault: Note the `CallArity=2`. And indeed, with `-fno-call-arity` this passes; same for your test case. :-( -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.10.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by NeilMitchell): I was expecting a simple pattern match on {{{(Case Lam{} _ _ [])}}}, what does your diff look like? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.10.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Ok, I think here is what happens, at least in my smaller test case: 1. Call Arity determines that `error1Arg` is always called with two arguments. Hence `CallArity=2`. This is correct. 2. The simplifier tries to eta-expand `error1Arg` to take two arguments. This fails in `mkEtaWW` in `CoreArity`, where we have this comment: {{{ -- This *can* legitmately happen: -- e.g. coerce Int (\x. x) Essentially the programmer is -- playing fast and loose with types (Happy does this a lot). -- So we simply decline to eta-expand. Otherwise we'd end up -- with an explicit lambda having a non-function type }}} 3. But still, the `Arity` field is updated. 4. Since it has `Arity=2`, `exprIsHNF (error1Arg @ _ ())` is true, and the simplifier does strange things. So maybe the solution is to ''not'' update `Arity` with the result from Call Arity, but instead let eta-expansion happen and update `Arity` with the manifest arity after eta expansion. I’ll try that. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.10.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Ok, I might have found a suitable fix. You can have a look at Phab:D747, although it’s still pending validation (and the new lint check might yet uncover other problems). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.10.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Or not quite. I think I did find a bug, but not the only one: With the change in Phab:D747, my small example and your example, when merged into one module, no longer fail. But your original test case still fails with Call Arity, and compiles fine without. There still seems to be some fishiness with Call Arity and `undefined`. /me continues brooding over the Core. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.10.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by hvr): not sure if this is useful information, but I compared the output of {{{ ghc -fforce-recomp -outputdir obj -O -ddump-simpl -dsuppress-uniques Buggy.hs }}} for acbfc19a6d27b51aaec5177e4b64ea9b45f74c84 (recent ghc-7.10 branch snapshot) vs. 029a296a770addbd096bbfd6de0936327ee620d4 (one commit before the big typeable-change that caused `shake-test oracle test` to start failing) And well, the Core output looks just the same, so I'm not sure if the `Buggy.hs`/`Errors.hs` test-case highlights the same issue causing `shake- test` to fail. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.10.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): I simplified your code slightly, removing everything about type classes: {{{ module Buggy(buggy) where import Errors newtype ReaderT r a = ReaderT { runReaderT :: r -> IO a } p = liftReaderT (return ()) m >>> k = ReaderT $ \r -> do runReaderT m r; runReaderT k r liftReaderT :: IO a -> ReaderT r a liftReaderT m = ReaderT (const m) {-# NOINLINE buggy #-} buggy :: (() -> Bool) -> () -> Bool -> IO () buggy fun unit bool = runReaderT ( (if bool then liftReaderT $ print () else p) >>> (if fun unit then error2Args unit unit >>> p else p)) () }}} still exhibits the problem. Removing the `newtype`, or turning it into a `data` makes the problem go away. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.10.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Also, changing the code to {{{ newtype Fun a b = Fun { runFun :: a -> b } type ReaderT r x = Fun r (IO x) }}} makes the problem go away. Must be some weird interaction with coercions... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3
-------------------------------------+-------------------------------------
Reporter: NeilMitchell | Owner:
Type: bug | Status: new
Priority: high | Milestone: 7.10.1
Component: Compiler | Version: 7.10.1-rc3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Blocked By: | Test Case:
Related Tickets: | Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by nomeata):
I think I found it. The problem is a bad interaction between Call Arity
and simplification based on the strictness result.
Consider this code:
{{{
e x = error "foo" x
... case e () () of {} ...
}}}
The strictness signature for `e` will be `

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: patch Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.10.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by nomeata): * status: new => patch Comment: Ok, validates. Does someone want to make sure I’m not talking complete nonsense before I merge this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: patch Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.10.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by NeilMitchell): To assess what does happen in this error case, I augmented the code to be: {{{ buggy fun unit bool = runReaderT (do if bool then liftReaderT $ print () else pure () if fun unit then do error2Args unit unit; liftReaderT $ print "here2" else pure () ) () :: IO () }}} Running {{{do print "here1"; buggy (const True) () True; print "here3"}}} gives {{{here1; here3}}}. GHC has used the presence of error to remove the {{{here2}}}, but since the code just falls out of the end of the function it returns back and still prints {{{here3}}}. That's a nasty result, and pretty much describes what happens in the full test case (I'm in the middle of compiling, and then suddenly I stop and do the thing that comes after compiling). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: patch Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.10.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): I've checked Phab:D747 which looks great to me; i've made some suggestions. Maybe we can turn comment:17 into a test that not only should compile (as D747 has) but should run also. thanks! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: patch Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.10.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by hvr): I can confirm that 1cc46b1fd5ce794d3a1519c65dcf4aded317598b + phab:D747 allows `shake-test oracle test` to succeed! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: nomeata Type: bug | Status: patch Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.10.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by hvr): * owner: => nomeata -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3
-------------------------------------+-------------------------------------
Reporter: NeilMitchell | Owner: nomeata
Type: bug | Status: patch
Priority: high | Milestone: 7.10.1
Component: Compiler | Version: 7.10.1-rc3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Blocked By: | Test Case:
Related Tickets: | Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Joachim Breitner

#10176: Invalid core generated with GHC 7.10 RC3
-------------------------------------+-------------------------------------
Reporter: NeilMitchell | Owner: nomeata
Type: bug | Status: patch
Priority: high | Milestone: 7.10.1
Component: Compiler | Version: 7.10.1-rc3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Blocked By: | Test Case:
Related Tickets: | Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Joachim Breitner

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: nomeata Type: bug | Status: merge Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.10.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by nomeata): * status: patch => merge Comment: Pushed. hvr, you said you wanted this to be in 7.10, so marking it as merge. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: nomeata Type: bug | Status: closed Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.10.1-rc3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by hvr): * status: merge => closed * resolution: => fixed Comment: I've merged (& validated) the fix & test (but not the linter-change) to ghc-7.10 via 011f691333aff2833acc900ee3911885e488cf1b & 7e1758a9cf86c28440834d3e3d44737186e5ca5f respectively. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10176: Invalid core generated with GHC 7.10 RC3 -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: nomeata Type: bug | Status: closed Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.10.1-rc3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Thanks. Note that the test case is quite useless without the lint (but doesn’t hurt either so just leave it like it is). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10176#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC