[GHC] #14934: Repeated "impossible" go_axiom_rule error.

#14934: Repeated "impossible" go_axiom_rule error. -------------------------------------+------------------------------------- Reporter: galen | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I am getting the following error repeatedly: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.4.1 for x86_64-unknown-linux): go_axiom_rule Sub0R Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in ghc:Outputable pprPanic, called at compiler/iface/TcIface.hs:1371:15 in ghc:TcIface }}} I got it on 8.2.1, and tried upgrading to 8.4.1 to see if it went away, but it did not. It occurs frequently when I do a `--make` and recompile a subset of modules. I can avoid it by force-recompiling all modules, although of course this is inefficient. Since I'm working with a codebase of thousands of lines and don't understand ghc's innards, I'm not sure where to start looking for the cause, to produce a minimal failing example. But it did start happening around the time I expanded my use of this module: https://github.com/agrafix/superrecord Since there are unsafe operations in there, it is possible it is doing something illicit, but it is hard to see how it would cause this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14934 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14934: Repeated "impossible" go_axiom_rule error. -------------------------------------+------------------------------------- Reporter: galen | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => infoneeded Comment: We'll likely need some more information before we can debug this. As a start, you mentioned that you experienced this bug when recompiling modules after a change, which isn't [https://ghc.haskell.org/trac/ghc/ticket/13695 unheard of]. Can you point us to a project of yours where: 1. Building it, 2. Making some change, and 3. Rebuilding Produces the panic? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14934#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14934: Repeated "impossible" go_axiom_rule error. -------------------------------------+------------------------------------- Reporter: galen | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): That being said, I have a wild hunch what could be causing this. [http://git.haskell.org/ghc.git/blob/0693b0b0500236a3dec933350a13f1b0e8c1cb54... Here] is where `go_axiom_co` is defined: {{{#!hs tcIfaceCo :: IfaceCoercion -> IfL Coercion tcIfaceCo = go where -- ... go (IfaceAxiomRuleCo ax cos) = AxiomRuleCo <$> go_axiom_rule ax <*> mapM go cos -- ... go_axiom_rule :: FastString -> IfL CoAxiomRule go_axiom_rule n = case Map.lookup n typeNatCoAxiomRules of Just ax -> return ax _ -> pprPanic "go_axiom_rule" (ppr n) }}} It seems that the `Sub0R` axiom isn't in [http://git.haskell.org/ghc.git/blob/0693b0b0500236a3dec933350a13f1b0e8c1cb54... typeNatCoAxiomRules]: {{{#!hs typeNatCoAxiomRules :: Map.Map FastString CoAxiomRule typeNatCoAxiomRules = Map.fromList $ map (\x -> (coaxrName x, x)) [ axAddDef , axMulDef , axExpDef , axLeqDef , axCmpNatDef , axCmpSymbolDef , axAppendSymbolDef , axAdd0L , axAdd0R , axMul0L , axMul0R , axMul1L , axMul1R , axExp1L , axExp0R , axExp1R , axLeqRefl , axCmpNatRefl , axCmpSymbolRefl , axLeq0L , axSubDef -- axSub0R isn't here!!! , axAppendSymbol0R , axAppendSymbol0L , axDivDef , axDiv1 , axModDef , axMod1 , axLogDef ] }}} So perhaps we should just add it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14934#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14934: Repeated "impossible" go_axiom_rule error. -------------------------------------+------------------------------------- Reporter: galen | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: infoneeded => new Comment: I can reproduce the issue now. Take these two files: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE TypeOperators #-} module Foo where import GHC.TypeLits data Foo :: Nat -> * where MkFoo0 :: Foo 0 MkFoo1 :: Foo 1 f :: Foo (1 - 0) -> Foo 1 f x = x }}} {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeOperators #-} module Bar where import Foo import GHC.TypeLits g :: Foo (1 - 0) g = f MkFoo1 {- h :: Foo (1 - 0) h = MkFoo1 -} }}} And perform the following steps: 1. Run `/opt/ghc/8.2.2/bin/ghc Bar.hs -O2`. 2. Uncomment out the definition of `h` in `Bar.hs`. 3. Re-run `/opt/ghc/8.2.2/bin/ghc Bar.hs -O2`: {{{ $ /opt/ghc/8.2.2/bin/ghc Bar.hs -O2 [1 of 2] Compiling Foo ( Foo.hs, Foo.o ) [2 of 2] Compiling Bar ( Bar.hs, Bar.o ) $ vim Bar.hs $ /opt/ghc/8.2.2/bin/ghc Bar.hs -O2 [2 of 2] Compiling Bar ( Bar.hs, Bar.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.2 for x86_64-unknown-linux): go_axiom_rule Sub0R Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/iface/TcIface.hs:1349:15 in ghc:TcIface }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14934#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14934: Repeated "impossible" go_axiom_rule error. -------------------------------------+------------------------------------- Reporter: galen | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by galen): Nice! The commenting/uncommenting of `h` is not even necessary. If I compile with it uncommented, do a `touch Bar.hs`, and recompile, I still get the error. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14934#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14934: Repeated "impossible" go_axiom_rule error. -------------------------------------+------------------------------------- Reporter: galen | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4508 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D4508 Comment: Or, for maximum terseness: {{{ $ ghc Foo.hs -c -O $ ghc Bar.hs -c -O ghc: panic! (the 'impossible' happened) (GHC version 8.2.2 for x86_64-unknown-linux): go_axiom_rule Sub0R Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/iface/TcIface.hs:1349:15 in ghc:TcIface }}} I'll use this as the regression test in Phab:D4508. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14934#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14934: Repeated "impossible" go_axiom_rule error.
-------------------------------------+-------------------------------------
Reporter: galen | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler | Version: 8.4.1
Resolution: | Keywords:
Operating System: Linux | Architecture: x86_64
Type of failure: Compile-time | (amd64)
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D4508
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#14934: Repeated "impossible" go_axiom_rule error. -------------------------------------+------------------------------------- Reporter: galen | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4508 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge * milestone: => 8.4.2 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14934#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14934: Repeated "impossible" go_axiom_rule error. -------------------------------------+------------------------------------- Reporter: galen | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4508 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.4`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14934#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC