panic refineFromInScope from 3b823533
Summary
After 3b823533 landed, my TTG Dump.hs
for API annotations causes a panic on refineFromInscope
.
I minimised this to a reproduction from
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module GHC.Hs.Dump1 where
import qualified GHC.Utils.Ppr as Pretty
import GHC.Prelude (Maybe(..), maybe,Bool (True), ($), head)
import Data.Data (Data,Typeable, gmapQ, cast)
import Data.String
import GHC.Exts (oneShot)
runSDoc :: SDoc -> (Bool -> Pretty.Doc)
runSDoc (SDoc m) = m
{-# COMPLETE SDoc #-}
pattern SDoc :: (Bool -> Pretty.Doc) -> SDoc
pattern SDoc m <- SDoc' m
where
SDoc m = SDoc' (oneShot m)
newtype SDoc = SDoc' (Bool -> Pretty.Doc)
vcat :: [SDoc] -> SDoc
vcat ds = head ds
docToSDoc :: Pretty.Doc -> SDoc
docToSDoc d = SDoc (\_ -> d)
text :: String -> SDoc
text s = docToSDoc $ Pretty.text s
data SrcSpanAnn' a = SrcSpanAnn a
deriving (Data)
data ApiAnn' ann
= ApiAnn ann
deriving (Data)
showAstData :: Data a => Bool -> a -> SDoc
showAstData ba a0 = showAstData' a0
where
showAstData' :: Data a => a -> SDoc
showAstData' =
generic `extQ` srcSpanAnnA
where generic :: Data a => a -> SDoc
generic t = vcat (gmapQ showAstData' t)
srcSpanAnnA :: SrcSpanAnn' (ApiAnn' ()) -> SDoc
srcSpanAnnA = locatedAnn''
locatedAnn'' :: forall a. (Typeable a, Data a)
=> SrcSpanAnn' a -> SDoc
locatedAnn'' ss =
case cast ss of
Just ((SrcSpanAnn ann ) :: SrcSpanAnn' a) ->
case ba of
True
-> showAstData' ann
Nothing -> text "locatedAnn:unmatched"
-- | Extend a generic query by a type-specific case
extQ :: ( Typeable a
, Typeable b
)
=> (a -> q)
-> (b -> q)
-> a
-> q
extQ f g a = maybe (f a) g (cast a)
which gives
compiler/GHC/Hs/Dump1.hs:62:19: warning: [-Wincomplete-patterns]
Pattern match(es) are non-exhaustive
In a case alternative:
Patterns of type ‘Bool’ not matched: ghc-prim:GHC.Types.False
|
62 | case ba of
| ^^^^^^^^^^...
ghc: panic! (the 'impossible' happened)
(GHC version 9.1.20210130:
refineFromInScope
InScope {wild_00 eta_B0 ba_a1w2 a0_a1w3 $tApiAnn'_a1ya
$cApiAnn_a1yb $tSrcSpanAnn'_a1yc $cSrcSpanAnn_a1yd a_a32a
$dData_a32b $cgfoldl_a3aO $cdataCast1_a3bC $cgmapQl_a3cD
$cgmapQr_a3cW $cgmapQ_a3de $cgmapQi_a3dr $cgmapM_a3dG $cgmapMp_a3e0
$cgmapMo_a3ek $cgfoldl_a3eG $cdataCast1_a3fm $cgmapQl_a3fY
$cgmapQr_a3ga $cgmapQ_a3gm $cgmapQi_a3gw $cgmapM_a3gG $cgmapMp_a3gS
$cgmapMo_a3h4 $krep_a3kK $krep_a3kL $krep_a3kM $krep_a3kN
$krep_a3kO $krep_a3kP $krep_a3kQ $krep_a3kR $krep_a3kS $krep_a3kT
runSDoc vcat docToSDoc text showAstData extQ $tc'SDoc' $tcSDoc
$tc'SrcSpanAnn $tcSrcSpanAnn' $tc'ApiAnn $tcApiAnn' $fDataApiAnn'
$fDataSrcSpanAnn' $mSDoc $bSDoc $trModule $bSDoc_s3NK
docToSDoc_s3NL text_s3NP runSDoc_s3NQ $cApiAnn_s3Ol $cApiAnn_s3Om
$cApiAnn_s3On $tApiAnn'_s3Oo $tApiAnn'_s3Op $tApiAnn'_s3Oq
$cSrcSpanAnn_s3Or $cSrcSpanAnn_s3Os $cSrcSpanAnn_s3Ot
$tSrcSpanAnn'_s3Ou $tSrcSpanAnn'_s3Ov $tSrcSpanAnn'_s3Ow
$trModule_s3Ox $trModule_s3Oy $trModule_s3Oz $trModule_s3OA
$krep_s3OB $tcSDoc_s3OC $tcSDoc_s3OD $tc'SDoc'_s3OE $tc'SDoc'_s3OF
$tcSrcSpanAnn'_s3OG $tcSrcSpanAnn'_s3OH $krep_s3OI
$tc'SrcSpanAnn_s3OJ $tc'SrcSpanAnn_s3OK $cp1Data_s3Pk
$tcApiAnn'_s3R4 $tcApiAnn'_s3R5 $krep_s3R6 $tc'ApiAnn_s3R7
$tc'ApiAnn_s3R8 $cp1Data_s3R9 $cgmapT_s3RT $cgmapT_s3RU
showAstData'_s3RW $dTypeable_s3S2 $dTypeable_s3S3 $dTypeable_s3S6
$dData_s3S7 $dTypeable_s3Sd $dTypeable_s3Se $dTypeable_s3Sh
$s$fDataApiAnn'_s3Sl $s$cgmapMo_s3Ss $s$cgmapT_s3Su $s$cgmapQl_s3Sw
$s$cgmapQ_s3Sy $s$cgmapQr_s3SA $s$cgmapQi_s3SC $s$cgmapM_s3SE
$s$cgmapMp_s3SK $s$cdataCast1_s3SQ $s$cp1Data_s3SS $s$cgfoldl_s3T0
$scast_s3T6 $scast_s3T9 lvl_s3Tg lvl_s3Th lvl_s3Ti lvl_s3Tj
lvl_s3Tk lvl_s3Tl lvl_s3Tm lvl_s3Tn lvl_s3To lvl_s3Tp lvl_s3Tq
lvl_s3Tr lvl_s3Tv lvl_s3Tw lvl_s3Tx lvl_s3Ty lvl_s3Tz lvl_s3TC
lvl_s3TD lvl_s3TG lvl_s3U0 lvl_s3U1 lvl_s3Ul lvl_s3Um lvl_s3Uo
lvl_s3Uq lvl_s3Ur lvl_s3Uu lvl_s3Uv $dTypeable_s3Uz $dTypeable_s3UC
lvl_s3UE lvl_s3UG lvl_s3UH lvl_s3UJ lvl_s3UK lvl_s3UL lvl_s3UM
lvl_s3UN lvl_s3UT $dTypeable_s3UV lvl_s3UX lvl_s3UY lvl_s3V1
lvl_s3V3 lvl_s3Vn lvl_s3Vo lvl_s3Vp lvl_s3Vs lvl_s3Vt lvl_s3Vu
lvl_s3Vx lvl_s3Vz lvl_s3VC lvl_s3VE $dTypeable_s3VF
$sshowAstData'_s3VJ showAstData'_s3VM showAstData_s3VN}
$sshowAstData'_s3Si
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler/GHC/Utils/Panic.hs:181:37 in ghc:GHC.Utils.Panic
pprPanic, called at compiler/GHC/Core/Opt/Simplify/Env.hs:685:30 in ghc:GHC.Core.Opt.Simplify.Env
Please report this as a GHC bug: https://www.haskell.org/ghc/reportabug
Steps to reproduce
Build GHC from commit 3b823533
Invoke the stage0 compiler on the Dump1.hs file shown above. My command line (from invoking hadrian with -V, will not be portable) is
_build/stage0/bin/ghc -Wall -fdiagnostics-color=never -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -hide-all-packages -no-user-package-db '-package-env -' '-package-db _build/stage1/lib/package.conf.d' '-this-unit-id ghc-9.1' '-package-id array-0.5.4.0' '-package-id base-4.16.0.0' '-package-id binary-0.8.7.0' '-package-id bytestring-0.10.12.0' '-package-id containers-0.6.4.1' '-package-id deepseq-1.4.4.0' '-package-id directory-1.3.6.1' '-package-id exceptions-0.10.4' '-package-id filepath-1.4.2.1' '-package-id ghc-boot-9.1' '-package-id ghc-heap-9.1' '-package-id ghci-9.1' '-package-id hpc-0.6.1.0' '-package-id parsec-3.1.14.0' '-package-id process-1.6.10.0' '-package-id template-haskell-2.17.0.0' '-package-id terminfo-0.4.1.4' '-package-id time-1.11.1.1' '-package-id transformers-0.5.6.2' '-package-id unix-2.7.2.2' -i -i/home/alanz/mysrc/git.haskell.org/worktree/exactprint/_build/stage1/compiler/build -i/home/alanz/mysrc/git.haskell.org/worktree/exactprint/_build/stage1/compiler/build/autogen -i/home/alanz/mysrc/git.haskell.org/worktree/exactprint/compiler -Iincludes -I_build/stage1/lib -I_build/stage1/compiler/build -I_build/stage1/compiler/build/. -I_build/stage1/compiler/build/../rts/dist/build -Icompiler/. -Icompiler/../rts/dist/build -I/home/alanz/mysrc/git.haskell.org/worktree/exactprint/_build/stage1/lib/x86_64-linux-ghc-9.1.20210212/process-1.6.10.0/include -I/home/alanz/mysrc/git.haskell.org/worktree/exactprint/_build/stage1/lib/x86_64-linux-ghc-9.1.20210212/unix-2.7.2.2/include -I/home/alanz/mysrc/git.haskell.org/worktree/exactprint/_build/stage1/lib/x86_64-linux-ghc-9.1.20210212/time-1.11.1/include -I/home/alanz/mysrc/git.haskell.org/worktree/exactprint/_build/stage1/lib/x86_64-linux-ghc-9.1.20210212/bytestring-0.10.12.0/include -I/home/alanz/mysrc/git.haskell.org/worktree/exactprint/_build/stage1/lib/x86_64-linux-ghc-9.1.20210212/base-4.16.0.0/include -I/home/alanz/mysrc/git.haskell.org/worktree/exactprint/_build/stage1/lib/x86_64-linux-ghc-9.1.20210212/ghc-bignum-1.0/include -I/home/alanz/mysrc/git.haskell.org/worktree/exactprint/_build/stage1/lib/x86_64-linux-ghc-9.1.20210212/rts-1.0/include -I_build/stage1/lib -optc-I_build/stage1/lib -optP-include -optP_build/stage1/compiler/build/autogen/cabal_macros.h -optP-DHAVE_INTERNAL_INTERPRETER -optP-DCAN_LOAD_DLL -outputdir _build/stage1/compiler/build -Wnoncanonical-monad-instances -optc-Wno-error=inline -optP-Wno-nonportable-include-path -c compiler/GHC/Hs/Dump1.hs -o _build/stage1/compiler/build/GHC/Hs/Dump.p_o -O2 -H32m -Wall -Wno-name-shadowing -Wnoncanonical-monad-instances -Wnoncanonical-monoid-instances -this-unit-id ghc -XHaskell2010 -XNoImplicitPrelude -XBangPatterns -XScopedTypeVariables -XMonoLocalBinds -no-global-package-db -package-db=/home/alanz/mysrc/git.haskell.org/worktree/exactprint/_build/stage1/lib/package.conf.d -ghcversion-file=/home/alanz/mysrc/git.haskell.org/worktree/exactprint/_build/stage1/lib/ghcversion.h -Wno-deprecated-flags -Wcpp-undef
Expected behavior
It should compile without a panic
Environment
- GHC version used: 3b823533
Optional:
- Operating System: Debian testing
- System Architecture: amd64
FYI, my bisect log is
$ git bisect log
git bisect start
# bad: [ab5fd982a7a501136cb8b90fa841c02cc9551b5a] Bump Haddock submodule
git bisect bad ab5fd982a7a501136cb8b90fa841c02cc9551b5a
# good: [81f0665513d65c2d7e544cbe8adeff4b0d6fdfff] Separate AST from GhcPass (#18936)
git bisect good 81f0665513d65c2d7e544cbe8adeff4b0d6fdfff
# good: [ae8379abb8aa1defc86dc60bece70546d42af177] Ppr: compute length of string literals at compile time (#19266)
git bisect good ae8379abb8aa1defc86dc60bece70546d42af177
# bad: [6085cfb5e508e969ecb69d8dbeb8cfd1fb87ca3d] Remove misleading 'lazy' pattern matches from 'head' and 'tail' in Data.List.NonEmpty
git bisect bad 6085cfb5e508e969ecb69d8dbeb8cfd1fb87ca3d
# bad: [a3d995fa18079ac31623febc8f41297c9acfb6a5] Fix -dynamic-too with wired-in modules (#19264)
git bisect bad a3d995fa18079ac31623febc8f41297c9acfb6a5
# bad: [f5d62eb2d5a1058f355aaa1fd0a959694d160ec4] ghci: Take editor from VISUAL environment variable
git bisect bad f5d62eb2d5a1058f355aaa1fd0a959694d160ec4
# bad: [3b8235334b7838013c9e955db3e7762a1c7fef43] Make PatSyn immutable
git bisect bad 3b8235334b7838013c9e955db3e7762a1c7fef43
# good: [5140841ca1acaeaeef893233ae3d08ce4573b01b] Fix check-uniques script
git bisect good 5140841ca1acaeaeef893233ae3d08ce4573b01b
# first bad commit: [3b8235334b7838013c9e955db3e7762a1c7fef43] Make PatSyn immutable