[commit: ghc] master: Move AsmCodeGen.makeFarBranches to PPC.Instr (#709) (aa1d7d3)
Simon Marlow
marlowsd at gmail.com
Mon Feb 4 12:35:53 CET 2013
Repository : ssh://darcs.haskell.org//srv/darcs/ghc
On branch : master
http://hackage.haskell.org/trac/ghc/changeset/aa1d7d35ac27625c9aa67fe71c186f79600f0201
>---------------------------------------------------------------
commit aa1d7d35ac27625c9aa67fe71c186f79600f0201
Author: PHO <pho at cielonegro.org>
Date: Thu Dec 20 02:13:51 2012 +0900
Move AsmCodeGen.makeFarBranches to PPC.Instr (#709)
Its implementation is totally specific to PPC.
>---------------------------------------------------------------
compiler/nativeGen/AsmCodeGen.lhs | 39 +-----------------------------------
compiler/nativeGen/PPC/Instr.hs | 40 ++++++++++++++++++++++++++++++++++++-
2 files changed, 40 insertions(+), 39 deletions(-)
diff --git a/compiler/nativeGen/AsmCodeGen.lhs b/compiler/nativeGen/AsmCodeGen.lhs
index 58c3c75..9ab1c4a 100644
--- a/compiler/nativeGen/AsmCodeGen.lhs
+++ b/compiler/nativeGen/AsmCodeGen.lhs
@@ -27,7 +27,6 @@ import qualified SPARC.ShortcutJump
import qualified SPARC.CodeGen.Expand
import qualified PPC.CodeGen
-import qualified PPC.Cond
import qualified PPC.Regs
import qualified PPC.RegInfo
import qualified PPC.Instr
@@ -210,7 +209,7 @@ ppcNcgImpl dflags
,ncg_x86fp_kludge = id
,ncgAllocMoreStack = PPC.Instr.allocMoreStack platform
,ncgExpandTop = id
- ,ncgMakeFarBranches = makeFarBranches
+ ,ncgMakeFarBranches = PPC.Instr.makeFarBranches
}
where platform = targetPlatform dflags
@@ -734,42 +733,6 @@ reorder id accum (b@(block,id',out) : rest)
-- -----------------------------------------------------------------------------
--- Making far branches
-
--- Conditional branches on PowerPC are limited to +-32KB; if our Procs get too
--- big, we have to work around this limitation.
-
-makeFarBranches
- :: [NatBasicBlock PPC.Instr.Instr]
- -> [NatBasicBlock PPC.Instr.Instr]
-makeFarBranches blocks
- | last blockAddresses < nearLimit = blocks
- | otherwise = zipWith handleBlock blockAddresses blocks
- where
- blockAddresses = scanl (+) 0 $ map blockLen blocks
- blockLen (BasicBlock _ instrs) = length instrs
-
- handleBlock addr (BasicBlock id instrs)
- = BasicBlock id (zipWith makeFar [addr..] instrs)
-
- makeFar _ (PPC.Instr.BCC PPC.Cond.ALWAYS tgt) = PPC.Instr.BCC PPC.Cond.ALWAYS tgt
- makeFar addr (PPC.Instr.BCC cond tgt)
- | abs (addr - targetAddr) >= nearLimit
- = PPC.Instr.BCCFAR cond tgt
- | otherwise
- = PPC.Instr.BCC cond tgt
- where Just targetAddr = lookupUFM blockAddressMap tgt
- makeFar _ other = other
-
- nearLimit = 7000 -- 8192 instructions are allowed; let's keep some
- -- distance, as we have a few pseudo-insns that are
- -- pretty-printed as multiple instructions,
- -- and it's just not worth the effort to calculate
- -- things exactly
-
- blockAddressMap = listToUFM $ zip (map blockId blocks) blockAddresses
-
--- -----------------------------------------------------------------------------
-- Generate jump tables
-- Analyzes all native code and generates data sections for all jump
diff --git a/compiler/nativeGen/PPC/Instr.hs b/compiler/nativeGen/PPC/Instr.hs
index 80b7556..212d10d 100644
--- a/compiler/nativeGen/PPC/Instr.hs
+++ b/compiler/nativeGen/PPC/Instr.hs
@@ -14,7 +14,8 @@ module PPC.Instr (
RI(..),
Instr(..),
maxSpillSlots,
- allocMoreStack
+ allocMoreStack,
+ makeFarBranches
)
where
@@ -36,6 +37,7 @@ import CLabel
import Outputable
import Platform
import FastBool
+import UniqFM (listToUFM, lookupUFM)
import UniqSupply
--------------------------------------------------------------------------------
@@ -505,3 +507,39 @@ ppc_mkJumpInstr id
ppc_takeRegRegMoveInstr :: Instr -> Maybe (Reg,Reg)
ppc_takeRegRegMoveInstr (MR dst src) = Just (src,dst)
ppc_takeRegRegMoveInstr _ = Nothing
+
+-- -----------------------------------------------------------------------------
+-- Making far branches
+
+-- Conditional branches on PowerPC are limited to +-32KB; if our Procs get too
+-- big, we have to work around this limitation.
+
+makeFarBranches
+ :: [NatBasicBlock Instr]
+ -> [NatBasicBlock Instr]
+makeFarBranches blocks
+ | last blockAddresses < nearLimit = blocks
+ | otherwise = zipWith handleBlock blockAddresses blocks
+ where
+ blockAddresses = scanl (+) 0 $ map blockLen blocks
+ blockLen (BasicBlock _ instrs) = length instrs
+
+ handleBlock addr (BasicBlock id instrs)
+ = BasicBlock id (zipWith makeFar [addr..] instrs)
+
+ makeFar _ (BCC ALWAYS tgt) = BCC ALWAYS tgt
+ makeFar addr (BCC cond tgt)
+ | abs (addr - targetAddr) >= nearLimit
+ = BCCFAR cond tgt
+ | otherwise
+ = BCC cond tgt
+ where Just targetAddr = lookupUFM blockAddressMap tgt
+ makeFar _ other = other
+
+ nearLimit = 7000 -- 8192 instructions are allowed; let's keep some
+ -- distance, as we have a few pseudo-insns that are
+ -- pretty-printed as multiple instructions,
+ -- and it's just not worth the effort to calculate
+ -- things exactly
+
+ blockAddressMap = listToUFM $ zip (map blockId blocks) blockAddresses
More information about the ghc-commits
mailing list