Implement dead basic block elimination.
[ghc-hetmet.git] / compiler / cmm / CmmOpt.hs
index 0dec26d..1c7e7e5 100644 (file)
@@ -14,6 +14,7 @@
 -----------------------------------------------------------------------------
 
 module CmmOpt (
+       cmmEliminateDeadBlocks,
        cmmMiniInline,
        cmmMachOpFold,
        cmmLoopifyForC,
@@ -30,10 +31,70 @@ import UniqFM
 import Unique
 import FastTypes
 import Outputable
+import BlockId
 
 import Data.Bits
 import Data.Word
 import Data.Int
+import Data.Maybe
+
+import Compiler.Hoopl hiding (Unique)
+
+-- -----------------------------------------------------------------------------
+-- Eliminates dead blocks
+
+{-
+We repeatedly expand the set of reachable blocks until we hit a
+fixpoint, and then prune any blocks that were not in this set.  This is
+actually a required optimization, as dead blocks can cause problems
+for invariants in the linear register allocator (and possibly other
+places.)
+-}
+
+-- Deep fold over statements could probably be abstracted out, but it
+-- might not be worth the effort since OldCmm is moribund
+cmmEliminateDeadBlocks :: [CmmBasicBlock] -> [CmmBasicBlock]
+cmmEliminateDeadBlocks [] = []
+cmmEliminateDeadBlocks blocks@(BasicBlock base_id _:_) =
+    let -- Calculate what's reachable from what block
+        -- We have to do a deep fold into CmmExpr because
+        -- there may be a BlockId in the CmmBlock literal.
+        reachableMap = foldl f emptyBlockMap blocks
+            where f m (BasicBlock block_id stmts) = mapInsert block_id (reachableFrom stmts) m
+        reachableFrom stmts = foldl stmt emptyBlockSet stmts
+            where
+                stmt m CmmNop = m
+                stmt m (CmmComment _) = m
+                stmt m (CmmAssign _ e) = expr m e
+                stmt m (CmmStore e1 e2) = expr (expr m e1) e2
+                stmt m (CmmCall c _ as _ _) = f (actuals m as) c
+                    where f m (CmmCallee e _) = expr m e
+                          f m (CmmPrim _) = m
+                stmt m (CmmBranch b) = setInsert b m
+                stmt m (CmmCondBranch e b) = setInsert b (expr m e)
+                stmt m (CmmSwitch e bs) = foldl (flip setInsert) (expr m e) (catMaybes bs)
+                stmt m (CmmJump e as) = expr (actuals m as) e
+                stmt m (CmmReturn as) = actuals m as
+                actuals m as = foldl (\m h -> expr m (hintlessCmm h)) m as
+                expr m (CmmLit l) = lit m l
+                expr m (CmmLoad e _) = expr m e
+                expr m (CmmReg _) = m
+                expr m (CmmMachOp _ es) = foldl expr m es
+                expr m (CmmStackSlot _ _) = m
+                expr m (CmmRegOff _ _) = m
+                lit m (CmmBlock b) = setInsert b m
+                lit m _ = m
+        -- Expand reachable set until you hit fixpoint
+        initReachable = setSingleton base_id :: BlockSet
+        expandReachable old_set new_set =
+            if setSize new_set > setSize old_set
+                then expandReachable new_set $ setFold
+                        (\x s -> maybe setEmpty id (mapLookup x reachableMap) `setUnion` s)
+                        new_set
+                        (setDifference new_set old_set)
+                else new_set -- fixpoint achieved
+        reachable = expandReachable setEmpty initReachable
+    in filter (\(BasicBlock block_id _) -> setMember block_id reachable) blocks
 
 -- -----------------------------------------------------------------------------
 -- The mini-inliner
@@ -115,12 +176,15 @@ cmmMiniInlineStmts uses (stmt@(CmmAssign (CmmLocal (LocalReg u _)) expr) : stmts
 cmmMiniInlineStmts uses (stmt:stmts)
   = stmt : cmmMiniInlineStmts uses stmts
 
-lookForInline u expr (stmt : rest)
+lookForInline u expr stmts = lookForInline' u expr regset stmts
+    where regset = foldRegsUsed extendRegSet emptyRegSet expr
+
+lookForInline' u expr regset (stmt : rest)
   | Just 1 <- lookupUFM (countUses stmt) u, ok_to_inline
   = Just (inlineStmt u expr stmt : rest)
 
   | ok_to_skip
-  = case lookForInline u expr rest of
+  = case lookForInline' u expr regset rest of
            Nothing    -> Nothing
            Just stmts -> Just (stmt:stmts)
 
@@ -137,13 +201,18 @@ lookForInline u expr (stmt : rest)
                     CmmCall{} -> hasNoGlobalRegs expr
                     _ -> True
 
-   -- We can skip over assignments to other tempoararies, because we
-   -- know that expressions aren't side-effecting and temporaries are
-   -- single-assignment.
+   -- Expressions aren't side-effecting.  Temporaries may or may not
+   -- be single-assignment depending on the source (the old code
+   -- generator creates single-assignment code, but hand-written Cmm
+   -- and Cmm from the new code generator is not single-assignment.)
+   -- So we do an extra check to make sure that the register being
+   -- changed is not one we were relying on.  I don't know how much of a
+   -- performance hit this is (we have to create a regset for every
+   -- instruction.) -- EZY
     ok_to_skip = case stmt of
                  CmmNop -> True
                  CmmComment{} -> True
-                 CmmAssign (CmmLocal (LocalReg u' _)) rhs | u' /= u -> True
+                 CmmAssign (CmmLocal r@(LocalReg u' _)) rhs | u' /= u && not (r `elemRegSet` regset) -> True
                  CmmAssign g@(CmmGlobal _) rhs -> not (g `regUsedIn` expr)
                  _other -> False