summaryrefslogtreecommitdiff
path: root/compiler
diff options
context:
space:
mode:
authorEdward Z. Yang <ezyang@mit.edu>2011-06-16 18:28:49 +0100
committerEdward Z. Yang <ezyang@mit.edu>2011-06-17 12:48:41 +0100
commite26ea0f4144f0989e390367c2cf138ce48550ff4 (patch)
treec020ea51bdde76b369497ccaf65132e719a69350 /compiler
parentf141e108deade85c51bf064e9ccbca785ad8e1c1 (diff)
downloadhaskell-e26ea0f4144f0989e390367c2cf138ce48550ff4.tar.gz
Refactoring CmmSpillReload and CmmLive.
Signed-off-by: Edward Z. Yang <ezyang@mit.edu>
Diffstat (limited to 'compiler')
-rw-r--r--compiler/cmm/CmmLive.hs22
-rw-r--r--compiler/cmm/CmmPipeline.hs1
-rw-r--r--compiler/cmm/CmmSpillReload.hs58
-rw-r--r--compiler/cmm/cmm-notes5
4 files changed, 49 insertions, 37 deletions
diff --git a/compiler/cmm/CmmLive.hs b/compiler/cmm/CmmLive.hs
index c87a3a9b33..8baad04dc9 100644
--- a/compiler/cmm/CmmLive.hs
+++ b/compiler/cmm/CmmLive.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE GADTs #-}
+
{-# OPTIONS_GHC -fno-warn-warnings-deprecations #-}
module CmmLive
@@ -47,9 +48,6 @@ cmmLiveness graph =
where entry = g_entry graph
check facts = noLiveOnEntry entry (expectJust "check" $ mapLookup entry facts) facts
-gen_kill :: (DefinerOfLocalRegs a, UserOfLocalRegs a) => a -> CmmLive -> CmmLive
-gen_kill a = gen a . kill a
-
-- | On entry to the procedure, there had better not be any LocalReg's live-in.
noLiveOnEntry :: BlockId -> CmmLive -> a -> a
noLiveOnEntry bid in_fact x =
@@ -57,19 +55,23 @@ noLiveOnEntry bid in_fact x =
else pprPanic "LocalReg's live-in to graph" (ppr bid <+> ppr in_fact)
-- | The transfer equations use the traditional 'gen' and 'kill'
--- notations, which should be familiar from the dragon book.
-gen :: UserOfLocalRegs a => a -> RegSet -> RegSet
-gen a live = foldRegsUsed extendRegSet live a
+-- notations, which should be familiar from the Dragon Book.
+gen :: UserOfLocalRegs a => a -> RegSet -> RegSet
+gen a live = foldRegsUsed extendRegSet live a
kill :: DefinerOfLocalRegs a => a -> RegSet -> RegSet
kill a live = foldRegsDefd delOneFromUniqSet live a
--- Testing!
+gen_kill :: (DefinerOfLocalRegs a, UserOfLocalRegs a) => a -> CmmLive -> CmmLive
+gen_kill a = gen a . kill a
+
+-- | The transfer function
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 f
lst :: CmmNode O C -> FactBase CmmLive -> CmmLive
- lst n f = gen_kill n $ case n of CmmCall {} -> emptyRegSet
- CmmForeignCall {} -> emptyRegSet
- _ -> joinOutFacts liveLattice n f
+ lst n f = gen_kill n
+ $ case n of CmmCall{} -> emptyRegSet
+ CmmForeignCall{} -> emptyRegSet
+ _ -> joinOutFacts liveLattice n f
diff --git a/compiler/cmm/CmmPipeline.hs b/compiler/cmm/CmmPipeline.hs
index a63413cf53..7cfece45b4 100644
--- a/compiler/cmm/CmmPipeline.hs
+++ b/compiler/cmm/CmmPipeline.hs
@@ -108,6 +108,7 @@ cpsTop hsc_env (CmmProc h@(TopInfo {stack_info=StackInfo {arg_space=entry_off}})
----------- Eliminate dead assignments -------------------
-- Remove redundant reloads (and any other redundant asst)
+ -- in CmmSpillReloads
g <- runOptimization $ removeDeadAssignmentsAndReloads procPoints g
dump Opt_D_dump_cmmz_dead "Post Dead Assignment Elimination" g
diff --git a/compiler/cmm/CmmSpillReload.hs b/compiler/cmm/CmmSpillReload.hs
index 1dbfbb051b..e3f631da09 100644
--- a/compiler/cmm/CmmSpillReload.hs
+++ b/compiler/cmm/CmmSpillReload.hs
@@ -9,11 +9,7 @@
#endif
module CmmSpillReload
- ( DualLive(..)
- , dualLiveLattice, dualLiveTransfers, dualLiveness
- --, insertSpillsAndReloads --- XXX todo check live-in at entry against formals
- , dualLivenessWithInsertion
-
+ ( dualLivenessWithInsertion
, removeDeadAssignmentsAndReloads
)
where
@@ -35,21 +31,22 @@ import Prelude hiding (succ, zip)
{- Note [Overview of spill/reload]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-The point of this module is to insert spills and reloads to
-establish the invariant that at a call (or at any proc point with
-an established protocol) all live variables not expected in
-registers are sitting on the stack. We use a backward analysis to
-insert spills and reloads. It should be followed by a
-forward transformation to sink reloads as deeply as possible, so as
-to reduce register pressure.
+The point of this module is to insert spills and reloads to establish
+the invariant that at a call or any proc point with an established
+protocol all live variables not expected in registers are sitting on the
+stack. We use a backward dual liveness analysis (both traditional
+register liveness as well as register slot liveness on the stack) to
+insert spills and reloads. It should be followed by a forward
+transformation to sink reloads as deeply as possible, so as to reduce
+register pressure: this transformation is performed by
+CmmRewriteAssignments.
A variable can be expected to be live in a register, live on the
stack, or both. This analysis ensures that spills and reloads are
inserted as needed to make sure that every live variable needed
-after a call is available on the stack. Spills are pushed back to
-their reaching definitions, but reloads are dropped immediately after
-we return from a call and will have to be sunk by a later forward
-transformation.
+after a call is available on the stack. Spills are placed immediately
+after their reaching definitions, but reloads are placed immediately
+after a return from a call (the entry point.)
Note that we offer no guarantees about the consistency of the value
in memory and the value in the register, except that they are
@@ -89,19 +86,26 @@ dualLivenessWithInsertion procPoints g =
(dualLiveTransfers (g_entry g) procPoints)
(insertSpillAndReloadRewrites g procPoints)
-dualLiveness :: BlockSet -> CmmGraph -> FuelUniqSM (BlockEnv DualLive)
-dualLiveness procPoints g =
+_dualLiveness :: BlockSet -> CmmGraph -> FuelUniqSM (BlockEnv DualLive)
+_dualLiveness procPoints g =
liftM snd $ dataflowPassBwd g [] $ analBwd dualLiveLattice $ dualLiveTransfers (g_entry g) procPoints
+-- Note [Live registers on entry to procpoints]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+-- Remember that the transfer function is only ever run on the rewritten
+-- version of a graph, and the rewrite function for spills and reloads
+-- enforces the invariant that no local registers are live on entry to
+-- a procpoint. Accordingly, we check for this invariant here. An old
+-- version of this code incorrectly claimed that any live registers were
+-- live on the stack before entering the function: this is wrong, but
+-- didn't cause bugs because it never actually was invoked.
+
dualLiveTransfers :: BlockId -> BlockSet -> (BwdTransfer CmmNode DualLive)
dualLiveTransfers entry procPoints = mkBTransfer3 first middle last
where first :: CmmNode C O -> DualLive -> DualLive
- first (CmmEntry id) live = check live id $ -- live at procPoint => spill
- if id /= entry && setMember id procPoints
- then DualLive { on_stack = on_stack live `plusRegSet` in_regs live
- , in_regs = emptyRegSet }
- else live
- where check live id x = if id == entry then noLiveOnEntry id (in_regs live) x else x
+ first (CmmEntry id) live -- See Note [Live registers on entry to procpoints]
+ | id == entry || setMember id procPoints = noLiveOnEntry id (in_regs live) live
+ | otherwise = live
middle :: CmmNode O O -> DualLive -> DualLive
middle m = changeStack updSlots
@@ -114,9 +118,13 @@ dualLiveTransfers entry procPoints = mkBTransfer3 first middle last
spill live _ = live
reload live s@(RegSlot r, _, _) = check s $ extendRegSet live r
reload live _ = live
+ -- Ensure the assignment refers to the entirety of the
+ -- register slot (and not just a slice).
check (RegSlot (LocalReg _ ty), o, w) x
| o == w && w == widthInBytes (typeWidth ty) = x
check _ _ = panic "middleDualLiveness unsupported: slices"
+
+ -- Differences from vanilla liveness analysis
last :: CmmNode O C -> FactBase DualLive -> DualLive
last l fb = case l of
CmmBranch id -> lkp id
@@ -184,6 +192,8 @@ spill, reload :: LocalReg -> CmmNode O O
spill r = CmmStore (regSlot r) (CmmReg $ CmmLocal r)
reload r = CmmAssign (CmmLocal r) (CmmLoad (regSlot r) $ localRegType r)
+-- XXX: This should be done with generic liveness analysis and moved to
+-- its own module
removeDeadAssignmentsAndReloads :: BlockSet -> CmmGraph -> FuelUniqSM CmmGraph
removeDeadAssignmentsAndReloads procPoints g =
liftM fst $ dataflowPassBwd g [] $ analRewBwd dualLiveLattice
diff --git a/compiler/cmm/cmm-notes b/compiler/cmm/cmm-notes
index 4a87911ec5..f35e72d36c 100644
--- a/compiler/cmm/cmm-notes
+++ b/compiler/cmm/cmm-notes
@@ -12,9 +12,6 @@ More notes (June 11)
insertLateReloads is now gone, every reload is reloading a live variable.
Test and nuke.
-* Sink and inline S(RegSlot(x)) = e in precisely the same way that we
- sink and inline x = e
-
* Stack layout is very like register assignment: find non-conflicting assigments.
In particular we can use colouring or linear scan (etc).
@@ -103,6 +100,8 @@ Things to do:
dichotomy. Mostly this means global replace, but we also need to make
Label an instance of Outputable (probably in the Outputable module).
+ EZY: We should use Label, since that's the terminology Hoopl uses.
+
- NB that CmmProcPoint line 283 has a hack that works around a GADT-related
bug in 6.10.