[GHC] #11644: Core lint error in result of Specialise for TEST=T3220 WAY=profasm
GHC
ghc-devs at haskell.org
Thu Feb 25 18:01:47 UTC 2016
#11644: Core lint error in result of Specialise for TEST=T3220 WAY=profasm
-------------------------------------+-------------------------------------
Reporter: thomie | Owner:
Type: bug | Status: new
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 8.0.1-rc2
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: indexed- | Blocked By:
types/should_compile/T3220 |
Blocking: | Related Tickets: #11371, #11643
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
This is the code:
{{{
{-# LANGUAGE TypeFamilies, ScopedTypeVariables#-}
module T3220 where
class Foo m where
type Bar m :: *
action :: m -> Bar m -> m
right x m = action m (Right x)
right' :: (Either a b ~ Bar m, Foo m) => b -> m -> m
right' x m = action m (Right x)
instance Foo Int where
type Bar Int = Either Int Int
action m a = either (*) (+) a m
instance Foo Float where
type Bar Float = Either Float Float
action m a = either (*) (+) a m
foo = print $ right (1::Int) (3 :: Int)
bar = print $ right (1::Float) (3 :: Float)
}}}
Invocation:
{{{
$ ghc-8.0.1 T3220.hs -prof -O -dcore-lint
}}}
{{{
[1 of 1] Compiling T3220 ( T3220.hs, T3220.o )
*** Core Lint errors : in result of Specialise ***
<no location info>: warning:
In the expression: action
@ Float
$fFooFloat
m_ayb
((Right @ Float @ Float x_aya)
`cast` (Sub (Sym cobox_aUe) :: Either a_aU3
b_aU4 ~R# Bar m_aU1))
cobox_aUe :: Bar m_aU1 ~# Either a_aU3 b_aU4
[LclId[CoVarId], Str=DmdType] is out of scope
}}}
Interestingly, with HEAD (2aee41960aa00fe09a2cd1983e02c15e06013037), it
hits an assert from #11371.
{{{
=====> T3220(profasm) 12 of 21 [0, 11, 0]
cd ./indexed-types/should_compile && "/home/thomas/ghc-
validate/inplace/test spaces/ghc-stage2" -c T3220.hs -fforce-recomp
-dcore-lint -dcmm-lint -dno-debug-output -no-user-package-db -rtsopts
-fno-warn-tabs -fno-warn-missed-specialisations -fno-ghci-history -O
-prof -static -auto-all > T3220.comp.stderr 2>&1
Compile failed (status 256) errors were:
ghc-stage2: panic! (the 'impossible' happened)
(GHC version 8.1.20160221 for x86_64-unknown-linux):
ASSERT failed!
CallStack (from HasCallStack):
assertPprPanic, called at compiler/types/TyCoRep.hs:1942:51 in
ghc:TyCoRep
checkValidSubst, called at compiler/types/TyCoRep.hs:2076:17 in
ghc:TyCoRep
substCo, called at compiler/coreSyn/CoreSubst.hs:605:20 in ghc:CoreSubst
in_scope InScope {x_axS m_axT $caction_a1dp $caction_a1dR right
right' foo bar $tcFoo $tc'C:Foo $fFooFloat $fFooInt
$trModule
a_s1fZ a_s1g0 a_s1g1 a_s1g2}
tenv [aTT :-> Float, aTV :-> Float, aTW :-> Float]
cenv []
tys []
cos [Sub (Sym cobox_aU6)]
needInScope [aU6 :-> cobox_aU6]
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
This is a regression from 7.10.3. Setting priority=highest.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11644>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list