[commit: ghc] wip/T10137: Use import lists in simple cases (fd51a9b)
git at git.haskell.org
git at git.haskell.org
Mon Mar 9 15:59:51 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/T10137
Link : http://ghc.haskell.org/trac/ghc/changeset/fd51a9b344ee823353e7d1922e8cfaaf7f5363a1/ghc
>---------------------------------------------------------------
commit fd51a9b344ee823353e7d1922e8cfaaf7f5363a1
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Mon Mar 9 16:07:20 2015 +0100
Use import lists in simple cases
>---------------------------------------------------------------
fd51a9b344ee823353e7d1922e8cfaaf7f5363a1
compiler/cmm/CmmCommonBlockElim.hs | 2 +-
compiler/cmm/CmmContFlowOpt.hs | 2 +-
compiler/cmm/CmmLint.hs | 2 +-
compiler/cmm/CmmNode.hs | 2 +-
compiler/cmm/CmmParse.y | 2 +-
compiler/cmm/MkGraph.hs | 4 ++--
6 files changed, 7 insertions(+), 7 deletions(-)
diff --git a/compiler/cmm/CmmCommonBlockElim.hs b/compiler/cmm/CmmCommonBlockElim.hs
index 8f2b07e..0912410 100644
--- a/compiler/cmm/CmmCommonBlockElim.hs
+++ b/compiler/cmm/CmmCommonBlockElim.hs
@@ -8,7 +8,7 @@ where
import BlockId
import Cmm
import CmmUtils
-import CmmSwitch
+import CmmSwitch (eqSwitchTargetWith)
import CmmContFlowOpt
import Prelude hiding (iterate, succ, unzip, zip)
diff --git a/compiler/cmm/CmmContFlowOpt.hs b/compiler/cmm/CmmContFlowOpt.hs
index 6842687..95c1950 100644
--- a/compiler/cmm/CmmContFlowOpt.hs
+++ b/compiler/cmm/CmmContFlowOpt.hs
@@ -12,7 +12,7 @@ import Hoopl
import BlockId
import Cmm
import CmmUtils
-import CmmSwitch
+import CmmSwitch (mapSwitchTargets)
import Maybes
import Panic
diff --git a/compiler/cmm/CmmLint.hs b/compiler/cmm/CmmLint.hs
index d1e80fd..edce2e9 100644
--- a/compiler/cmm/CmmLint.hs
+++ b/compiler/cmm/CmmLint.hs
@@ -14,7 +14,7 @@ import Hoopl
import Cmm
import CmmUtils
import CmmLive
-import CmmSwitch
+import CmmSwitch (switchTargetsToList)
import PprCmm ()
import BlockId
import FastString
diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs
index 1899a00..3bdc70f 100644
--- a/compiler/cmm/CmmNode.hs
+++ b/compiler/cmm/CmmNode.hs
@@ -494,7 +494,7 @@ mapExpM f (CmmAssign r e) = CmmAssign r `fmap` f e
mapExpM f (CmmStore addr e) = (\[addr', e'] -> CmmStore addr' e') `fmap` mapListM f [addr, e]
mapExpM _ (CmmBranch _) = Nothing
mapExpM f (CmmCondBranch e ti fi) = (\x -> CmmCondBranch x ti fi) `fmap` f e
-mapExpM f (CmmSwitch e ids) = (\x -> CmmSwitch x ids) `fmap` f e
+mapExpM f (CmmSwitch e tbl) = (\x -> CmmSwitch x tbl) `fmap` f e
mapExpM f (CmmCall tgt mb_id r o i s) = (\x -> CmmCall x mb_id r o i s) `fmap` f tgt
mapExpM f (CmmUnsafeForeignCall tgt fs as)
= case mapForeignTargetM f tgt of
diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y
index 0322927..8ce5c1d 100644
--- a/compiler/cmm/CmmParse.y
+++ b/compiler/cmm/CmmParse.y
@@ -226,7 +226,7 @@ import CmmOpt
import MkGraph
import Cmm
import CmmUtils
-import CmmSwitch
+import CmmSwitch ( mkSwitchTargets )
import CmmInfo
import BlockId
import CmmLex
diff --git a/compiler/cmm/MkGraph.hs b/compiler/cmm/MkGraph.hs
index 6a7ee01..d2aa4aa 100644
--- a/compiler/cmm/MkGraph.hs
+++ b/compiler/cmm/MkGraph.hs
@@ -22,7 +22,7 @@ where
import BlockId
import Cmm
import CmmCallConv
-import CmmSwitch
+import CmmSwitch (SwitchTargets)
import Compiler.Hoopl hiding (Unique, (<*>), mkFirst, mkMiddle, mkLast, mkLabel, mkBranch, Shape(..))
import DynFlags
@@ -225,7 +225,7 @@ mkCbranch :: CmmExpr -> BlockId -> BlockId -> CmmAGraph
mkCbranch pred ifso ifnot = mkLast (CmmCondBranch pred ifso ifnot)
mkSwitch :: CmmExpr -> SwitchTargets -> CmmAGraph
-mkSwitch e ids = mkLast $ CmmSwitch e ids
+mkSwitch e tbl = mkLast $ CmmSwitch e tbl
mkReturn :: DynFlags -> CmmExpr -> [CmmActual] -> UpdFrameOffset
-> CmmAGraph
More information about the ghc-commits
mailing list