[commit: ghc] wip/T10137: CmmSwitch: Actually do nothing when targetting C or LLVM (92452b3)
git at git.haskell.org
git at git.haskell.org
Thu Mar 19 09:12:08 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/T10137
Link : http://ghc.haskell.org/trac/ghc/changeset/92452b36417da684de9b81d8b0731731b632605d/ghc
>---------------------------------------------------------------
commit 92452b36417da684de9b81d8b0731731b632605d
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Thu Mar 19 10:12:00 2015 +0100
CmmSwitch: Actually do nothing when targetting C or LLVM
>---------------------------------------------------------------
92452b36417da684de9b81d8b0731731b632605d
compiler/cmm/CmmCreateSwitchPlans.hs | 4 +++-
compiler/cmm/CmmSwitch.hs | 9 +++++++++
2 files changed, 12 insertions(+), 1 deletion(-)
diff --git a/compiler/cmm/CmmCreateSwitchPlans.hs b/compiler/cmm/CmmCreateSwitchPlans.hs
index 0fac30c..1ca0cd4 100644
--- a/compiler/cmm/CmmCreateSwitchPlans.hs
+++ b/compiler/cmm/CmmCreateSwitchPlans.hs
@@ -29,7 +29,9 @@ import DynFlags
-- | Traverses the 'CmmGraph', making sure that 'CmmSwitch' are suitable for
-- code generation.
cmmCreateSwitchPlans :: DynFlags -> CmmGraph -> UniqSM CmmGraph
-cmmCreateSwitchPlans dflags g = do
+cmmCreateSwitchPlans dflags g
+ | targetSupportsSwitch (hscTarget dflags) = return g
+ | otherwise = do
blocks' <- concat `fmap` mapM (visitSwitches dflags) (toBlockList g)
return $ ofBlockList (g_entry g) blocks'
diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs
index 7190d6e..edb2087 100644
--- a/compiler/cmm/CmmSwitch.hs
+++ b/compiler/cmm/CmmSwitch.hs
@@ -7,10 +7,12 @@ module CmmSwitch (
switchTargetsToList, eqSwitchTargetWith,
SwitchPlan(..),
+ targetSupportsSwitch,
createSwitchPlan,
) where
import Outputable
+import DynFlags
import Compiler.Hoopl (Label)
import Data.Maybe
@@ -243,6 +245,13 @@ data SwitchPlan
type FlatSwitchPlan = SeparatedList Integer SwitchPlan
+-- | Does the target support switch out of the box? Then leave this to the
+-- target!
+targetSupportsSwitch :: HscTarget -> Bool
+targetSupportsSwitch HscC = True
+targetSupportsSwitch HscLlvm = True
+targetSupportsSwitch _ = False
+
-- | This function creates a SwitchPlan from a SwitchTargets value, breaking it
-- down into smaller pieces suitable for code generation.
createSwitchPlan :: SwitchTargets -> SwitchPlan
More information about the ghc-commits
mailing list