ghc-6.10.2: The GHC APIContentsIndex
ZipCfg
Synopsis
data Graph m l = Graph {
g_entry :: ZTail m l
g_blocks :: BlockEnv (Block m l)
}
data LGraph m l = LGraph {
lg_entry :: BlockId
lg_blocks :: BlockEnv (Block m l)
}
data FGraph m l = FGraph {
fg_entry :: BlockId
fg_focus :: ZBlock m l
fg_others :: BlockEnv (Block m l)
}
data Block m l = Block BlockId (ZTail m l)
data ZBlock m l = ZBlock (ZHead m) (ZTail m l)
data ZHead m
= ZFirst BlockId
| ZHead (ZHead m) m
data ZTail m l
= ZLast (ZLast l)
| ZTail m (ZTail m l)
data ZLast l
= LastExit
| LastOther l
insertBlock :: Block m l -> BlockEnv (Block m l) -> BlockEnv (Block m l)
class HavingSuccessors b where
succs :: b -> [BlockId]
fold_succs :: (BlockId -> a -> a) -> b -> a -> a
class HavingSuccessors l => LastNode l where
mkBranchNode :: BlockId -> l
isBranchNode :: l -> Bool
branchNodeTarget :: l -> BlockId
blockId :: Block m l -> BlockId
zip :: ZBlock m l -> Block m l
unzip :: Block m l -> ZBlock m l
last :: ZBlock m l -> ZLast l
goto_end :: ZBlock m l -> (ZHead m, ZLast l)
zipht :: ZHead m -> ZTail m l -> Block m l
tailOfLast :: l -> ZTail m l
splice_tail :: Graph m l -> ZTail m l -> Graph m l
splice_head :: ZHead m -> LGraph m l -> (LGraph m l, ZHead m)
splice_head_only' :: ZHead m -> Graph m l -> LGraph m l
splice_head' :: ZHead m -> Graph m l -> (BlockEnv (Block m l), ZHead m)
of_block_list :: BlockId -> [Block m l] -> LGraph m l
to_block_list :: LGraph m l -> [Block m l]
graphOfLGraph :: LastNode l => LGraph m l -> Graph m l
map_blocks :: (Block m l -> Block m' l') -> LGraph m l -> LGraph m' l'
map_nodes :: (BlockId -> BlockId) -> (m -> m') -> (l -> l') -> LGraph m l -> LGraph m' l'
mapM_blocks :: Monad mm => (Block m l -> mm (Block m' l')) -> LGraph m l -> mm (LGraph m' l')
postorder_dfs :: LastNode l => LGraph m l -> [Block m l]
postorder_dfs_from :: (HavingSuccessors b, LastNode l) => BlockEnv (Block m l) -> b -> [Block m l]
postorder_dfs_from_except :: (HavingSuccessors b, LastNode l) => BlockEnv (Block m l) -> b -> BlockSet -> [Block m l]
fold_layout :: LastNode l => (Block m l -> Maybe BlockId -> a -> a) -> a -> LGraph m l -> a
fold_blocks :: (Block m l -> a -> a) -> a -> LGraph m l -> a
fold_fwd_block :: (BlockId -> a -> a) -> (m -> a -> a) -> (ZLast l -> a -> a) -> Block m l -> a -> a
translate :: Monad tm => (m -> tm (LGraph m' l')) -> (l -> tm (LGraph m' l')) -> LGraph m l -> tm (LGraph m' l')
pprLgraph :: (Outputable m, Outputable l, LastNode l) => LGraph m l -> SDoc
pprGraph :: (Outputable m, Outputable l, LastNode l) => Graph m l -> SDoc
entry :: LGraph m l -> FGraph m l
Documentation
data Graph m l
Constructors
Graph
g_entry :: ZTail m l
g_blocks :: BlockEnv (Block m l)
show/hide Instances
data LGraph m l
Constructors
LGraph
lg_entry :: BlockId
lg_blocks :: BlockEnv (Block m l)
show/hide Instances
data FGraph m l
Constructors
FGraph
fg_entry :: BlockId
fg_focus :: ZBlock m l
fg_others :: BlockEnv (Block m l)
data Block m l
Blocks and flow graphs; see Note [Kinds of graphs]
Constructors
Block BlockId (ZTail m l)
show/hide Instances
data ZBlock m l
And now the zipper. The focus is between the head and tail. We cannot ever focus on an inter-block edge.
Constructors
ZBlock (ZHead m) (ZTail m l)
show/hide Instances
data ZHead m
Constructors
ZFirst BlockId
ZHead (ZHead m) m
data ZTail m l
Constructors
ZLast (ZLast l)
ZTail m (ZTail m l)
show/hide Instances
data ZLast l
A basic block is a first node, followed by zero or more middle nodes, followed by a last node.
Constructors
LastExit
LastOther l
show/hide Instances
insertBlock :: Block m l -> BlockEnv (Block m l) -> BlockEnv (Block m l)
insertBlock should not be used to replace an existing block but only to insert a new one
class HavingSuccessors b where
We can't make a graph out of just any old 'last node' type. A last node has to be able to find its successors, and we need to be able to create and identify unconditional branches. We put these capabilities in a type class. Moreover, the property of having successors is also shared by Blocks and ZTails, so it is useful to have that property in a type class of its own.
Methods
succs :: b -> [BlockId]
fold_succs :: (BlockId -> a -> a) -> b -> a -> a
show/hide Instances
class HavingSuccessors l => LastNode l where
Methods
mkBranchNode :: BlockId -> l
isBranchNode :: l -> Bool
branchNodeTarget
:: l
-> BlockIdN.B. This interface seems to make for more congenial clients than a single function of type 'l -> Maybe BlockId'
show/hide Instances
blockId :: Block m l -> BlockId
zip :: ZBlock m l -> Block m l
unzip :: Block m l -> ZBlock m l
last :: ZBlock m l -> ZLast l
goto_end :: ZBlock m l -> (ZHead m, ZLast l)
zipht :: ZHead m -> ZTail m l -> Block m l
Take a head and tail and go to beginning or end. The asymmetry in the types and names is a bit unfortunate, but 'Block m l' is effectively '(BlockId, ZTail m l)' and is accepted in many more places.
tailOfLast :: l -> ZTail m l
splice_tail :: Graph m l -> ZTail m l -> Graph m l
splice_head :: ZHead m -> LGraph m l -> (LGraph m l, ZHead m)

