#5884: GHC panics while trying to derive a Generic instance for Complex a
---------------------------------+------------------------------------------
Reporter: mux | Owner: dreixel
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.4.1
Keywords: | Os: Unknown/Multiple
Architecture: Unknown/Multiple | Failure: Compile-time crash
Difficulty: Unknown | Testcase:
Blockedby: | Blocking:
Related: |
---------------------------------+------------------------------------------
Comment(by guest):
A variable given to isTouchableMetaTyVar_InRange is a TyVar instead of the
expected TcTyVar. For example, for this test program (Main.hs):
{{{
{-# LANGUAGE StandaloneDeriving, DeriveGeneric #-}
import GHC.Generics
{- case (a)
import Data.Complex
-}
{- case (b)
infix 6 :+
data Complex a = a :+ a
-}
deriving instance Generic (Complex theVARIABLE)
main = putStrLn "test"
}}}
Uncommenting (a) to use Data.Complex a:
{{{
$ inplace/bin/ghc-stage2 -fforce-recomp Main.hs
[1 of 1] Compiling Main ( Main.hs, Main.o )
isTouchableMetaTyVar call @ TcInteract.lhs:482 for i_c
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for i_c
isTouchableMetaTyVar call @ TcInteract.lhs:482 for i_g
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for i_g
isTouchableMetaTyVar call @ TcInteract.lhs:482 for i_n
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for i_n
isTouchableMetaTyVar call @ TcInteract.lhs:482 for i_r
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for i_r
isTouchableMetaTyVar call @ TcInteract.lhs:474 for a
isTouchableMetaTyVar call @ TcInteract.lhs:475 for theVARIABLE
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for a
ghc-stage2: panic! (the 'impossible' happened)
(GHC version 7.5.20120420 for x86_64-unknown-linux):
ASSERT failed!
file compiler/typecheck/TcSMonad.lhs line 1221 a{tv ahY} [tv]
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
Uncommenting (b) to use our own Complex a:
{{{
$ inplace/bin/ghc-stage2 -fforce-recomp Main.hs
[1 of 1] Compiling Main ( Main.hs, Main.o )
isTouchableMetaTyVar call @ TcInteract.lhs:482 for i_c
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for i_c
isTouchableMetaTyVar call @ TcInteract.lhs:482 for i_g
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for i_g
isTouchableMetaTyVar call @ TcInteract.lhs:482 for i_n
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for i_n
isTouchableMetaTyVar call @ TcInteract.lhs:482 for i_r
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for i_r
isTouchableMetaTyVar call @ TcInteract.lhs:482 for c_o
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for c_o
isTouchableMetaTyVar call @ TcInteract.lhs:482 for i_u
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for i_u
isTouchableMetaTyVar call @ TcInteract.lhs:482 for i_y
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for i_y
isTouchableMetaTyVar call @ TcInteract.lhs:482 for c_v
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for c_v
isTouchableMetaTyVar call @ TcInteract.lhs:482 for c_h
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for c_h
isTouchableMetaTyVar call @ TcInteract.lhs:482 for c_d
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for c_d
isTouchableMetaTyVar call @ TcInteract.lhs:474 for p_f
isTouchableMetaTyVar call @ TcInteract.lhs:475 for x
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for p_f
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for x
isTouchableMetaTyVar call @ TcInteract.lhs:482 for t_ts
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for t_ts
isTouchableMetaTyVar call @ TcInteract.lhs:482 for t_tw
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for t_tw
isTouchableMetaTyVar call @ TcInteract.lhs:482 for t_tB
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for t_tB
isTouchableMetaTyVar call @ TcInteract.lhs:482 for t_tE
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for t_tE
isTouchableMetaTyVar call @ TcInteract.lhs:482 for t_tC
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for t_tC
isTouchableMetaTyVar call @ TcInteract.lhs:482 for t_tG
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for t_tG
isTouchableMetaTyVar call @ TcInteract.lhs:482 for t_tJ
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for t_tJ
isTouchableMetaTyVar call @ TcInteract.lhs:482 for t_tH
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for t_tH
isTouchableMetaTyVar call @ TcInteract.lhs:482 for t_tx
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for t_tx
isTouchableMetaTyVar call @ TcInteract.lhs:482 for t_tt
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for t_tt
isTouchableMetaTyVar call @ TcInteract.lhs:474 for t_tv
isTouchableMetaTyVar call @ TcInteract.lhs:475 for x
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for t_tv
isTouchableMetaTyVar_InRange call @ TcSMonad.lhs for x
Linking Main ...
}}}
The debugging output is just 'trace' calls inserted at the call sites of
isTouchableMetaTyVar and isTouchableMetaTyVar_InRange (diffs against the
HEAD follow, reported line numbers may be wrong if you have local
modifications):
TcInteract.lhs diff:
{{{
diff --git a/compiler/typecheck/TcInteract.lhs
b/compiler/typecheck/TcInteract.lhs
index a2e0b99..fa4a630 100644
--- a/compiler/typecheck/TcInteract.lhs
+++ b/compiler/typecheck/TcInteract.lhs
@@ -471,15 +471,15 @@ trySpontaneousSolve workItem@(CTyEqCan { cc_flavor =
gw
| isGivenOrSolved gw
= return SPCantSolve
| Just tv2 <- tcGetTyVar_maybe xi
- = do { tch1 <- isTouchableMetaTyVar tv1
- ; tch2 <- isTouchableMetaTyVar tv2
+ = do { tch1 <- trace ("isTouchableMetaTyVar call @ TcInteract.lhs:474
for "++(showSDoc (ppr tv1))) (isTouchableMetaTyVar tv1)
+ ; tch2 <- trace ("isTouchableMetaTyVar call @ TcInteract.lhs:475
for "++(showSDoc (ppr tv2))) (isTouchableMetaTyVar tv2)
; case (tch1, tch2) of
(True, True) -> trySpontaneousEqTwoWay d gw tv1 tv2
(True, False) -> trySpontaneousEqOneWay d gw tv1 xi
(False, True) -> trySpontaneousEqOneWay d gw tv2 (mkTyVarTy
tv1)
_ -> return SPCantSolve }
| otherwise
- = do { tch1 <- isTouchableMetaTyVar tv1
+ = do { tch1 <- trace ("isTouchableMetaTyVar call @ TcInteract.lhs:482
for "++(showSDoc (ppr tv1))) (isTouchableMetaTyVar tv1)
; if tch1 then trySpontaneousEqOneWay d gw tv1 xi
else do { traceTcS "Untouchable LHS, can't spontaneously
solve workitem:" $
ppr workItem
@@ -1935,8 +1935,8 @@ matchClassInst inerts clas tys loc
, cc_flavor = fl })
| isGiven fl
= ASSERT( clas_g == clas )
- case tcUnifyTys (\tv -> if isTouchableMetaTyVar_InRange untch tv
&&
- tv `elemVarSet` tyVarsOfTypes tys
+ case tcUnifyTys (\tv -> if (trace ("isTouchableMetaTyVar_InRange
call @ TcInteract.lhs:1938 for "++(showSDoc (ppr tv)))
(isTouchableMetaTyVar_InRange untch tv &&
+ tv `elemVarSet` tyVarsOfTypes tys))
then BindMe else Skolem) tys sys of
-- We can't learn anything more about any variable at this point,
so the only
-- cause of overlap can be by an instantiation of a touchable
unification
}}}
TcSimplify.lhs diff:
{{{
diff --git a/compiler/typecheck/TcSimplify.lhs
b/compiler/typecheck/TcSimplify.lhs
index 26d4c9f..24a1125 100644
--- a/compiler/typecheck/TcSimplify.lhs
+++ b/compiler/typecheck/TcSimplify.lhs
@@ -1149,7 +1149,7 @@ getSolvableCTyFunEqs untch cts
, cc_rhs = xi })
| Just tv <- tcGetTyVar_maybe xi -- RHS is a type variable
- , isTouchableMetaTyVar_InRange untch tv
+ , trace ("isTouchableMetaTyVar_InRange call @ TcSimplify.lhs:1152
for "++(showSDoc (ppr tv))) (isTouchableMetaTyVar_InRange untch tv)
-- And it's a *touchable* unification variable
, typeKind xi `tcIsSubKind` tyVarKind tv
@@ -1297,7 +1297,7 @@ defaultTyVar :: TcsUntouchables -> TcTyVar -> TcS
Cts
-- whatever, because the type-class defaulting rules have yet to run.
defaultTyVar untch the_tv
- | isTouchableMetaTyVar_InRange untch the_tv
+ | trace ("isTouchableMetaTyVar_InRange call @ TcSimplify.lhs:1300 for
"++(showSDoc (ppr the_tv))) (isTouchableMetaTyVar_InRange untch the_tv)
, not (k `eqKind` default_k)
= tryTcS $ -- Why tryTcS? See Note [tryTcS in defaulting]
do { let loc = CtLoc DefaultOrigin (getSrcSpan the_tv) [] -- Yuk
@@ -1353,7 +1353,7 @@ findDefaultableGroups (ctxt, default_tys,
(ovl_strings, extended_defaults))
is_defaultable_group ds@((_,tv):_)
= let b1 = isTyConableTyVar tv -- Note [Avoiding spurious errors]
b2 = not (tv `elemVarSet` bad_tvs)
- b3 = isTouchableMetaTyVar_InRange untch tv
+ b3 = trace ("isTouchableMetaTyVar_InRange call @
TcSimplify.lhs:1356 for "++(showSDoc (ppr tv)))
(isTouchableMetaTyVar_InRange untch tv )
b4 = defaultable_classes [cc_class cc | (cc,_) <- ds]
in (b1 && b2 && b3 && b4)
{- pprTrace "is_defaultable_group" (vcat [ text "isTyConable
" <+> ppr tv <+> ppr b1
}}}
TcSMonad.lhs diff:
{{{
diff --git a/compiler/typecheck/TcSMonad.lhs
b/compiler/typecheck/TcSMonad.lhs
index b3a64e3..5d3abf8 100644
--- a/compiler/typecheck/TcSMonad.lhs
+++ b/compiler/typecheck/TcSMonad.lhs
@@ -1214,7 +1214,7 @@ pprEq ty1 ty2 = pprType $ mkEqPred ty1 ty2
isTouchableMetaTyVar :: TcTyVar -> TcS Bool
isTouchableMetaTyVar tv
= do { untch <- getUntouchables
- ; return $ isTouchableMetaTyVar_InRange untch tv }
+ ; return $ (trace ("isTouchableMetaTyVar_InRange call @
TcSMonad.lhs for "++(showSDoc (ppr tv))) (isTouchableMetaTyVar_InRange
untch tv)) }
isTouchableMetaTyVar_InRange :: TcsUntouchables -> TcTyVar -> Bool
isTouchableMetaTyVar_InRange (untch,untch_tcs) tv
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5884#comment:7>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs