
#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