summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--compiler/cmm/CmmBuildInfoTables.hs2
-rw-r--r--compiler/cmm/CmmLive.hs7
-rw-r--r--compiler/cmm/CmmProcPoint.hs2
-rw-r--r--compiler/cmm/CmmUtils.hs40
-rw-r--r--compiler/cmm/Hoopl.hs8
-rw-r--r--compiler/cmm/Hoopl/Dataflow.hs81
6 files changed, 59 insertions, 81 deletions
diff --git a/compiler/cmm/CmmBuildInfoTables.hs b/compiler/cmm/CmmBuildInfoTables.hs
index e756b06ac0..a7ef994f11 100644
--- a/compiler/cmm/CmmBuildInfoTables.hs
+++ b/compiler/cmm/CmmBuildInfoTables.hs
@@ -107,7 +107,7 @@ cafTransfers = mkBTransfer3 first middle last
else s
cafAnal :: CmmGraph -> CAFEnv
-cafAnal g = dataflowAnalBwd g [] $ analBwd cafLattice cafTransfers
+cafAnal g = dataflowAnalBwd g [] cafLattice cafTransfers
-----------------------------------------------------------------------
-- Building the SRTs
diff --git a/compiler/cmm/CmmLive.hs b/compiler/cmm/CmmLive.hs
index bbb36cbd9b..97bf361bcd 100644
--- a/compiler/cmm/CmmLive.hs
+++ b/compiler/cmm/CmmLive.hs
@@ -18,10 +18,9 @@ where
import DynFlags
import BlockId
import Cmm
-import CmmUtils
import PprCmmExpr ()
+import Hoopl.Dataflow
-import Hoopl
import Maybes
import Outputable
@@ -52,14 +51,14 @@ type BlockEntryLiveness r = BlockEnv (CmmLive r)
cmmLocalLiveness :: DynFlags -> CmmGraph -> BlockEntryLiveness LocalReg
cmmLocalLiveness dflags graph =
- check $ dataflowAnalBwd graph [] $ analBwd liveLattice (xferLive dflags)
+ check $ dataflowAnalBwd graph [] liveLattice (xferLive dflags)
where entry = g_entry graph
check facts = noLiveOnEntry entry
(expectJust "check" $ mapLookup entry facts) facts
cmmGlobalLiveness :: DynFlags -> CmmGraph -> BlockEntryLiveness GlobalReg
cmmGlobalLiveness dflags graph =
- dataflowAnalBwd graph [] $ analBwd liveLattice (xferLive dflags)
+ dataflowAnalBwd graph [] liveLattice (xferLive dflags)
-- | On entry to the procedure, there had better not be any LocalReg's live-in.
noLiveOnEntry :: BlockId -> CmmLive LocalReg -> a -> a
diff --git a/compiler/cmm/CmmProcPoint.hs b/compiler/cmm/CmmProcPoint.hs
index 0e772c41d0..e409fc42a1 100644
--- a/compiler/cmm/CmmProcPoint.hs
+++ b/compiler/cmm/CmmProcPoint.hs
@@ -135,7 +135,7 @@ procPointAnalysis :: ProcPointSet -> CmmGraph -> UniqSM (BlockEnv Status)
-- See Note [Proc-point analysis]
procPointAnalysis procPoints g@(CmmGraph {g_graph = graph}) =
-- pprTrace "procPointAnalysis" (ppr procPoints) $
- dataflowAnalFwdBlocks g initProcPoints $ analFwd lattice forward
+ return $ dataflowAnalFwdBlocks g initProcPoints lattice forward
where initProcPoints = [(id, ProcPoint) | id <- setElems procPoints,
id `setMember` labelsInGraph ]
-- See Note [Non-existing proc-points]
diff --git a/compiler/cmm/CmmUtils.hs b/compiler/cmm/CmmUtils.hs
index bce02fa948..241c2695b9 100644
--- a/compiler/cmm/CmmUtils.hs
+++ b/compiler/cmm/CmmUtils.hs
@@ -58,10 +58,6 @@ module CmmUtils(
toBlockListEntryFirst, toBlockListEntryFirstFalseFallthrough,
foldGraphBlocks, mapGraphNodes, postorderDfs, mapGraphNodes1,
- analFwd, analBwd,
- dataflowAnalFwd, dataflowAnalBwd,
- dataflowAnalFwdBlocks,
-
-- * Ticks
blockTicks
) where
@@ -77,7 +73,6 @@ import BlockId
import CLabel
import Outputable
import Unique
-import UniqSupply
import DynFlags
import Util
import CodeGen.Platform
@@ -559,41 +554,6 @@ postorderDfs :: CmmGraph -> [CmmBlock]
postorderDfs g = {-# SCC "postorderDfs" #-} postorder_dfs_from (toBlockMap g) (g_entry g)
-------------------------------------------------
--- Running dataflow analysis and/or rewrites
-
--- Constructing forward and backward analysis-only pass
-analFwd :: DataflowLattice f -> FwdTransfer n f -> FwdPass UniqSM n f
-analBwd :: DataflowLattice f -> BwdTransfer n f -> BwdPass UniqSM n f
-
-analFwd lat xfer =
- FwdPass {fp_lattice = lat, fp_transfer = xfer, fp_rewrite = noFwdRewrite}
-analBwd lat xfer =
- BwdPass {bp_lattice = lat, bp_transfer = xfer, bp_rewrite = noBwdRewrite}
-
-dataflowAnalFwd :: NonLocal n =>
- GenCmmGraph n -> [(BlockId, f)]
- -> FwdPass UniqSM n f
- -> BlockEnv f
-dataflowAnalFwd (CmmGraph {g_entry=entry, g_graph=graph}) facts fwd =
- analyzeFwd fwd (JustC [entry]) graph (mkFactBase (fp_lattice fwd) facts)
-
-dataflowAnalFwdBlocks :: NonLocal n =>
- GenCmmGraph n -> [(BlockId, f)]
- -> FwdPass UniqSM n f
- -> UniqSM (BlockEnv f)
-dataflowAnalFwdBlocks (CmmGraph {g_entry=entry, g_graph=graph}) facts fwd = do
--- (graph, facts, NothingO) <- analyzeAndRewriteFwd fwd (JustC [entry]) graph (mkFactBase (fp_lattice fwd) facts)
--- return facts
- return (analyzeFwdBlocks fwd (JustC [entry]) graph (mkFactBase (fp_lattice fwd) facts))
-
-dataflowAnalBwd :: NonLocal n =>
- GenCmmGraph n -> [(BlockId, f)]
- -> BwdPass UniqSM n f
- -> BlockEnv f
-dataflowAnalBwd (CmmGraph {g_entry=entry, g_graph=graph}) facts bwd =
- analyzeBwd bwd (JustC [entry]) graph (mkFactBase (bp_lattice bwd) facts)
-
--------------------------------------------------
-- Tick utilities
-- | Extract all tick annotations from the given block
diff --git a/compiler/cmm/Hoopl.hs b/compiler/cmm/Hoopl.hs
index b8acc5a3e6..513ab5b596 100644
--- a/compiler/cmm/Hoopl.hs
+++ b/compiler/cmm/Hoopl.hs
@@ -10,13 +10,9 @@ import Compiler.Hoopl hiding
Unique,
FwdTransfer(..), FwdRewrite(..), FwdPass(..),
BwdTransfer(..), BwdRewrite(..), BwdPass(..),
- noFwdRewrite, noBwdRewrite,
- analyzeAndRewriteFwd, analyzeAndRewriteBwd,
mkFactBase, Fact,
- mkBRewrite, mkBRewrite3, mkBTransfer, mkBTransfer3,
- mkFRewrite, mkFRewrite3, mkFTransfer, mkFTransfer3,
- deepFwdRw, deepFwdRw3, thenFwdRw, iterFwdRw,
- deepBwdRw, deepBwdRw3, thenBwdRw, iterBwdRw
+ mkBRewrite3, mkBTransfer3,
+ mkFRewrite3, mkFTransfer3,
)
import Hoopl.Dataflow
diff --git a/compiler/cmm/Hoopl/Dataflow.hs b/compiler/cmm/Hoopl/Dataflow.hs
index 47142d5d7b..d8d37121f1 100644
--- a/compiler/cmm/Hoopl/Dataflow.hs
+++ b/compiler/cmm/Hoopl/Dataflow.hs
@@ -18,32 +18,55 @@
--
module Hoopl.Dataflow
- ( DataflowLattice(..), OldFact(..), NewFact(..), Fact, mkFactBase
+ ( C, O, DataflowLattice(..), OldFact(..), NewFact(..), Fact, FactBase
+ , mkFactBase
, ChangeFlag(..)
- , FwdPass(..), FwdTransfer, mkFTransfer, mkFTransfer3, getFTransfer3
+ , FwdPass(..), FwdTransfer, mkFTransfer3
- , BwdPass(..), BwdTransfer, mkBTransfer, mkBTransfer3, getBTransfer3
-
- , noBwdRewrite, noFwdRewrite
+ , BwdPass(..), BwdTransfer, mkBTransfer3
+ , dataflowAnalFwdBlocks, dataflowAnalBwd
, analyzeFwd, analyzeFwdBlocks, analyzeBwd
+
+ , changeIf
+ , joinOutFacts
)
where
-import UniqSupply
+import BlockId
+import Cmm
import Data.Array
-import Compiler.Hoopl hiding (noFwdRewrite, noBwdRewrite)
-
-noRewrite :: a -> b -> UniqSM (Maybe c)
-noRewrite _ _ = return Nothing
+import Compiler.Hoopl
-noFwdRewrite :: FwdRewrite UniqSM n f
-noFwdRewrite = FwdRewrite3 (noRewrite, noRewrite, noRewrite)
+-- TODO(michalt): This wrapper will go away once we refactor the analyze*
+-- methods.
+dataflowAnalFwdBlocks
+ :: NonLocal n
+ => GenCmmGraph n
+ -> [(BlockId, f)]
+ -> DataflowLattice f
+ -> FwdTransfer n f
+ -> BlockEnv f
+dataflowAnalFwdBlocks
+ (CmmGraph {g_entry = entry, g_graph = graph}) facts lattice xfer =
+ analyzeFwdBlocks
+ lattice xfer (JustC [entry]) graph (mkFactBase lattice facts)
+
+-- TODO(michalt): This wrapper will go away once we refactor the analyze*
+-- methods.
+dataflowAnalBwd
+ :: NonLocal n
+ => GenCmmGraph n
+ -> [(BlockId, f)]
+ -> DataflowLattice f
+ -> BwdTransfer n f
+ -> BlockEnv f
+dataflowAnalBwd
+ (CmmGraph {g_entry = entry, g_graph = graph}) facts lattice xfer =
+ analyzeBwd lattice xfer (JustC [entry]) graph (mkFactBase lattice facts)
-noBwdRewrite :: BwdRewrite UniqSM n f
-noBwdRewrite = BwdRewrite3 (noRewrite, noRewrite, noRewrite)
----------------------------------------------------------------
-- Forward Analysis only
@@ -52,14 +75,14 @@ noBwdRewrite = BwdRewrite3 (noRewrite, noRewrite, noRewrite)
-- | if the graph being analyzed is open at the entry, there must
-- be no other entry point, or all goes horribly wrong...
analyzeFwd
- :: forall n f e . NonLocal n =>
- FwdPass UniqSM n f
+ :: forall n f e . NonLocal n
+ => DataflowLattice f
+ -> FwdTransfer n f
-> MaybeC e [Label]
-> Graph n e C -> Fact e f
-> FactBase f
-analyzeFwd FwdPass { fp_lattice = lattice,
- fp_transfer = FwdTransfer3 (ftr, mtr, ltr) }
- entries g in_fact = graph g in_fact
+analyzeFwd lattice (FwdTransfer3 (ftr, mtr, ltr)) entries g in_fact =
+ graph g in_fact
where
graph :: Graph n e C -> Fact e f -> FactBase f
graph (GMany entry blockmap NothingO)
@@ -94,14 +117,14 @@ analyzeFwd FwdPass { fp_lattice = lattice,
-- | if the graph being analyzed is open at the entry, there must
-- be no other entry point, or all goes horribly wrong...
analyzeFwdBlocks
- :: forall n f e . NonLocal n =>
- FwdPass UniqSM n f
+ :: forall n f e . NonLocal n
+ => DataflowLattice f
+ -> FwdTransfer n f
-> MaybeC e [Label]
-> Graph n e C -> Fact e f
-> FactBase f
-analyzeFwdBlocks FwdPass { fp_lattice = lattice,
- fp_transfer = FwdTransfer3 (ftr, _, ltr) }
- entries g in_fact = graph g in_fact
+analyzeFwdBlocks lattice (FwdTransfer3 (ftr, _, ltr)) entries g in_fact =
+ graph g in_fact
where
graph :: Graph n e C -> Fact e f -> FactBase f
graph (GMany entry blockmap NothingO)
@@ -136,14 +159,14 @@ analyzeFwdBlocks FwdPass { fp_lattice = lattice,
-- | if the graph being analyzed is open at the entry, there must
-- be no other entry point, or all goes horribly wrong...
analyzeBwd
- :: forall n f e . NonLocal n =>
- BwdPass UniqSM n f
+ :: forall n f e . NonLocal n
+ => DataflowLattice f
+ -> BwdTransfer n f
-> MaybeC e [Label]
-> Graph n e C -> Fact C f
-> FactBase f
-analyzeBwd BwdPass { bp_lattice = lattice,
- bp_transfer = BwdTransfer3 (ftr, mtr, ltr) }
- entries g in_fact = graph g in_fact
+analyzeBwd lattice (BwdTransfer3 (ftr, mtr, ltr)) entries g in_fact =
+ graph g in_fact
where
graph :: Graph n e C -> Fact C f -> FactBase f
graph (GMany entry blockmap NothingO)