Backpack Regression for Representation-Polymorphic Binders
Summary
If you use let x = Z
, where the type of Z
is TYPE R
, where R
is an abstract top-level runtime rep from a signature, you get a compiler panic. But if you write case Z of {x -> ...}
, the panic goes away.
This did not happen in GHC 8.10 or in GHC 9.2 (I have not tested GHC 9.0), but it happens in GHC 9.4 and every release since then.
Steps to reproduce
Here is a minimal reproducer:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PolyKinds #-}
unit example where
signature Order where
import GHC.Exts
data R :: RuntimeRep
data E :: TYPE R
pickMinimum :: E -> E -> E
pickMaximum :: E -> E -> E
module OrderedPair where
import Order (E,pickMinimum,pickMaximum)
makeOrderedPair :: E -> E -> (# E, E #)
makeOrderedPair a b =
let greater = pickMaximum a b
lesser = pickMinimum a b
in (# greater, lesser #)
Building this with ghc --backpack buggy.bkp
results in:
<no location info>: error:
panic! (the 'impossible' happened)
GHC version 9.6.4:
isUnliftedType
E :: TYPE R
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler/GHC/Utils/Panic.hs:189:37 in ghc:GHC.Utils.Panic
pprPanic, called at compiler/GHC/Core/Type.hs:2257:7 in ghc:GHC.Core.Type
CallStack (from HasCallStack):
panic, called at compiler/GHC/Utils/Error.hs:454:29 in ghc:GHC.Utils.Error
Notice that we do not have to instantiate the indefinite unit to trigger the bug. Merely defining it is enough. The problematic lines (not indicated by the error message) are the binding sites of greater
and lesser
. If we bind using case
instead of let
, GHC is able to compile the program. My observation in larger projects that instantiate functions like this is that everything else downstream works once we trick GHC into correctly compiling the function. Here is the workaround using case
instead of let
:
makeOrderedPair :: E -> E -> (# E, E #)
makeOrderedPair a b = case pickMaximum a b of
greater -> case pickMinimum a b of
lesser -> (# greater, lesser #)
Context Around Why This Might Be Happening
I'm not sure why this is happening, and I am not able to dig into it. Here's what I've considered. In GHC, isUnliftedType
is defined like this:
isUnliftedType :: HasDebugCallStack => Type -> Bool
isUnliftedType ty =
case typeLevity_maybe ty of
Just Lifted -> False
Just Unlifted -> True
Nothing -> pprPanic "isUnliftedType" (ppr ty <+> dcolon <+> ppr (typeKind ty))
So representation-polymorphic types lead to panics. In an indefinite module, we still want to panic when we encounter a binding whose type's runtime representation includes a locally bound Rep
. But we do not want to panic when the representation is a top-level abstract representation. I've not been able to investigate this further.
Environment
- GHC versions that trigger the panic: 9.4, 9.6, 9.8
- GHC versions that do not trigger the panic: 8.10, 9.2