ghc-7.0.4: The GHC API

ZipDataflow

Synopsis

Documentation

newtype LastOutFacts a Source

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

zdfSolveFromSource

Arguments

:: (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.

Constructors

ForwardTransfers 

Fields

ft_first_out :: BlockId -> a -> a
 
ft_middle_out :: middle -> a -> a
 
ft_last_outs :: last -> a -> LastOutFacts a
 
ft_exit_out :: a -> a
 

Instances

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.

Constructors

BackwardTransfers 

Fields

bt_first_in :: BlockId -> a -> a
 
bt_middle_in :: middle -> a -> a
 
bt_last_in :: last -> (BlockId -> a) -> a
 

Instances

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.

Constructors

ForwardRewrites 

Fields

fr_first :: BlockId -> a -> Maybe (AGraph middle last)
 
fr_middle :: middle -> a -> Maybe (AGraph middle last)
 
fr_last :: last -> a -> Maybe (AGraph middle last)
 
fr_exit :: a -> Maybe (AGraph middle last)
 

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.

Constructors

BackwardRewrites 

Fields

br_first :: BlockId -> a -> Maybe (AGraph middle last)
 
br_middle :: middle -> a -> Maybe (AGraph middle last)
 
br_last :: last -> (BlockId -> a) -> Maybe (AGraph middle last)
 
br_exit :: Maybe (AGraph middle last)
 

data ForwardFixedPoint m l fact a Source

A forward problem needs the common fields, plus the facts on the outedges.

Instances

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