GHC Panic with O1/O2 when case matching existentials in arrow/proc syntax
Summary
GHC seems to panic when doing case matches on existentials under ArrowChoice/proc syntax with O1/O2. Note that the error does not reproduce with -O0!
Steps to reproduce
I tried to produce the minimal example. I wasn't able to trim it further. The problem does not seem to reproduce if I don't also pack the existential somehow, next to the SBool b
or B b
constraint.
{-# language Arrows #-}
{-# language DataKinds #-}
{-# language GADTs #-}
{-# language KindSignatures #-}
{-# language RankNTypes #-}
{-# language TypeApplications #-}
{-# OPTIONS_GHC -O1 #-}
module Panic where
import Control.Arrow
import Prelude
data SBool (b :: Bool) where
STrue :: SBool 'True
SFalse :: SBool 'False
data Exists i where
Exists :: SBool b -> i b -> Exists i
dispatchExistsArrow
:: forall arr i r
. ArrowChoice arr
=> (forall b. arr (i b) r)
-> arr (Exists i) r
dispatchExistsArrow arrow = proc exists -> do
case exists of
Exists tag inner -> case tag of
STrue -> arrow @'True -< inner
SFalse -> arrow @'False -< inner
It can also be reproduced if we pack a constraint equivalent to the packed SBool b
:
{-# language Arrows #-}
{-# language DataKinds #-}
{-# language GADTs #-}
{-# language KindSignatures #-}
{-# language RankNTypes #-}
{-# language TypeApplications #-}
{-# OPTIONS_GHC -O1 #-}
{-# language ScopedTypeVariables #-}
module Panic2 where
import Control.Arrow
import Prelude
data SBool (b :: Bool) where
STrue :: SBool 'True
SFalse :: SBool 'False
class B (b :: Bool) where
tag :: SBool b
instance B 'True where
tag = STrue
instance B 'False where
tag = SFalse
data Exists i where
Exists :: B b => i b -> Exists i
dispatchExistsArrow
:: forall arr i r
. ArrowChoice arr
=> (forall b. arr (i b) r)
-> arr (Exists i) r
dispatchExistsArrow arrow = proc exists -> do
case exists of
Exists (inner :: i b) -> case tag @b of
STrue -> arrow @'True -< inner
SFalse -> arrow @'False -< inner
The error in both cases is
ghc: panic! (the 'impossible' happened)
(GHC version 8.10.2:
mkSingleAltCase
ds_d15E
[b_aUW, $dB_aUX, ds_d15D]
Either (i_aUQ b_aUW, ()) (i_aUQ b_aUW, ())
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler/utils/Outputable.hs:1179:37 in ghc:Outputable
pprPanic, called at compiler/coreSyn/CoreUtils.hs:536:9 in ghc:CoreUtils
Please report this as a GHC bug: https://www.haskell.org/ghc/reportabug
Expected behavior
Compile for any optimization levels.
Environment
- GHC version used: 8.10.2
Optional:
- Operating System:
- System Architecture: