Segfault with UnliftedDatatypes + ghci + levity polymorphism
This bug is a variant of #19628 (closed).
To reproduce, load the following file into ghci:
{-# LANGUAGE UnliftedDatatypes #-}
import GHC.Exts
type Strict :: forall r. * -> TYPE ('BoxedRep r)
data Strict a where
Force :: a -> Strict @r a
x :: Int
x = 10
where
test :: Strict @Unlifted Int
test = Force undefined
and evaluate x
:
ghci> x
Segmentation fault (core dumped)
The code is the same as in #19628 (closed), except that I defined Force
to be levity-polymorphic (and instantiated to Unlifted
at the call site).
I believe the problem is in schemeT
:
if isUnliftedTypeKind (tyConResKind (dataConTyCon con))
then RETURN_UNLIFTED P
else ENTER)
This attempts to check for liftedness by looking at the type of the datacon,
but this is not enough: the kind is TYPE (BoxedRep r)
,
and isUnliftedTypeKind
conservatively returns False
.
The correct thing to do would be to check arguments, but in STG
the type arguments are erased. So I'm not sure how to proceed.
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information