Repository : ssh://darcs.haskell.org//srv/darcs/ghc On branch :
http://hackage.haskell.org/trac/ghc/changeset/3506e622aaefb00eb20b379ab210a8a417de1172 >--------------------------------------------------------------- commit 3506e622aaefb00eb20b379ab210a8a417de1172 Author: Max Bolingbroke <batterseapo...@hotmail.com> Date: Tue Mar 20 15:28:18 2012 +0000 Fix possible kinding error associated with defaulting dead type variables >--------------------------------------------------------------- .../supercompile/Supercompile/Drive/Process.hs | 15 +++++++-------- 1 files changed, 7 insertions(+), 8 deletions(-) diff --git a/compiler/supercompile/Supercompile/Drive/Process.hs b/compiler/supercompile/Supercompile/Drive/Process.hs index a6dc8c2..e3c3685 100644 --- a/compiler/supercompile/Supercompile/Drive/Process.hs +++ b/compiler/supercompile/Supercompile/Drive/Process.hs @@ -47,15 +47,14 @@ import Supercompile.Termination.Generaliser import Supercompile.StaticFlags import Supercompile.Utilities hiding (Monad(..)) -import Var (isId, isTyVar, varType, setVarType) +import Var (isTyVar, isId, tyVarKind, varType, setVarType) import Id (idType, zapFragileIdInfo, localiseId, isDictId) import MkId (voidArgId, realWorldPrimId, mkPrimOpId) -import Type (isUnLiftedType, mkTyVarTy) import Coercion (isCoVar, mkCoVarCo, mkUnsafeCo, coVarKind) import TyCon (PrimRep(..)) -import Type (eqType, mkFunTy, mkPiTypes, mkTyConApp, typePrimRep, splitTyConApp_maybe) +import Type (Kind, isUnLiftedType, mkTyVarTy, eqType, mkFunTy, mkPiTypes, mkTyConApp, typePrimRep, splitTyConApp_maybe) import TysPrim -import TysWiredIn (unitTy, unboxedPairDataCon, unboxedPairTyCon) +import TysWiredIn (unboxedPairDataCon, unboxedPairTyCon) import MkCore (mkWildValBinder, quantVarLe) import PrimOp (PrimOp(MyThreadIdOp)) import Literal @@ -769,14 +768,14 @@ mkLiveAbsVar x = AbsVar { absVarDead = False, absVarVar = x } -- We map *all* occurrences of dead TyVars to this type, to ensure that dead TyVars in the -- type of applied Ids match the applied dead TyVars. This type can be any closed type, as long -- as we use it consistently! -deadTy :: Type -deadTy = unitTy +deadTy :: Kind -> Type +deadTy = anyTypeOfKind renameAbsVarType :: M.Map Var Var -> Var -> Var renameAbsVarType rn x = x `setVarType` renameType (mkInScopeSet as) complete_rn ty where ty = varType x as = tyVarsOfType ty - complete_rn = mkTyVarRenaming [(a, case M.lookup a rn of Nothing -> deadTy; Just a' -> mkTyVarTy a') | a <- varSetElems as] + complete_rn = mkTyVarRenaming [(a, case M.lookup a rn of Nothing -> deadTy (tyVarKind a); Just a' -> mkTyVarTy a') | a <- varSetElems as] -- If a variable is not present in the input renaming, we assume that it has become dead -- and set the deadness information accordingly @@ -813,7 +812,7 @@ applyAbsVars x xs = snd (foldl go (unitVarSet x, var x) xs) True -> (fvs, case () of () -- We can encounter TyVars, where we should be able to instantiate them any way: | isTyVar x - -> e `tyApp` deadTy + -> e `tyApp` deadTy (tyVarKind x) -- Dead CoVars are easy: | isCoVar x, let (ty1, ty2) = coVarKind x _______________________________________________ Cvs-ghc mailing list Cvs-ghc@haskell.org http://www.haskell.org/mailman/listinfo/cvs-ghc