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

On branch  : supercompiler

http://hackage.haskell.org/trac/ghc/changeset/07302b1cc7adb6faedb6739d2dd007054bba63f7

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

commit 07302b1cc7adb6faedb6739d2dd007054bba63f7
Author: Max Bolingbroke <batterseapo...@hotmail.com>
Date:   Wed Jul 4 18:15:32 2012 +0100

    Restrict stack pruning to preserve effectivness of NOINLINE and friends

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

 .../Supercompile/Evaluator/Evaluate.hs             |   19 ++++++++++++++++++-
 1 files changed, 18 insertions(+), 1 deletions(-)

diff --git a/compiler/supercompile/Supercompile/Evaluator/Evaluate.hs 
b/compiler/supercompile/Supercompile/Evaluator/Evaluate.hs
index 10f9b9a..0fb500c 100644
--- a/compiler/supercompile/Supercompile/Evaluator/Evaluate.hs
+++ b/compiler/supercompile/Supercompile/Evaluator/Evaluate.hs
@@ -24,6 +24,7 @@ import TyCon
 import Type
 import PrelRules
 import Id
+import IdInfo (isShortableIdInfo)
 import DataCon
 import Pair
 import BasicTypes
@@ -662,8 +663,24 @@ gc _state@(deeds0, Heap h ids, k, in_e)
               | x' `elemVarSet` live = (h_pending_kvs,            M.insert x' 
hb h_output, live `unionVarSet` heapBindingFreeVars hb `unionVarSet` 
varBndrFreeVars x')
               | otherwise            = ((x', hb) : h_pending_kvs, h_output,    
            live)
     
+    -- NB: doing this is cool yet also dangerous at the same time. What if we 
have:
+    --  {-# NOINLINE foo #-}
+    --  foo = \x -> e
+    --
+    --  root = case foo 100 of \Delta
+    --
+    -- After normalisation + GCing (including dropping dead update frames) we 
will basically get:
+    --  case (\x -> e) 100 of \Delta
+    --
+    -- So this is really bad because we have lost the NOINLINE information!
+    -- Of course, this is also sometimes cool because it turns non-normalising 
beta-reductions into manifestly normalising ones.
+    --
+    -- My compromise is to allow dumping only those binders with "shortable" 
IdInfo, where shortability
+    -- is a notion stolen from GHCs simplifier.
+    --
+    -- TODO: perhaps this same check should be applied in the Update frame 
compressor, though that would destroy some stack invariants
     pruneLiveStack :: Deeds -> Stack -> FreeVars -> (Deeds, Stack)
-    pruneLiveStack init_deeds k live = trainFoldr (\kf (deeds, k_live) -> if 
(case tagee kf of Update x' -> x' `elemVarSet` live; _ -> True)
+    pruneLiveStack init_deeds k live = trainFoldr (\kf (deeds, k_live) -> if 
(case tagee kf of Update x' | isShortableIdInfo (idInfo x') -> x' `elemVarSet` 
live; _ -> True)
                                                                           then 
(deeds, kf `Car` k_live)
                                                                           else 
(deeds `releaseStackFrameDeeds` kf, k_live))
                                                   (\gen deeds -> (deeds, Loco 
gen)) init_deeds k



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

Reply via email to