|
|
|
|
Synopsis |
|
class (Outputable m, Outputable l, LastNode l, Outputable (LGraph m l)) => DebugNodes m l | | | | 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 {} | | data BackwardTransfers middle last a = BackwardTransfers {} | | 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 |
|
|
Documentation |
|
class (Outputable m, Outputable l, LastNode l, Outputable (LGraph m l)) => DebugNodes m l |
| 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 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)) |
|
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 | |
|
| 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 | |
|
| 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 | | 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 | | Instances | |
|
|
data ForwardFixedPoint m l fact a |
A forward problem needs the common fields, plus the facts on the outedges.
| 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 |