Skip to content

GHC panics with unzonked kinds (typeOrConstraint & others)

Consider the following program:

module T26277 where

import Data.Kind

type FunLike :: forall {k}. (k -> k -> Type) -> Constraint
class FunLike p where
  myId :: p a a
instance FunLike (->) where
  myId = id

test x = myId @(->) x

With GHC 9.10, GHC 9.12 and HEAD, I get:

panic! (the 'impossible' happened)
  GHC version 9.15.20250723:
        typeOrConstraint
  a_aBk[tau:1] :: k_aBf[tau:1]
  Call stack:
      CallStack (from HasCallStack):
        pprPanic, called at compiler\GHC\Core\Type.hs:2743:14 in ghc-9.15-inplace:GHC.Core.Type
        typeTypeOrConstraint, called at compiler\GHC\Core\TyCo\Rep.hs:773:18 in ghc-9.15-inplace:GHC.Core.TyCo.Rep
        mkScaledFunTys, called at compiler\GHC\Tc\Utils\Unify.hs:802:33 in ghc-9.15-inplace:GHC.Tc.Utils.Unify

The problem is that we have a filled metavariable k_aBf := TYPE kappa, but several functions in the compiler expect the TYPE part to be directly visible (instead of requiring zonking); in this case it's the call to mkScaledFunTys in matchActualFunTy.

If we change matchActualFunTy to do a full representation-polymorphism check (as in !14357 (closed)), then instead we get an error like:

<no location info>: error:
    panic! (the 'impossible' happened)
  GHC version 9.15.20250801:
        unifyConcrete_kind: kind is not of the form 'TYPE rep' or 'CONSTRAINT rep'
  k_aBf[tau:1] :: *
  Call stack:
      CallStack (from HasCallStack):
        pprPanic, called at compiler\GHC\Tc\Utils\Concrete.hs:784:5 in ghc-9.15-inplace:GHC.Tc.Utils.Concrete
        unifyConcrete_kind, called at compiler\GHC\Tc\Utils\Concrete.hs:688:40 in ghc-9.15-inplace:GHC.Tc.Utils.Concrete
        hasFixedRuntimeRep, called at compiler\GHC\Tc\Utils\Unify.hs:179:32 in ghc-9.15-inplace:GHC.Tc.Utils.Unify

where again we have k_aBF := TYPE kappa but this is only apparent after zonking.

Several functions in the compiler expect that the input type is of the form TYPE rep or CONSTRAINT rep, but I'm not sure how we are supposed to be upholding that.

To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information