[GHC] #13474: GHC HEAD regression: Prelude.!!: index too large
GHC
ghc-devs at haskell.org
Thu Mar 23 23:10:56 UTC 2017
#13474: GHC HEAD regression: Prelude.!!: index too large
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone: 8.2.1
Component: Compiler | Version: 8.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by simonpj):
Stunning. Here's an even small test case
{{{
module T13474 where
import qualified Data.Map as M
class Default a where
def :: a
foo :: Default a => b -> a
foo x = def
mapdef :: Default v => M.Map k v -> M.Map k v
mapdef = M.map foo
}}}
With a debug compiler I get
{{{
matchN
map/coerce
[TYPE: a_a1eq, TYPE: b_a1er, TYPE: k_a1ep,
(\ (v_a1et :: a_a1eq) -> v_a1et)
`cast` (<a_a1eq>_R -> $r$dCoercible_a1es
:: ((a_a1eq -> a_a1eq) :: *) ~R# ((a_a1eq -> b_a1er) :: *))]
[TYPE: v_aJ1, TYPE: v_aJ1, TYPE: k_aJ2,
(\ _ [Occ=Dead] -> $dDefault_aJ4)
`cast` (<v_aJ1>_R -> N:Default[0] <v_aJ1>_N
:: ((v_aJ1 -> Default v_aJ1) :: *) ~R# ((v_aJ1 -> v_aJ1) ::
*))]
ghc-stage1.exe: panic! (the 'impossible' happened)
(GHC version 8.3.20170316 for x86_64-unknown-mingw32):
ASSERT failed!
0
Constraint
Call stack:
CallStack (from HasCallStack):
prettyCurrentCallStack, called at
compiler\utils\Outputable.hs:1191:58 in ghc:Outputable
callStackDoc, called at compiler\utils\Outputable.hs:1246:22 in
ghc:Outputable
assertPprPanic, called at compiler\types\Coercion.hs:898:49 in
ghc:Coercion
mkNthCo, called at compiler\types\Coercion.hs:430:5 in
ghc:Coercion
mkRuntimeRepCo, called at compiler\types\Coercion.hs:343:36 in
ghc:Coercion
splitTyConAppCo_maybe, called at
compiler\specialise\Rules.hs:806:10 in ghc:Rules
Call stack:
CallStack (from HasCallStack):
prettyCurrentCallStack, called at
compiler\utils\Outputable.hs:1191:58 in ghc:Outputable
callStackDoc, called at compiler\utils\Outputable.hs:1195:37 in
ghc:Outputable
pprPanic, called at compiler\utils\Outputable.hs:1244:5 in
ghc:Outputable
assertPprPanic, called at compiler\types\Coercion.hs:898:49 in
ghc:Coercion
mkNthCo, called at compiler\types\Coercion.hs:430:5 in
ghc:Coercion
mkRuntimeRepCo, called at compiler\types\Coercion.hs:343:36 in
ghc:Coercion
splitTyConAppCo_maybe, called at
compiler\specialise\Rules.hs:806:10 in ghc:Rules
}}}
I'm still not sure what's actually wrong, but something is very wrong.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13474#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list