typeOrConstraint panic with out of scope function, default method and representation-polymorphism
module T23883 where
import Data.Kind
import GHC.Exts
type SetField :: forall {a_rep}. Type -> TYPE a_rep -> Constraint
class SetField r a where
setField :: a -> r -> r
setField x = nonsense (\ _ -> x)
<no location info>: error:
panic! (the 'impossible' happened)
GHC version 9.9.20230817:
typeOrConstraint
(a_a1rM[ssk:1] |> {co_a1se}) :: cx_a1sd[conc:1]
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler\GHC\Utils\Panic.hs:191:37 in ghc-9.9-inplace:GHC.Utils.Panic
pprPanic, called at compiler\GHC\Core\Type.hs:2708:14 in ghc-9.9-inplace:GHC.Core.Type
typeTypeOrConstraint, called at compiler\GHC\Core\TyCo\Rep.hs:778:18 in ghc-9.9-inplace:GHC.Core.TyCo.Rep
mkScaledFunTys, called at compiler\GHC\Tc\Utils\Unify.hs:473:32 in ghc-9.9-inplace:GHC.Tc.Utils.Unify
CallStack (from HasCallStack):
panic, called at compiler\GHC\Utils\Error.hs:512:29 in ghc-9.9-inplace:GHC.Utils.Error
I get this error starting from GHC 9.6 (including 9.8 and HEAD).
On GHC 9.4 I instead get the following panic:
panic! (the 'impossible' happened)
GHC version 9.4.5:
getRuntimeRep
(a_aBi[ssk:1] |> Sym {co_aCl}) :: c_aC1[conc:1]
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler\GHC\Utils\Panic.hs:182:37 in ghc:GHC.Utils.Panic
pprPanic, called at compiler\GHC\Core\Type.hs:2534:18 in ghc:GHC.Core.Type
On GHC 9.2 I correctly get the out of scope error:
Variable not in scope: nonsense :: (p0 -> a) -> r -> r