Repository : ssh://darcs.haskell.org//srv/darcs/ghc On branch : supercompiler
http://hackage.haskell.org/trac/ghc/changeset/007e71025d9a151fdde664d1b4f141b000f795e5 >--------------------------------------------------------------- commit 007e71025d9a151fdde664d1b4f141b000f795e5 Author: Max Bolingbroke <batterseapo...@hotmail.com> Date: Tue Apr 24 10:37:04 2012 +0100 Tweak dead type defaulting >--------------------------------------------------------------- .../supercompile/Supercompile/Drive/Process.hs | 7 ++++++- 1 files changed, 6 insertions(+), 1 deletions(-) diff --git a/compiler/supercompile/Supercompile/Drive/Process.hs b/compiler/supercompile/Supercompile/Drive/Process.hs index 74916a5..28a7da5 100644 --- a/compiler/supercompile/Supercompile/Drive/Process.hs +++ b/compiler/supercompile/Supercompile/Drive/Process.hs @@ -53,6 +53,7 @@ import MkId (voidArgId, realWorldPrimId, mkPrimOpId) import Coercion (isCoVar, mkCoVarCo, mkUnsafeCo, coVarKind) import TyCon (PrimRep(..)) import Type (Kind, isUnLiftedType, mkTyVarTy, eqType, mkFunTy, mkPiTypes, mkTyConApp, typePrimRep, splitTyConApp_maybe) +import Kind (isUnliftedTypeKind) import TysPrim import TysWiredIn (unboxedPairDataCon, unboxedPairTyCon) import MkCore (mkWildValBinder, quantVarLe) @@ -734,8 +735,12 @@ 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! +-- +-- NB: we can't use anyTypeOfKind for the unlifted kind because Any# is hardcoded as having Ptr +-- representation, which causes us to make some weird unsafeCoerces deadTy :: Kind -> Type -deadTy = anyTypeOfKind +deadTy k | isUnliftedTypeKind k = realWorldStatePrimTy + | otherwise = anyTypeOfKind k renameAbsVarType :: Renaming -> Var -> Var renameAbsVarType rn x = x `setVarType` renameType (mkInScopeSet as) rn ty _______________________________________________ Cvs-ghc mailing list Cvs-ghc@haskell.org http://www.haskell.org/mailman/listinfo/cvs-ghc