- data AGraph m l
- (<*>) :: AGraph m l -> AGraph m l -> AGraph m l
- catAGraphs :: [AGraph m l] -> AGraph m l
- freshBlockId :: MonadUnique m => String -> m BlockId
- emptyAGraph :: AGraph m l
- withFreshLabel :: String -> (BlockId -> AGraph m l) -> AGraph m l
- withUnique :: (Unique -> AGraph m l) -> AGraph m l
- mkMiddle :: m -> AGraph m l
- mkMiddles :: [m] -> AGraph m l
- mkLast :: (Outputable m, Outputable l, LastNode l) => l -> AGraph m l
- mkZTail :: (Outputable m, Outputable l, LastNode l) => ZTail m l -> AGraph m l
- mkBranch :: (Outputable m, Outputable l, LastNode l) => BlockId -> AGraph m l
- mkLabel :: LastNode l => BlockId -> AGraph m l
- mkIfThenElse :: (Outputable m, Outputable l, LastNode l) => (BlockId -> BlockId -> AGraph m l) -> AGraph m l -> AGraph m l -> AGraph m l
- mkWhileDo :: (Outputable m, Outputable l, LastNode l) => (BlockId -> BlockId -> AGraph m l) -> AGraph m l -> AGraph m l
- outOfLine :: (LastNode l, Outputable m, Outputable l) => AGraph m l -> AGraph m l
- emptyGraph :: Graph m l
- graphOfMiddles :: [m] -> Graph m l
- graphOfZTail :: ZTail m l -> Graph m l
- lgraphOfAGraph :: AGraph m l -> UniqSM (LGraph m l)
- graphOfAGraph :: AGraph m l -> UniqSM (Graph m l)
- labelAGraph :: BlockId -> AGraph m l -> UniqSM (LGraph m l)
- pprAGraph :: (Outputable m, LastNode l, Outputable l) => AGraph m l -> UniqSM SDoc
Documentation
catAGraphs :: [AGraph m l] -> AGraph m lSource
freshBlockId :: MonadUnique m => String -> m BlockIdSource
The string argument to freshBlockId
was originally helpful in debugging
the Quick C-- compiler, so I have kept it here even though at present it is
thrown away at this spot---there's no reason a BlockId couldn't one day carry
a string.
emptyAGraph :: AGraph m lSource
A graph is built up by splicing together graphs each containing a
single node (where a label is considered a first
node. The empty
graph is a left and right unit for splicing. All of the AGraph
constructors (even complex ones like mkIfThenElse
, as well as the
splicing operation *, are constant-time operations.
withFreshLabel :: String -> (BlockId -> AGraph m l) -> AGraph m lSource
This function provides access to fresh labels without requiring clients to be programmed monadically.
withUnique :: (Unique -> AGraph m l) -> AGraph m lSource
mkLast :: (Outputable m, Outputable l, LastNode l) => l -> AGraph m lSource
mkZTail :: (Outputable m, Outputable l, LastNode l) => ZTail m l -> AGraph m lSource
mkBranch :: (Outputable m, Outputable l, LastNode l) => BlockId -> AGraph m lSource
mkIfThenElse :: (Outputable m, Outputable l, LastNode l) => (BlockId -> BlockId -> AGraph m l) -> AGraph m l -> AGraph m l -> AGraph m lSource
mkWhileDo :: (Outputable m, Outputable l, LastNode l) => (BlockId -> BlockId -> AGraph m l) -> AGraph m l -> AGraph m lSource
outOfLine :: (LastNode l, Outputable m, Outputable l) => AGraph m l -> AGraph m lSource
The argument is an AGraph that has an empty entry sequence and no exit sequence. The result is a new AGraph that has an empty entry sequence connected to an empty exit sequence, with the original graph sitting to the side out-of-line.
Example: mkMiddle (x = 3) * outOfLine (mkLabel L * ...stuff...) * mkMiddle (y = x) Control will flow directly from x=3 to y=x; the block starting with L is on the side.
N.B. algebraically forall g g' : g * outOfLine g' == outOfLine g' * g
emptyGraph :: Graph m lSource
The functions below build Graphs directly; for convenience, they are included here with the rest of the constructor functions.
graphOfMiddles :: [m] -> Graph m lSource
graphOfZTail :: ZTail m l -> Graph m lSource
graphOfAGraph :: AGraph m l -> UniqSM (Graph m l)Source
Converting an abstract graph to a concrete form is expensive: the cost is linear in the number of nodes in the answer, plus N log N in the number of basic blocks. The conversion is also monadic because it may require the allocation of fresh, unique labels.
pprAGraph :: (Outputable m, LastNode l, Outputable l) => AGraph m l -> UniqSM SDocSource