Assertion failure with levity polymorphism
The following code, taken from T13233, triggers an assertion failure in HEAD.
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE MagicHash #-}
module Bug where
import GHC.Exts (TYPE, RuntimeRep, Weak#, State#, RealWorld, mkWeak# )
-- It used to be that primops has no binding. However, as described in
-- Note [Primop wrappers] in PrimOp we now rewrite unsaturated primop
-- applications to their wrapper, which allows safe use of levity polymorphism.
primop :: forall (rep :: RuntimeRep) (a :: TYPE rep) b c.
a -> b -> (State# RealWorld -> (# State# RealWorld, c #))
-> State# RealWorld -> (# State# RealWorld, Weak# b #)
primop = mkWeak#
WARNING: file compiler/coreSyn/CoreArity.hs, line 1122
4 forall (q :: RuntimeRep) (a :: TYPE q) b c.
a
-> b
-> (State# RealWorld -> (# State# RealWorld, c #))
-> State# RealWorld
-> (# State# RealWorld, Weak# b #)
mkWeak#
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler/utils/Outputable.hs:1248:29 in ghc:Outputable
warnPprTrace, called at compiler/coreSyn/CoreArity.hs:1122:11 in ghc:CoreArity
ghc-stage2: panic! (the 'impossible' happened)
(GHC version 8.11.0.20200210:
ASSERT failed!
primop
Id arity: 4
STG arity: 0
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler/utils/Outputable.hs:1187:37 in ghc:Outputable
pprPanic, called at compiler/utils/Outputable.hs:1257:5 in ghc:Outputable
assertPprPanic, called at compiler/GHC/CoreToStg.hs:314:66 in ghc:GHC.CoreToStg
This is not caught by the test itself, because it fails to compile due to other code present in this file. As a part of this ticket, let's split it into two (and remove mkWeak#
from T13233_elab).
Edited by Krzysztof Gogolewski