- class (Outputable m, Outputable l, LastNode l, Outputable (LGraph m l)) => DebugNodes m l
- data RewritingDepth
- 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))
- zdfSolveFromL :: (DataflowSolverDirection transfers fixedpt, DebugNodes m l, Outputable a) => BlockEnv a -> PassName -> DataflowLattice a -> transfers m l a -> a -> LGraph m l -> FuelMonad (fixedpt m l a ())
- data ForwardTransfers middle last a = ForwardTransfers {
- ft_first_out :: BlockId -> a -> a
- ft_middle_out :: middle -> a -> a
- ft_last_outs :: last -> a -> LastOutFacts a
- ft_exit_out :: a -> a
- data BackwardTransfers middle last a = BackwardTransfers {
- bt_first_in :: BlockId -> a -> a
- bt_middle_in :: middle -> a -> a
- bt_last_in :: last -> (BlockId -> a) -> a
- data ForwardRewrites middle last a = ForwardRewrites {}
- data BackwardRewrites middle last a = BackwardRewrites {}
- 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
- zdfBRewriteFromL :: (DebugNodes m l, Outputable a) => RewritingDepth -> BlockEnv a -> PassName -> DataflowLattice a -> BackwardTransfers m l a -> BackwardRewrites m l a -> a -> LGraph m l -> FuelMonad (BackwardFixedPoint m l a (LGraph m l))
- zdfFRewriteFromL :: (DebugNodes m l, Outputable a) => RewritingDepth -> BlockEnv a -> PassName -> DataflowLattice a -> ForwardTransfers m l a -> ForwardRewrites m l a -> a -> LGraph m l -> FuelMonad (ForwardFixedPoint m l a (LGraph m l))
Documentation
class (Outputable m, Outputable l, LastNode l, Outputable (LGraph m l)) => DebugNodes m l Source
newtype LastOutFacts a Source
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 |
:: (DataflowSolverDirection transfers fixedpt, DebugNodes m l, Outputable a) | |
=> BlockEnv a | Initial facts (unbound == bottom) |
-> PassName | |
-> DataflowLattice a | Lattice |
-> transfers m l a | Dataflow transfer functions |
-> a | Fact flowing in (at entry or exit) |
-> Graph m l | Graph 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))Source
zdfSolveFromL :: (DataflowSolverDirection transfers fixedpt, DebugNodes m l, Outputable a) => BlockEnv a -> PassName -> DataflowLattice a -> transfers m l a -> a -> LGraph m l -> FuelMonad (fixedpt m l a ())Source
data ForwardTransfers middle last a Source
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.
ForwardTransfers | |
|
DataflowSolverDirection ForwardTransfers ForwardFixedPoint | |
DataflowDirection ForwardTransfers ForwardFixedPoint ForwardRewrites |
data BackwardTransfers middle last a Source
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.
BackwardTransfers | |
|
DataflowSolverDirection BackwardTransfers BackwardFixedPoint | |
DataflowDirection BackwardTransfers BackwardFixedPoint BackwardRewrites |
data ForwardRewrites middle last a Source
A forward rewrite takes the same inputs as a forward transfer, but instead of producing a fact, it produces a replacement graph or Nothing.
DataflowDirection ForwardTransfers ForwardFixedPoint ForwardRewrites |
data BackwardRewrites middle last a Source
A backward rewrite takes the same inputs as a backward transfer, but instead of producing a fact, it produces a replacement graph or Nothing.
DataflowDirection BackwardTransfers BackwardFixedPoint BackwardRewrites |
data ForwardFixedPoint m l fact a Source
A forward problem needs the common fields, plus the facts on the outedges.
FixedPoint ForwardFixedPoint | |
DataflowSolverDirection ForwardTransfers ForwardFixedPoint | |
DataflowDirection ForwardTransfers ForwardFixedPoint ForwardRewrites |
type BackwardFixedPoint = CommonFixedPointSource
The common fixed point is sufficient for a backward problem.
zdfFpFacts :: FixedPoint fp => fp m l fact a -> BlockEnv factSource
zdfFpOutputFact :: FixedPoint fp => fp m l fact a -> factSource
zdfGraphChanged :: FixedPoint fp => fp m l fact a -> ChangeFlagSource
zdfDecoratedGraph :: FixedPoint fp => fp m l fact a -> Graph (fact, m) (fact, l)Source
zdfFpContents :: FixedPoint fp => fp m l fact a -> aSource
zdfFpLastOuts :: ForwardFixedPoint m l fact a -> LastOutFacts factSource
zdfBRewriteFromL :: (DebugNodes m l, Outputable a) => RewritingDepth -> BlockEnv a -> PassName -> DataflowLattice a -> BackwardTransfers m l a -> BackwardRewrites m l a -> a -> LGraph m l -> FuelMonad (BackwardFixedPoint m l a (LGraph m l))Source
zdfFRewriteFromL :: (DebugNodes m l, Outputable a) => RewritingDepth -> BlockEnv a -> PassName -> DataflowLattice a -> ForwardTransfers m l a -> ForwardRewrites m l a -> a -> LGraph m l -> FuelMonad (ForwardFixedPoint m l a (LGraph m l))Source