Compiler panic with unused existential type variable and -O2
Summary
The following file makes GHC panic:
-- B.hs
{-# LANGUAGE
DeriveDataTypeable,
StandaloneDeriving,
GADTs,
ScopedTypeVariables #-}
module B where
import Data.Data (Data(..))
data T where
C :: forall k. T
deriving instance Data T
Steps to reproduce
ghc -O B.hs
Output:
[1 of 1] Compiling B ( test/B.hs, test/B.o )
ghc: panic! (the 'impossible' happened)
(GHC version 8.10.4:
setBndrsDemandInfo
[k_a15F]
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler/utils/Outputable.hs:1179:37 in ghc:Outputable
pprPanic, called at compiler/stranal/DmdAnal.hs:964:28 in ghc:DmdAnal
Expected behavior
Should compile successfully.
Environment
- GHC version used: 8.10, 9.0.1
Edited by Xia Li-yao