[GHC] #12926: ghc master (8.1.20161202) panics with assertion failure with devel2 flavor and -O2
GHC
ghc-devs at haskell.org
Mon Dec 5 06:42:48 UTC 2016
#12926: ghc master (8.1.20161202) panics with assertion failure with devel2 flavor
and -O2
-------------------------------------+-------------------------------------
Reporter: pacak | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Compile-time
Unknown/Multiple | crash or panic
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Following code if compiled with -O2 (but not -O1) causes assertion
failure. Depends only on vector.
{{{#!hs
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module A where
import GHC.Base
import qualified Data.Vector.Unboxed.Base
import qualified Data.Vector.Generic.Base
import Data.Vector.Generic.Mutable
import qualified Data.Vector.Generic.Mutable.Base
import Data.Vector.Generic (fromList)
data A = A Int Int Int
instance Data.Vector.Unboxed.Base.Unbox A
newtype instance Data.Vector.Unboxed.Base.MVector s_a4iX A
= MV_A (Data.Vector.Unboxed.Base.MVector s_a4iX (Int, Int, Int))
instance MVector Data.Vector.Unboxed.Base.MVector A where
basicLength (MV_A v) = basicLength v
basicUnsafeSlice idx len (MV_A v) = MV_A (basicUnsafeSlice idx len v)
basicUnsafeNew len = (MV_A `liftM` (basicUnsafeNew len))
basicUnsafeWrite (MV_A v) idx val_a4iW = basicUnsafeWrite v idx ( (\ (A
a_a4iT b_a4iU c_a4iV) -> (a_a4iT, b_a4iU, c_a4iV)) val_a4iW)
newtype instance Data.Vector.Unboxed.Base.Vector A = V_A
(Data.Vector.Unboxed.Base.Vector (Int, Int, Int))
instance Data.Vector.Generic.Base.Vector Data.Vector.Unboxed.Base.Vector A
where
mkA :: Data.Vector.Unboxed.Base.Vector A
mkA = fromList []
}}}
{{{
ghc: panic! (the 'impossible' happened)
[7/1644]
(GHC version 8.1.20161202 for x86_64-unknown-linux):
ASSERT failed!
in_scope InScope {wild_00 eta_X1T $cbasicUnsafeFreeze_a6sr
$cbasicUnsafeThaw_a6st $cbasicLength_a6sv
$cbasicUnsafeSlice_a6sx
$cbasicUnsafeIndexM_a6sz $cbasicUnsafeCopy_a6sF
$celemseq_a6t3
$cbasicLength_a6tm $cbasicUnsafeSlice_a6ty
$cbasicOverlaps_a6tL
$cbasicUnsafeNew_a6tN $cbasicInitialize_a6uj
$cbasicUnsafeReplicate_a6up $cbasicUnsafeRead_a6uJ
$cbasicUnsafeWrite_a6uL $cbasicClear_a6vg
$cbasicSet_a6vE
$cbasicUnsafeCopy_a6w2 $cbasicUnsafeMove_a6wr
$cbasicUnsafeGrow_a6wQ wild_a7QO dt_a7QQ ds1_a7QR
ds2_a7QS ds3_a7QT
wild_a80U x_a819 xs1_a81a ds4_a84V z_a84W s7_a84X
ds5_a851
wild5_a85V v3_a85X i_a85Y wild7_a866 x_a868 y_a86k
wild9_a86m $tcA
$trModule $tc'A $fVectorVectorA $fUnboxA
$fMVectorMVectorA mkA
$cbasicUnsafeSlice_s7QF $trModule_s7Su $trModule_s7Sv
$tc'A_s7Sw
$s$dmbasicUnsafeGrow_s7Vp $s$dmbasicUnsafeMove_s7Vw
$s$dmbasicUnsafeReplicate_s7VB $s$dmbasicSet_s7VG
$s$dmbasicUnsafeCopy_s7VN $s$dmbasicUnsafeCopy_s7VW
$sunstream_s886
$s$fMVectorMVector(,,)_$cbasicUnsafeNew_s896
$s$fMVectorMVector(,,)_$cbasicUnsafeWrite_s89h
$s$fMVectorMVector(,,)_$cbasicUnsafeSlice_s89k
$s$fMVectorMVector(,,)_$cbasicLength_s89l
$sfromList_s89m
$snew_s89n $s$dmelemseq_s89o $s$dmbasicClear_s89p
lvl_s89Y $j_sa8p
lvl_sbhM lvl_sbhN lvl_sbhO lvl_sbhP lvl_sbhQ lvl_sbhR
lvl_sbhT
lvl_sbhU lvl_sbhV lvl_sbhW lvl_sbi1 lvl_sbi2 lvl_sbi4
lvl_sbi5
lvl_sbi6 lvl_sbi7 foldlM_loop_sbns foldlM_loop_sbnL
lvl_sbo2
$sfoldlM_loop_sbHS $s$j_sbI5 $sfoldlM_loop_sbIa
$sfoldlM_loop_sbIx}
tenv []
tenvFVs []
cenv [sbHY :-> sg_sbHY]
cenvFVs [sbHY :-> sg_sbHY]
tys [PrimState (ST RealWorld)]
cos []
Call stack:
CallStack (from HasCallStack):
prettyCurrentCallStack, called at
compiler/utils/Outputable.hs:1114:58 in ghc:Outputable
callStackDoc, called at compiler/utils/Outputable.hs:1163:22 in
ghc:Outputable
assertPprPanic, called at compiler/types/TyCoRep.hs:2023:56 in
ghc:TyCoRep
checkValidSubst, called at compiler/types/TyCoRep.hs:2056:17 in
ghc:TyCoRep
substTy, called at compiler/types/Coercion.hs:1457:33 in
ghc:Coercion
Call stack:
CallStack (from HasCallStack):
prettyCurrentCallStack, called at
compiler/utils/Outputable.hs:1114:58 in ghc:Outputable
callStackDoc, called at compiler/utils/Outputable.hs:1118:37 in
ghc:Outputable
pprPanic, called at compiler/utils/Outputable.hs:1161:5 in
ghc:Outputable
assertPprPanic, called at compiler/types/TyCoRep.hs:2023:56 in
ghc:TyCoRep
checkValidSubst, called at compiler/types/TyCoRep.hs:2056:17 in
ghc:TyCoRep
substTy, called at compiler/types/Coercion.hs:1457:33 in
ghc:Coercion
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12926>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list