We can splice a single-entry, single-exit LGraph onto a head or a tail. For a head, we have a head h followed by a LGraph g. The entry node of g gets joined to h, forming the entry into the new LGraph. The exit of g becomes the new head. For both arguments and results, the order of values is the order of control flow: before splicing, the head flows into the LGraph; after splicing, the LGraph flows into the head. Splicing a tail is the dual operation. (In order to maintain the order-means-control-flow convention, the orders are reversed.)

For example, assume head = [L: x:=0] grph = (M, [M: stuff, blocks, N: y:=x; LastExit]) tail = [return (y,x)]

Then splice_head head grph = ((L, [L: x:=0; goto M, M: stuff, blocks]) , N: y:=x)

Then splice_tail grph tail = ( stuff , (???, [blocks, N: y:=x; return (y,x)])

splice_head_only' :: ZHead m -> Graph m l -> LGraph m l
splice_head' :: ZHead m -> Graph m l -> (BlockEnv (Block m l), ZHead m)
of_block_list :: BlockId -> [Block m l] -> LGraph m l

A safe operation

Conversion to and from the environment form is convenient. For layout or dataflow, however, one will want to use postorder_dfs in order to get the blocks in an order that relates to the control flow in the procedure.

to_block_list :: LGraph m l -> [Block m l]
graphOfLGraph :: LastNode l => LGraph m l -> Graph m l
Conversion from LGraph to Graph
map_blocks :: (Block m l -> Block m' l') -> LGraph m l -> LGraph m' l'
map_nodes :: (BlockId -> BlockId) -> (m -> m') -> (l -> l') -> LGraph m l -> LGraph m' l'
mapM_blocks :: Monad mm => (Block m l -> mm (Block m' l')) -> LGraph m l -> mm (LGraph m' l')
postorder_dfs :: LastNode l => LGraph m l -> [Block m l]

Traversal: postorder_dfs returns a list of blocks reachable from the entry node. This list has the following property:

Say a back reference exists if one of a block's control-flow successors precedes it in the output list

Then there are as few back references as possible

The output is suitable for use in a forward dataflow problem. For a backward problem, simply reverse the list. (postorder_dfs is sufficiently tricky to implement that one doesn't want to try and maintain both forward and backward versions.)

postorder_dfs_from :: (HavingSuccessors b, LastNode l) => BlockEnv (Block m l) -> b -> [Block m l]
postorder_dfs_from_except :: (HavingSuccessors b, LastNode l) => BlockEnv (Block m l) -> b -> BlockSet -> [Block m l]

This is the most important traversal over this data structure. It drops unreachable code and puts blocks in an order that is good for solving forward dataflow problems quickly. The reverse order is good for solving backward dataflow problems quickly. The forward order is also reasonably good for emitting instructions, except that it will not usually exploit Forrest Baskett's trick of eliminating the unconditional branch from a loop. For that you would need a more serious analysis, probably based on dominators, to identify loop headers.

The ubiquity of postorder_dfs is one reason for the ubiquity of the LGraph representation, when for most purposes the plain Graph representation is more mathematically elegant (but results in more complicated code).

Here's an easy way to go wrong! Consider A -> [B,C] B -> D C -> D Then ordinary dfs would give [A,B,D,C] which has a back ref from C to D. Better to geot [A,B,C,D]

fold_layout :: LastNode l => (Block m l -> Maybe BlockId -> a -> a) -> a -> LGraph m l -> a

For layout, we fold over pairs of 'Block m l' and 'Maybe BlockId' in layout order. The 'Maybe BlockId', if present, identifies the block that will be the layout successor of the current block. This may be useful to help an emitter omit the final goto of a block that flows directly to its layout successor.

For example: fold_layout f z [ L1:B1, L2:B2, L3:B3 ] = z $ f (L1:B1) (Just L2) $ f (L2:B2) (Just L3) $ f (L3:B3) Nothing where a $ f = f a

fold_blocks :: (Block m l -> a -> a) -> a -> LGraph m l -> a
We can also fold over blocks in an unspecified order. The ZipCfgExtras module provides a monadic version, which we haven't needed (else it would be here).
fold_fwd_block :: (BlockId -> a -> a) -> (m -> a -> a) -> (ZLast l -> a -> a) -> Block m l -> a -> a
Fold from first to last
translate :: Monad tm => (m -> tm (LGraph m' l')) -> (l -> tm (LGraph m' l')) -> LGraph m l -> tm (LGraph m' l')
These translation functions are speculative. I hope eventually they will be used in the native-code back ends ---NR
pprLgraph :: (Outputable m, Outputable l, LastNode l) => LGraph m l -> SDoc
pprGraph :: (Outputable m, Outputable l, LastNode l) => Graph m l -> SDoc
entry :: LGraph m l -> FGraph m l
Produced by Haddock version 2.4.2