[GHC] #11254: GHC panic

#11254: GHC panic ----------------------------------------+--------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Keywords: | Operating System: Linux Architecture: Unknown/Multiple | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: ----------------------------------------+--------------------------------- I like to mix features to make code fail, code inspired by [https://phabricator.haskell.org/diffusion/GHC/browse/master/testsuite/tests /indexed-types/should_compile/T10318.hs$1 T10318]: {{{#!hs -- /tmp/panic.hs {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE InstanceSigs #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE UndecidableSuperClasses #-} class (Frac (Frac a) ~ Frac a, Fractional (Frac a), ID (Frac a)) => ID a where type Frac a embed :: a -> Frac a instance ID Rational where type Frac Rational = Int embed :: Rational -> Rational embed = undefined }}} When running it with `defer-type-errors` it causes GHC to panic: {{{#!hs % ghci -fdefer-type-errors -ignore-dot-ghci panic.hs &> panic.log }}} actual error included in panic.log. GHC asks me to report this as a bug and I do as I'm told. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11254 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11254: GHC panic ---------------------------------+---------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by Iceland_jack): * Attachment "panic.log" added. Output of ghci -fdefer-type-errors -ignore-dot-ghci panic.hs -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11254 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11254: GHC panic ---------------------------------+---------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by Iceland_jack): * Attachment "panic.hs" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11254 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11254: GHC panic ---------------------------------+---------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by simonpj): * owner: => goldfire Comment: Richard, what is the story for deferred type errors? We get a Lint error from the program as follows {{{ cobox_aPt :: Ratio Integer ~# Int [LclId[CoVarId], Str=DmdType] cobox_aPt = typeError @ 'Unlifted @ (Ratio Integer ~# Int) "T11254.hs:16:12: error:...blah..blah... "# $cembed_aP2 :: Rational -> Frac Rational [LclId, Str=DmdType] $cembed_aP2 = (...blah....) `cast` (<Rational>_R -> Sub (cobox_aPt ; Sym TFCo:R:FracRatio[0]) }}} So we have a top-level unboxed value. That's not right. What became of coercion holes? Obviously the can't call `error`. Writing a `Note` about how deferred type errors fits with unlifted equalities would be great. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11254#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11254: GHC panic ---------------------------------+---------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by goldfire): From TcErrors: {{{ Note [Deferred errors for coercion holes] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Suppose we need to defer a type error where the destination for the evidence is a coercion hole. We can't just put the error in the hole, because we can't make an erroneous coercion. (Remember that coercions are erased for runtime.) Instead, we invent a new EvVar, bind it to an error and then make a coercion from that EvVar, filling the hole with that coercion. Because coercions' types are unlifted, the error is guaranteed to be hit before we get to the coercion. }}} But that's admittedly not the whole story. This also matters, from `TcUnify.buildImplication`: {{{ -- But with the solver producing unlifted equalities, we need -- to have an EvBindsVar for them when they might be deferred to -- runtime. Otherwise, they end up as top-level unlifted bindings, -- which are verboten. See also Note [Deferred errors for coercion holes] -- in TcErrors. }}} The comment describes a check to make sure that we always build an implication when `-fdefer-type-errors` is on (and we're at top-level). I noticed an unexpected `pushTcLevelM` at !TcInstDecls:811 that may throw this check off. Do you have a recommendation for how to improve the documentation? I'll look into this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11254#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11254: GHC panic ---------------------------------+---------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by goldfire): I've looked into it. And I can't think of a convenient solution to the problem, which is restricted to instance signatures that produce a deferred type error. The problem is that deferred type errors absolutely must have an enclosing, non-top-level `EvBindsVar` in which to put the error. That's because the deferred type error is now unlifted and so cannot appear at top level. This is also why we can't have deferred kind errors, though there is logic to detect that and report an error without producing bad Core. With instance signatures, the (ab)use of `AbsBinds` means there's just not the right spot to put the `HsWrapper` that does the signature impedence- matching in a spot where the local evidence bindings are in scope. I could create such a spot, but that just doesn't seem like the right way forward. But wait! I've solved it! In parallel, I'm working on rushing my visible- type-application stuff to make it before the feature freeze. It turns out that it needed just such a spot, too, so I'll just reuse it here. So, we just have to wait a few days. :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11254#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11254: GHC panic
---------------------------------+----------------------------------------
Reporter: Iceland_jack | Owner: goldfire
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.11
Resolution: | Keywords:
Operating System: Linux | Architecture: Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
---------------------------------+----------------------------------------
Comment (by Richard Eisenberg

#11254: GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T11254 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * testcase: => typecheck/should_compile/T11254 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11254#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11254: GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T11254 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Fixed? Or still to do? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11254#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11254: GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T11254 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Still to do. But with visible types in, I know how to fix. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11254#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11254: GHC panic
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: goldfire
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.11
Resolution: | Keywords:
Operating System: Linux | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
| typecheck/should_compile/T11254
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#11254: GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T11254 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11254#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11254: GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: merge Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T11254 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * milestone: => 8.0.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11254#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11254: GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T11254 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Cherry-picked to `ghc-8.0` as 4c53ab2a108a749ae45657c73cda233b528fb029. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11254#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC