ghc-6.10.2: The GHC APIContentsIndex
ZipDataflow
Synopsis
class (Outputable m, Outputable l, LastNode l, Outputable (LGraph m l)) => DebugNodes m l
data RewritingDepth
= RewriteShallow
| RewriteDeep
newtype LastOutFacts a = LastOutFacts [(BlockId, a)]
zdfSolveFrom :: (DataflowSolverDirection transfers fixedpt, DebugNodes m l, Outputable a) => BlockEnv a -> PassName -> DataflowLattice a -> transfers m l a -> a -> Graph m l -> FuelMonad (fixedpt m l a ())
zdfRewriteFrom :: (DataflowDirection transfers fixedpt rewrites, DebugNodes m l, Outputable a) => RewritingDepth -> BlockEnv a -> PassName -> DataflowLattice a -> transfers m l a -> rewrites m l a -> a -> Graph m l -> FuelMonad (fixedpt m l a (Graph m l))
data ForwardTransfers middle last a = ForwardTransfers {
ft_first_out :: a -> BlockId -> a
ft_middle_out :: a -> middle -> a
ft_last_outs :: a -> last -> LastOutFacts a
ft_exit_out :: a -> a
}
data BackwardTransfers middle last a = BackwardTransfers {
bt_first_in :: a -> BlockId -> a
bt_middle_in :: a -> middle -> a
bt_last_in :: (BlockId -> a) -> last -> a
}
data ForwardRewrites middle last a = ForwardRewrites {
fr_first :: a -> BlockId -> Maybe (AGraph middle last)
fr_middle :: a -> middle -> Maybe (AGraph middle last)
fr_last :: a -> last -> Maybe (AGraph middle last)
fr_exit :: a -> Maybe (AGraph middle last)
}
data BackwardRewrites middle last a = BackwardRewrites {
br_first :: a -> BlockId -> Maybe (AGraph middle last)
br_middle :: a -> middle -> Maybe (AGraph middle last)
br_last :: (BlockId -> a) -> last -> Maybe (AGraph middle last)
br_exit :: Maybe (AGraph middle last)
}
data ForwardFixedPoint m l fact a
type BackwardFixedPoint = CommonFixedPoint
zdfFpFacts :: FixedPoint fp => fp m l fact a -> BlockEnv fact
zdfFpOutputFact :: FixedPoint fp => fp m l fact a -> fact
zdfGraphChanged :: FixedPoint fp => fp m l fact a -> ChangeFlag
zdfDecoratedGraph :: FixedPoint fp => fp m l fact a -> Graph (fact, m) (fact, l)
zdfFpContents :: FixedPoint fp => fp m l fact a -> a
zdfFpLastOuts :: ForwardFixedPoint m l fact a -> LastOutFacts fact
Documentation
class (Outputable m, Outputable l, LastNode l, Outputable (LGraph m l)) => DebugNodes m l
show/hide Instances
data RewritingDepth
Constructors
RewriteShallow
RewriteDeep
newtype LastOutFacts a
Constructors
LastOutFacts [(BlockId, a)]These are facts flowing out of a last node to the node's successors. They are either to be set (if they pertain to the graph currently under analysis) or propagated out of a sub-analysis
zdfSolveFrom
:: (DataflowSolverDirection transfers fixedpt, DebugNodes m l, Outputable a)
=> BlockEnv aInitial facts (unbound == bottom)
-> PassName
-> DataflowLattice aLattice
-> transfers m l aDataflow transfer functions
-> aFact flowing in (at entry or exit)
-> Graph m lGraph to be analyzed
-> FuelMonad (fixedpt m l a ())Answers
zdfRewriteFrom :: (DataflowDirection transfers fixedpt rewrites, DebugNodes m l, Outputable a) => RewritingDepth -> BlockEnv a -> PassName -> DataflowLattice a -> transfers m l a -> rewrites m l a -> a -> Graph m l -> FuelMonad (fixedpt m l a (Graph m l))
data ForwardTransfers middle last a
For a forward transfer, you're given the fact on a node's inedge and you compute the fact on the outedge. Because a last node may have multiple outedges, each pointing to a labelled block, so instead of a fact it produces a list of (BlockId, fact) pairs.
Constructors
ForwardTransfers
ft_first_out :: a -> BlockId -> a
ft_middle_out :: a -> middle -> a
ft_last_outs :: a -> last -> LastOutFacts a
ft_exit_out :: a -> a
show/hide Instances
data BackwardTransfers middle last a
For a backward transfer, you're given the fact on a node's outedge and you compute the fact on the inedge. Facts have type a. A last node may have multiple outedges, each pointing to a labelled block, so instead of a fact it is given a mapping from BlockId to fact.
Constructors
BackwardTransfers
bt_first_in :: a -> BlockId -> a
bt_middle_in :: a -> middle -> a
bt_last_in :: (BlockId -> a) -> last -> a
show/hide Instances
data ForwardRewrites middle last a
A forward rewrite takes the same inputs as a forward transfer, but instead of producing a fact, it produces a replacement graph or Nothing.
Constructors
ForwardRewrites
fr_first :: a -> BlockId -> Maybe (AGraph middle last)
fr_middle :: a -> middle -> Maybe (AGraph middle last)
fr_last :: a -> last -> Maybe (AGraph middle last)
fr_exit :: a -> Maybe (AGraph middle last)
show/hide Instances
data BackwardRewrites middle last a
A backward rewrite takes the same inputs as a backward transfer, but instead of producing a fact, it produces a replacement graph or Nothing. The type of the replacement graph is given as a type parameter g of kind * -> * -> *. This design offers great flexibility to clients, but it might be worth simplifying this module by replacing this type parameter with AGraph everywhere (SLPJ 19 May 2008).
Constructors
BackwardRewrites
br_first :: a -> BlockId -> Maybe (AGraph middle last)
br_middle :: a -> middle -> Maybe (AGraph middle last)
br_last :: (BlockId -> a) -> last -> Maybe (AGraph middle last)
br_exit :: Maybe (AGraph middle last)
show/hide Instances
data ForwardFixedPoint m l fact a
A forward problem needs the common fields, plus the facts on the outedges.
show/hide Instances
type BackwardFixedPoint = CommonFixedPoint
The common fixed point is sufficient for a backward problem.
zdfFpFacts :: FixedPoint fp => fp m l fact a -> BlockEnv fact
zdfFpOutputFact :: FixedPoint fp => fp m l fact a -> fact
zdfGraphChanged :: FixedPoint fp => fp m l fact a -> ChangeFlag
zdfDecoratedGraph :: FixedPoint fp => fp m l fact a -> Graph (fact, m) (fact, l)
zdfFpContents :: FixedPoint fp => fp m l fact a -> a
zdfFpLastOuts :: ForwardFixedPoint m l fact a -> LastOutFacts fact
Produced by Haddock version 2.4.2