[GHC] #13658: Assertion failure on HEAD: "optCoercion changed types!"
GHC
ghc-devs at haskell.org
Sun May 7 17:25:20 UTC 2017
#13658: Assertion failure on HEAD: "optCoercion changed types!"
-------------------------------------+-------------------------------------
Reporter: bgamari | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone: 8.2.1
Component: Compiler | Version: 8.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by slyfox):
This should be self-contained example. You'll need a debugging compiler to
build it.
I'm not sure I've preserved kind structure of original module as core-lint
detects
all sorts of problems in this program.
But the error is still the same. I was not able to remove foldl/foldr: the
error goes away.
{{{#!hs
-- Bug.hs:
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RankNTypes #-}
{- # OPTIONS_GHC -Werror #-}
{-# OPTIONS_GHC -g -O2 #-}
module Bug (bug) where
import Unsafe.Coerce (unsafeCoerce)
undefined :: a
undefined = undefined
prelude_id :: a -> a
prelude_id x = x
prelude_foldl :: forall a b. (b -> a -> b) -> b -> [a] -> b
prelude_foldl k z0 xs =
prelude_foldr (\v fn -> (\z -> fn (k z v))) prelude_id xs z0
prelude_foldr :: (a -> b -> b) -> b -> [a] -> b
prelude_foldr f z = go
where
go [] = z
go (y:ys) = y `f` go ys
data TypeRep (a :: k) where
TrTyCon :: TypeRep (a :: k)
TrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1). TypeRep (a b)
data SomeTypeRep where
SomeTypeRep :: forall k (a :: k). TypeRep a -> SomeTypeRep
mkTrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1).
TypeRep (a :: k1 -> k2)
-> TypeRep (a b)
mkTrApp TrTyCon = undefined
mkTrApp TrApp = undefined
bug :: [a] -> SomeTypeRep
bug args = prelude_foldl applyTy tycon_app args
where tycon_app = SomeTypeRep TrTyCon
applyTy :: SomeTypeRep -> a -> SomeTypeRep
applyTy (SomeTypeRep acc) _unused
= SomeTypeRep (mkTrApp (unsafeCoerce acc))
}}}
{{{
$ ../"inplace/bin/ghc-stage1" -hisuf hi -osuf o -hcsuf hc -static -H32m
-O -g -dcore-lint -DDEBUG -Wall -this-unit-id base-4.10.0.0 -hide-
all-packages -i.. -i../libraries/base/. -i../libraries/base/dist-
install/build -I../libraries/base/dist-install/build -i../libraries/base
/dist-install/build/./autogen -I../libraries/base/dist-
install/build/./autogen -Ilibraries/base/include -optP-
DOPTIMISE_INTEGER_GCD_LCM -optP-include -optP../libraries/base/dist-
install/build/./autogen/cabal_macros.h -package-id rts -package-id ghc-
prim-0.5.0.0 -package-id integer-gmp-1.0.0.1 -this-unit-id base
-XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy-safe
-Wno-deprecated-flags -Wnoncanonical-monad-instances -odir
libraries/base/dist-install/build -hidir libraries/base/dist-install/build
-stubdir libraries/base/dist-install/build -split-sections -dynamic-too
-c Bug.hs -fforce-recomp
ghc-stage1: panic! (the 'impossible' happened)
(GHC version 8.3.20170506 for x86_64-unknown-linux):
ASSERT failed!
optCoercion changed types!
in_co:
(TypeRep
(UnsafeCo nominal Any (Any -> Any))
(UnsafeCo nominal (Any Any) Any))_R
in_ty1: TypeRep (Any Any)
in_ty2: TypeRep Any
out_co: (TypeRep (UnsafeCo nominal Any (Any -> Any)) <Any>_N)_R
out_ty1: TypeRep Any
out_ty2: TypeRep Any
subst:
[TCvSubst
In scope: InScope {wild_00 wild_Xu y_a1t ys_a1u a_ayL $krep_aAd
$krep_aAe $krep_aAf $krep_aAg $krep_aAh
$krep_aAi $krep_aAj
$krep_aAk $krep_aAl $krep_aAm undefined
$tcTypeRep $tcSomeTypeRep
$tc'TrTyCon $tc'TrApp $trModule $tc'SomeTypeRep
bug $trModule_sB4
$trModule_sB5 $trModule_sB6 $trModule_sB7
$tcTypeRep_sB8
$tcTypeRep_sB9 $krep_sBa $krep_sBb
$tc'TrTyCon_sBc $tc'TrTyCon_sBd
$krep_sBe $krep_sBf $tc'TrApp_sBg $tc'TrApp_sBh
$tcSomeTypeRep_sBi
$tcSomeTypeRep_sBj $tc'SomeTypeRep_sBk
$tc'SomeTypeRep_sBl
poly_go_sBz lvl_sBA $spoly_go_sCu sc_sCv sc_sCw
$spoly_go_sCx}
Type env: []
Co env: []]
Call stack:
CallStack (from HasCallStack):
prettyCurrentCallStack, called at
compiler/utils/Outputable.hs:1134:58 in ghc:Outputable
callStackDoc, called at compiler/utils/Outputable.hs:1189:22 in
ghc:Outputable
assertPprPanic, called at compiler/types/OptCoercion.hs:96:188 in
ghc:OptCoercion
Call stack:
CallStack (from HasCallStack):
prettyCurrentCallStack, called at
compiler/utils/Outputable.hs:1134:58 in ghc:Outputable
callStackDoc, called at compiler/utils/Outputable.hs:1138:37 in
ghc:Outputable
pprPanic, called at compiler/utils/Outputable.hs:1187:5 in
ghc:Outputable
assertPprPanic, called at compiler/types/OptCoercion.hs:96:188 in
ghc:OptCoercion
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13658#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list