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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/8a0ab97b1daefb57b53d6cf08a01bd597d09e32d

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

commit 8a0ab97b1daefb57b53d6cf08a01bd597d09e32d
Author: Edward Z. Yang <ezy...@mit.edu>
Date:   Mon Apr 11 11:54:34 2011 +0100

    Unsafe foreign calls (fat machine instructions) do not kill all registers.
    
    The new code generator was doing some interesting spilling across
    unsafe foreign calls:
    
         _c1ao::I32 = Hp - 4;
         I32[Sp - 20] = _c1ao::I32;
         foreign "ccall"
           newCAF((BaseReg, PtrHint), (R1, PtrHint))[_unsafe_call_];
         _c1ao::I32 = I32[Sp - 20];
    
    This is fairly unnecessary, and resulted from over-conservative
    liveness analysis from CmmLive.  We can see that the old code
    generator only saved volatile registers across unsafe foreign calls:
    spilling variables was done by saveVolatileVarsAndRegs, which was
    only performed for ordinary calls.
    
    This commit removes the excess kill from the liveness analysis, as well
    as the *redundant* excess kill from spilling-and-reloading, and adds a
    note to CmmNode to this effect.  The only registers we need to kill
    are the ones that the foreign call assigns to, just like any other
    machine instruction.
    
    Signed-off-by: Edward Z. Yang <ezy...@mit.edu>

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

 compiler/cmm/CmmLive.hs        |    4 ++--
 compiler/cmm/CmmNode.hs        |    2 ++
 compiler/cmm/CmmSpillReload.hs |   10 +++++-----
 3 files changed, 9 insertions(+), 7 deletions(-)

diff --git a/compiler/cmm/CmmLive.hs b/compiler/cmm/CmmLive.hs
index 78867b0..c87a3a9 100644
--- a/compiler/cmm/CmmLive.hs
+++ b/compiler/cmm/CmmLive.hs
@@ -63,12 +63,12 @@ gen  a live = foldRegsUsed    extendRegSet      live a
 kill :: DefinerOfLocalRegs a => a -> RegSet -> RegSet
 kill a live = foldRegsDefd delOneFromUniqSet live a
 
+-- Testing!
 xferLive :: BwdTransfer CmmNode CmmLive
 xferLive = mkBTransfer3 fst mid lst
   where fst _ f = f
         mid :: CmmNode O O -> CmmLive -> CmmLive
-        mid n f = gen_kill n $ case n of CmmUnsafeForeignCall {} -> emptyRegSet
-                                         _                       -> f
+        mid n f = gen_kill n f
         lst :: CmmNode O C -> FactBase CmmLive -> CmmLive
         lst n f = gen_kill n $ case n of CmmCall {}            -> emptyRegSet
                                          CmmForeignCall {}     -> emptyRegSet
diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs
index 93564ac..e67321c 100644
--- a/compiler/cmm/CmmNode.hs
+++ b/compiler/cmm/CmmNode.hs
@@ -92,6 +92,8 @@ data CmmNode e x where
 A MidForeign call is used for *unsafe* foreign calls;
 a LastForeign call is used for *safe* foreign calls.
 Unsafe ones are easy: think of them as a "fat machine instruction".
+In particular, they do *not* kill all live registers (there was a bit
+of code in GHC that conservatively assumed otherwise.)
 
 Safe ones are trickier.  A safe foreign call 
      r = f(x)
diff --git a/compiler/cmm/CmmSpillReload.hs b/compiler/cmm/CmmSpillReload.hs
index 4e2dd38..17364ad 100644
--- a/compiler/cmm/CmmSpillReload.hs
+++ b/compiler/cmm/CmmSpillReload.hs
@@ -100,11 +100,11 @@ dualLiveTransfers entry procPoints = mkBTransfer3 first 
middle last
             where check live id x = if id == entry then noLiveOnEntry id 
(in_regs live) x else x
 
           middle :: CmmNode O O -> DualLive -> DualLive
-          middle m live = changeStack updSlots $ changeRegs (xferLiveMiddle m) 
(changeRegs regs_in live)
-            where xferLiveMiddle = case getBTransfer3 xferLive of (_, middle, 
_) -> middle
-                 regs_in :: RegSet -> RegSet
-                  regs_in live = case m of CmmUnsafeForeignCall {} -> 
emptyRegSet
-                                           _ -> live
+          middle m = changeStack updSlots
+                   . changeRegs  updRegs
+            where -- Reuse middle of liveness analysis from CmmLive
+                  updRegs = case getBTransfer3 xferLive of (_, middle, _) -> 
middle m
+
                   updSlots live = foldSlotsUsed reload (foldSlotsDefd spill 
live m) m
                   spill  live s@(RegSlot r, _, _) = check s $ deleteFromRegSet 
live r
                   spill  live _ = live



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

Reply via email to