
#13487: GHC panic with deferred custom type errors -------------------------------------+------------------------------------- Reporter: DimaSamoz | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * os: MacOS X => Unknown/Multiple * component: Compiler => GHCi * milestone: => 8.4.1 Comment: Thanks for the bug report! Here is a minimal file which exhibits the issue: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} module Mezzo where import Data.Kind (Constraint) import GHC.TypeLits data Foo a b where (:-:) :: Error a b => a -> b -> Foo a b type family Error a b :: Constraint where Error Int Int = () Error _ _ = TypeError ('Text "GHC panic in 3... 2... 1...") }}} Now load this into GHCi like so: {{{ $ /opt/ghc/8.2.1/bin/ghci Mezzo.hs -fdefer-type-errors GHCi, version 8.2.0.20170321: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Mezzo ( Mezzo.hs, interpreted ) Ok, modules loaded: Mezzo. λ> let v = 'a' :-: 'b' <interactive>:1:9: warning: [-Wdeferred-type-errors] • GHC panic in 3... 2... 1... • In the expression: 'a' :-: 'b' In an equation for ‘v’: v = 'a' :-: 'b' ghc: panic! (the 'impossible' happened) (GHC version 8.2.0.20170321 for x86_64-unknown-linux): nameModule system irred_a2AK Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1191:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1195:37 in ghc:Outputable pprPanic, called at compiler/basicTypes/Name.hs:239:3 in ghc:Name }}} I can reproduce this with 8.0.1, 8.0.2, 8.2.1, and HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13487#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler