Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : 

http://hackage.haskell.org/trac/ghc/changeset/167fed1eab77bdcf932fd7439b1ac7a01f5d6eb0

>---------------------------------------------------------------

commit 167fed1eab77bdcf932fd7439b1ac7a01f5d6eb0
Author: Max Bolingbroke <batterseapo...@hotmail.com>
Date:   Tue Jan 3 13:53:45 2012 +0000

    Ensure we localise AbsVars when building binding sites

>---------------------------------------------------------------

 .../supercompile/Supercompile/Drive/Process.hs     |   18 +++++++++++++++---
 1 files changed, 15 insertions(+), 3 deletions(-)

diff --git a/compiler/supercompile/Supercompile/Drive/Process.hs 
b/compiler/supercompile/Supercompile/Drive/Process.hs
index ef9a318..af20b89 100644
--- a/compiler/supercompile/Supercompile/Drive/Process.hs
+++ b/compiler/supercompile/Supercompile/Drive/Process.hs
@@ -45,7 +45,7 @@ import Supercompile.Utilities hiding (Monad(..))
 
 import Name       (getOccString)
 import Var        (isId, isTyVar, varType, setVarType)
-import Id         (idType, idOccInfo, zapFragileIdInfo, setIdOccInfo)
+import Id         (idType, idOccInfo, zapFragileIdInfo, setIdOccInfo, 
localiseId)
 import Type       (isUnLiftedType, mkTyVarTy)
 import Coercion   (isCoVar, mkCoVarCo, mkUnsafeCo, coVarKind_maybe, 
mkCoercionType)
 import TyCon      (PrimRep(..))
@@ -455,8 +455,20 @@ renameAbsVar rn (AbsVar { absVarDead = dead, absVarVar = x 
})
 --  1. If the h-function is unlifted, this delays its evaluation (so its 
effects, if any, do not happen too early)
 --  2. This expresses to GHC that we don't necessarily want the work in 
h-functions to be shared
 
+-- NB: it's important that we use localiseId on the absVarVar at binding 
sites, or else if we start
+-- with a state where a global Id is lambda-bound (because there is no 
unfolding) we might end up having an h-function
+-- that is lambda-abstracted over a global Id, which causes the assembler to 
barf.
+--
+-- (We will rely on a later simplifier run to propagate the local Id bindings 
down to the possibly-global Id use sites)
+--
+-- This will rarely happpen in practice because global variables should be 
Let-bound in the heap, which would prevent
+-- us from lambda-abstracting over them. However, it can happen if the global 
is abstracted due to generalisation,
+-- such as when the let-bound thing binds a (:) and we generalise away some 
other (:).
+absVarBinder :: AbsVar -> Var
+absVarBinder = localiseId . absVarVar
+
 absVarLambdas :: Symantics ann => [AbsVar] -> ann (TermF ann) -> ann (TermF 
ann)
-absVarLambdas xs = tyVarIdLambdas (map absVarVar xs)
+absVarLambdas xs = tyVarIdLambdas (map absVarBinder xs)
 
 applyAbsVars :: Symantics ann => Var -> [AbsVar] -> ann (TermF ann)
 applyAbsVars x xs = snd (foldl go (unitVarSet x, var x) xs)
@@ -499,7 +511,7 @@ applyAbsVars x xs = snd (foldl go (unitVarSet x, var x) xs)
                  -- Unlifted thing of PtrRep: yes, this can really happen 
(ByteArray# etc)
                  PtrRep    -> pprPanic "applyAbsVars: dead unlifted variable 
with PrimRep PtrRep: FIXME" (ppr ty)
          -> let_ x (e_repr `cast` mkUnsafeCo e_repr_ty ty) (e `app` x))
-         where shadowy_x = absVarVar absx
+         where shadowy_x = absVarBinder absx
                x = uniqAway (mkInScopeSet fvs) shadowy_x
                ty = idType x
     False -> (fvs `extendVarSet` x, case () of



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to