[GHC] #7805: Panic: promoteType with higher-rank datatype

#7805: Panic: promoteType with higher-rank datatype -------------------------------+-------------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Component: Compiler Version: 7.7 | Keywords: DataKinds Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: Compile-time crash | Blockedby: Blocking: | Related: -------------------------------+-------------------------------------------- The following code causes the panic in HEAD: {{{ {-# LANGUAGE DataKinds, RankNTypes, TypeFamilies #-} data HigherRank = HR (forall a. a -> a) type family F (x :: HigherRank) type instance F (HR x) = Bool }}} Here is the panic text: {{{ ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.7.20130329 for x86_64-apple-darwin): promoteType }}} This panic does not happen with GHC 7.6.1. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7805 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7805: Panic: promoteType with higher-rank datatype -------------------------------+-------------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Component: Compiler Version: 7.7 | Keywords: DataKinds Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: Compile-time crash | Blockedby: Blocking: | Related: -------------------------------+-------------------------------------------- Comment(by goldfire): The following change fixes the problem and passes the {{{polykinds}}} tests: {{{ diff --git a/compiler/typecheck/TcTyDecls.lhs b/compiler/typecheck/TcTyDecls.lhs index 99ee065..690bea6 100644 --- a/compiler/typecheck/TcTyDecls.lhs +++ b/compiler/typecheck/TcTyDecls.lhs @@ -506,21 +506,21 @@ isPromotableType :: NameSet -> Type -> Bool -- Must line up with DataCon.promoteType -- But the function lives here because we must treat the -- *recursive* tycons as promotable isPromotableType rec_tcs ty = case splitForAllTys ty of - (_, rho) -> go rho + (tvs, rho) -> null tvs && go rho where go (TyConApp tc tys) | tys `lengthIs` tyConArity tc , tyConName tc `elemNameSet` rec_tcs || isJust (promotableTyCon_maybe tc) = all go tys | otherwise = False go (FunTy arg res) = go arg && go res go (AppTy arg res) = go arg && go res - go (ForAllTy _ ty) = go ty + go (ForAllTy {}) = False go (TyVarTy {}) = True go (LitTy {}) = False \end{code} }}} The change looks right to me. The change to {{{ForAllTy}}} is unnecessary to fix the original bug, but it is easy to create another test case that requires the {{{ForAllTy}}} fix. Is there a reason that the quantified variables were ignored previously? -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7805#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7805: Panic: promoteType with higher-rank datatype
-------------------------------+--------------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.7 | Keywords: DataKinds
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: Compile-time crash | Blockedby:
Blocking: | Related:
-------------------------------+--------------------------------------------
Comment(by simonpj@…):
commit 7501a2c3a181a53789e4f4462847295354042849
{{{
Author: Simon Peyton Jones

#7805: Panic: promoteType with higher-rank datatype ---------------------------------+------------------------------------------ Reporter: goldfire | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: fixed | Keywords: DataKinds Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: Compile-time crash | Difficulty: Unknown Testcase: polykinds/T7805 | Blockedby: Blocking: | Related: ---------------------------------+------------------------------------------ Changes (by simonpj): * status: new => closed * difficulty: => Unknown * resolution: => fixed * testcase: => polykinds/T7805 Comment: Correct, thanks. Simon -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7805#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC