Type error, but all type error messages are suppressed: GHC 9.6.6, 9.8.2, 9.10.1
Summary
I was implementing some Data types a la carte stuff and encountered a ghc panic.
The steps to reproduce contain a minimal verison (that I found) reproducing the issue.
9.6.6
, 9.8.2
, 9.10.1
all panicked.
Steps to reproduce
Compile the following program with ghc
using any of the three aforementioned versions.
If I remove the unused parameter f
from Buggy
at the declaration and in the Ghcbug
typeclass then the code compiles without issues.
module Bug where
import Control.Monad.State
data (f :+: g) a = Inl (f a) | Inr (g a)
deriving Functor
newtype Buggy f m = Buggy { thing :: m Int }
class GhcBug f where
demo :: MonadState (Buggy f m) m => f (m Int) -> m Int
instance (GhcBug f, GhcBug g) => GhcBug (f :+: g) where
demo (Inl l) = demo l
demo (Inr r) = demo r
Error messages
<no location info>: error:
panic! (the 'impossible' happened)
GHC version 9.6.6:
lookupIdSubst
$dMonadState_aLh
InScope {f_aKX g_aKY $dGhcBug_aKZ $dGhcBug_aL0 m_aL5
$dMonadState_aL6}
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/Subst.hs:197:17 in ghc:GHC.Core.Subst
CallStack (from HasCallStack):
panic, called at compiler/GHC/Utils/Error.hs:454:29 in ghc:GHC.Utils.Error
Please report this as a GHC bug: https://www.haskell.org/ghc/reportabug
<no location info>: error:
panic! (the 'impossible' happened)
GHC version 9.8.2:
lookupIdSubst
$dMonadState_aFd
InScope {f_aER g_aES $dGhcBug_aET $dGhcBug_aEU m_aEZ
$dMonadState_aF0}
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler/GHC/Utils/Panic.hs:191:37 in ghc-9.8.2-inplace:GHC.Utils.Panic
pprPanic, called at compiler/GHC/Core/Subst.hs:197:17 in ghc-9.8.2-inplace:GHC.Core.Subst
CallStack (from HasCallStack):
panic, called at compiler/GHC/Utils/Error.hs:503:29 in ghc-9.8.2-inplace:GHC.Utils.Error
Please report this as a GHC bug: https://www.haskell.org/ghc/reportabug
<no location info>: error:
panic! (the 'impossible' happened)
GHC version 9.10.1:
lookupIdSubst
$dMonadState_aFt
InScope {f_aF6 g_aF7 $dGhcBug_aF8 $dGhcBug_aF9 m_aFf
$dMonadState_aFg}
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler/GHC/Utils/Panic.hs:190:37 in ghc-9.10.1-inplace:GHC.Utils.Panic
pprPanic, called at compiler/GHC/Core/Subst.hs:196:17 in ghc-9.10.1-inplace:GHC.Core.Subst
CallStack (from HasCallStack):
panic, called at compiler/GHC/Utils/Error.hs:507:29 in ghc-9.10.1-inplace:GHC.Utils.Error
Please report this as a GHC bug: https://www.haskell.org/ghc/reportabug
Expected behavior
Ghc should not panic.
Environment
- Architecture: x86_64
- Operating System: NixOS 24.11.20240926.1925c60
- GHC version: 9.6.6, 9.8.2, 9.10.1
Related issue
Issue #25064 seems to be related.