
#15142: GHC HEAD regression: tcTyVarDetails -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.5 checker) | Keywords: TypeInType, Resolution: | TypeFamilies 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: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Comparing the results of `-ddump-tc-trace` on this program: {{{#!hs {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} module Bug where import Data.Kind class C (a :: Type) (b :: k) where type T b }}} On GHC 8.4.2, we have: {{{ kcTyClGroup: initial kinds [r1xu :-> ATcTyCon C :: forall k. * -> k -> Constraint, r1xA :-> ATcTyCon T :: forall k. k -> *] }}} But on GHC HEAD, we have: {{{ kcTyClGroup: initial kinds C :: forall k. * -> k -> Constraint T :: forall (k :: k_a1zm[tau:1]) (co :: k_a1zm[tau:1] GHC.Prim.~# *). (k |> {co_a1zq}) -> * }}} And indeed, `tcTyVarDetails` appears to be panicking on `co`. But I haven't the foggiest idea of what it's doing there... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15142#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler