Constraint-vs-Type causes a panic
@monoidal observes in #11715 (comment 375240) that
{-# LANGUAGE TypeFamilies, PolyKinds, ConstraintKinds #-}
import GHC.Types
type family Id (a :: k -> Constraint) :: l -> Constraint
type instance Id f = f
type T :: Constraint -> Constraint
type T = Id Eq
data Proxy p = MkProxy
id' :: f a -> f a
id' x = x
z = id' (MkProxy @T)
causes
<no location info>: error:
panic! (the 'impossible' happened)
GHC version 9.3.20210824:
ASSERT failed!
Ill-kinded update to meta tyvar
a_aIJ[tau:1] :: Constraint -> Constraint
Constraint -> Constraint := Eq :: * -> Constraint
Call stack:
CallStack (from HasCallStack):
massertPpr, called at compiler/GHC/Tc/Utils/TcMType.hs:1009:10 in ghc:GHC.Tc.Utils.TcMType
when assertions are enabled (e.g. a DEBUG
compiler).
Constraint-vs-Type is a difficult problem (see #11715 (closed)), but I think we can pull this off and fix it. I imagine we just need to change an eqType
to tcEqType
somewhere.