SCM Repository
Annotation of /sml/trunk/src/MLRISC/flowgraph/cfg.sml
Parent Directory
|
Revision Log
Revision 1118 - (view) (download)
1 : | jhr | 1104 | (* cfg.sml |
2 : | * | ||
3 : | * COPYRIGHT (c) 2002 Bell Labs, Lucent Technologies | ||
4 : | * | ||
5 : | george | 906 | * The control flow graph representation used for optimizations. |
6 : | * | ||
7 : | * -- Allen | ||
8 : | *) | ||
9 : | jhr | 1104 | |
10 : | george | 906 | functor ControlFlowGraph |
11 : | george | 984 | (structure I : INSTRUCTIONS |
12 : | george | 906 | structure GraphImpl : GRAPH_IMPLEMENTATION |
13 : | jhr | 1084 | structure InsnProps : INSN_PROPERTIES where I = I |
14 : | george | 984 | structure Asm : INSTRUCTION_EMITTER where I = I |
15 : | george | 906 | ) : CONTROL_FLOW_GRAPH = |
16 : | struct | ||
17 : | |||
18 : | structure I = I | ||
19 : | george | 984 | structure P = Asm.S.P |
20 : | george | 906 | structure C = I.C |
21 : | structure W = Freq | ||
22 : | structure G = Graph | ||
23 : | structure A = Annotations | ||
24 : | structure S = Asm.S | ||
25 : | |||
26 : | type weight = W.freq | ||
27 : | |||
28 : | datatype block_kind = | ||
29 : | START (* entry node *) | ||
30 : | | STOP (* exit node *) | ||
31 : | | NORMAL (* normal node *) | ||
32 : | |||
33 : | george | 984 | and block = |
34 : | george | 906 | BLOCK of |
35 : | { id : int, (* block id *) | ||
36 : | kind : block_kind, (* block kind *) | ||
37 : | freq : weight ref, (* execution frequency *) | ||
38 : | labels : Label.label list ref, (* labels on blocks *) | ||
39 : | insns : I.instruction list ref, (* in rev order *) | ||
40 : | george | 984 | align : P.pseudo_op option ref, (* alignment only *) |
41 : | george | 906 | annotations : Annotations.annotations ref (* annotations *) |
42 : | } | ||
43 : | |||
44 : | jhr | 1084 | and edge_kind (* edge kinds (see cfg.sig for more info) *) |
45 : | = ENTRY (* entry edge *) | ||
46 : | | EXIT (* exit edge *) | ||
47 : | | JUMP (* unconditional jump *) | ||
48 : | | FALLSTHRU (* falls through to next block *) | ||
49 : | | BRANCH of bool (* branch *) | ||
50 : | | SWITCH of int (* computed goto *) | ||
51 : | | FLOWSTO (* FLOW_TO edge *) | ||
52 : | george | 906 | |
53 : | jhr | 1084 | and edge_info = EDGE of { |
54 : | k : edge_kind, (* edge kind *) | ||
55 : | w : weight ref, (* edge freq *) | ||
56 : | a : Annotations.annotations ref (* annotations *) | ||
57 : | } | ||
58 : | george | 906 | |
59 : | type edge = edge_info Graph.edge | ||
60 : | type node = block Graph.node | ||
61 : | |||
62 : | datatype info = | ||
63 : | INFO of { annotations : Annotations.annotations ref, | ||
64 : | firstBlock : int ref, | ||
65 : | george | 984 | reorder : bool ref, |
66 : | data : P.pseudo_op list ref | ||
67 : | george | 906 | } |
68 : | |||
69 : | type cfg = (block,edge_info,info) Graph.graph | ||
70 : | |||
71 : | fun error msg = MLRiscErrorMsg.error("ControlFlowGraph",msg) | ||
72 : | |||
73 : | (*======================================================================== | ||
74 : | * | ||
75 : | * Various kinds of annotations | ||
76 : | * | ||
77 : | *========================================================================*) | ||
78 : | (* escaping live out information *) | ||
79 : | val LIVEOUT = Annotations.new | ||
80 : | (SOME(fn c => "Liveout: "^ | ||
81 : | (LineBreak.lineBreak 75 | ||
82 : | (CellsBasis.CellSet.toString c)))) | ||
83 : | exception Changed of string * (unit -> unit) | ||
84 : | val CHANGED = Annotations.new' | ||
85 : | {create=Changed, | ||
86 : | get=fn Changed x => x | e => raise e, | ||
87 : | toString=fn (name,_) => "CHANGED:"^name | ||
88 : | } | ||
89 : | |||
90 : | (*======================================================================== | ||
91 : | * | ||
92 : | * Methods for manipulating basic blocks | ||
93 : | * | ||
94 : | *========================================================================*) | ||
95 : | fun defineLabel(BLOCK{labels=ref(l::_),...}) = l | ||
96 : | george | 984 | | defineLabel(BLOCK{labels, ...}) = let |
97 : | george | 906 | val l = Label.anon () |
98 : | in | ||
99 : | labels := [l]; | ||
100 : | l | ||
101 : | end | ||
102 : | fun insns(BLOCK{insns, ...}) = insns | ||
103 : | fun freq(BLOCK{freq, ...}) = freq | ||
104 : | |||
105 : | fun newBlock'(id,kind,insns,freq) = | ||
106 : | BLOCK{ id = id, | ||
107 : | kind = kind, | ||
108 : | freq = freq, | ||
109 : | labels = ref [], | ||
110 : | insns = ref insns, | ||
111 : | george | 984 | align = ref NONE, |
112 : | george | 906 | annotations = ref [] |
113 : | } | ||
114 : | |||
115 : | george | 984 | fun copyBlock(id,BLOCK{kind,freq,align,labels,insns,annotations,...}) = |
116 : | george | 906 | BLOCK{ id = id, |
117 : | kind = kind, | ||
118 : | freq = ref (!freq), | ||
119 : | labels = ref [], | ||
120 : | george | 984 | align = ref (!align), |
121 : | george | 906 | insns = ref (!insns), |
122 : | annotations = ref (!annotations) | ||
123 : | } | ||
124 : | |||
125 : | fun newBlock(id,freq) = newBlock'(id,NORMAL,[],freq) | ||
126 : | fun newStart(id,freq) = newBlock'(id,START,[],freq) | ||
127 : | fun newStop(id,freq) = newBlock'(id,STOP,[],freq) | ||
128 : | |||
129 : | fun branchOf(EDGE{k=BRANCH b,...}) = SOME b | ||
130 : | | branchOf _ = NONE | ||
131 : | fun edgeDir(_,_,e) = branchOf e | ||
132 : | |||
133 : | (*======================================================================== | ||
134 : | * | ||
135 : | * Emit a basic block | ||
136 : | * | ||
137 : | *========================================================================*) | ||
138 : | fun kindName START = "START" | ||
139 : | | kindName STOP = "STOP" | ||
140 : | | kindName NORMAL = "Block" | ||
141 : | |||
142 : | fun nl() = TextIO.output(!AsmStream.asmOutStream,"\n") | ||
143 : | |||
144 : | fun emitHeader (S.STREAM{comment,annotation,...}) | ||
145 : | (BLOCK{id,kind,freq,annotations,...}) = | ||
146 : | (comment(kindName kind ^"["^Int.toString id^ | ||
147 : | "] ("^W.toString (!freq)^")"); | ||
148 : | nl(); | ||
149 : | app annotation (!annotations) | ||
150 : | ) | ||
151 : | |||
152 : | fun emitFooter (S.STREAM{comment,...}) (BLOCK{annotations,...}) = | ||
153 : | (case #get LIVEOUT (!annotations) of | ||
154 : | SOME s => | ||
155 : | let val regs = String.tokens Char.isSpace(CellsBasis.CellSet.toString s) | ||
156 : | val K = 7 | ||
157 : | fun f(_,[],s,l) = s::l | ||
158 : | | f(0,vs,s,l) = f(K,vs," ",s::l) | ||
159 : | | f(n,[v],s,l) = v^s::l | ||
160 : | | f(n,v::vs,s,l) = f(n-1,vs,s^" "^v,l) | ||
161 : | val text = rev(f(K,regs,"",[])) | ||
162 : | in app (fn c => (comment c; nl())) text | ||
163 : | end | ||
164 : | | NONE => () | ||
165 : | ) handle Overflow => print("Bad footer\n") | ||
166 : | |||
167 : | fun emitStuff outline annotations | ||
168 : | george | 984 | (block as BLOCK{insns,labels,...}) = |
169 : | george | 906 | let val S as S.STREAM{pseudoOp,defineLabel,emit,...} = |
170 : | Asm.makeStream annotations | ||
171 : | in emitHeader S block; | ||
172 : | george | 959 | app defineLabel (!labels); |
173 : | george | 906 | if outline then () else app emit (rev (!insns)); |
174 : | emitFooter S block | ||
175 : | end | ||
176 : | |||
177 : | val emit = emitStuff false | ||
178 : | val emitOutline = emitStuff true [] | ||
179 : | |||
180 : | (*======================================================================== | ||
181 : | * | ||
182 : | * Methods for manipulating CFG | ||
183 : | * | ||
184 : | *========================================================================*) | ||
185 : | fun cfg info = GraphImpl.graph("CFG",info,10) | ||
186 : | fun new() = | ||
187 : | let val info = INFO{ annotations = ref [], | ||
188 : | firstBlock = ref 0, | ||
189 : | george | 984 | reorder = ref false, |
190 : | data = ref [] | ||
191 : | george | 906 | } |
192 : | in cfg info end | ||
193 : | |||
194 : | fun subgraph(CFG as G.GRAPH{graph_info=INFO graph_info,...}) = | ||
195 : | let val info = INFO{ annotations = ref [], | ||
196 : | firstBlock = #firstBlock graph_info, | ||
197 : | george | 984 | reorder = #reorder graph_info, |
198 : | data = #data graph_info | ||
199 : | george | 906 | } |
200 : | in UpdateGraphInfo.update CFG info end | ||
201 : | |||
202 : | fun init(G.GRAPH cfg) = | ||
203 : | (case #entries cfg () of | ||
204 : | [] => | ||
205 : | let val i = #new_id cfg () | ||
206 : | val start = newStart(i,ref 0) | ||
207 : | val _ = #add_node cfg (i,start) | ||
208 : | val j = #new_id cfg () | ||
209 : | val stop = newStop(j,ref 0) | ||
210 : | val _ = #add_node cfg (j,stop) | ||
211 : | in (* #add_edge cfg (i,j,EDGE{k=ENTRY,w=ref 0,a=ref []}); *) | ||
212 : | #set_entries cfg [i]; | ||
213 : | #set_exits cfg [j] | ||
214 : | end | ||
215 : | | _ => () | ||
216 : | ) | ||
217 : | |||
218 : | fun changed(G.GRAPH{graph_info=INFO{reorder,annotations,...},...}) = | ||
219 : | let fun signal [] = () | ||
220 : | | signal(Changed(_,f)::an) = (f (); signal an) | ||
221 : | | signal(_::an) = signal an | ||
222 : | in signal(!annotations); | ||
223 : | reorder := true | ||
224 : | end | ||
225 : | |||
226 : | fun annotations(G.GRAPH{graph_info=INFO{annotations=a,...},...}) = a | ||
227 : | |||
228 : | fun liveOut (BLOCK{annotations, ...}) = | ||
229 : | case #get LIVEOUT (!annotations) of | ||
230 : | SOME s => s | ||
231 : | | NONE => C.empty | ||
232 : | fun fallsThruFrom(G.GRAPH cfg,b) = | ||
233 : | let fun f [] = NONE | ||
234 : | | f((i,_,EDGE{k=BRANCH false,...})::_) = SOME i | ||
235 : | | f((i,_,EDGE{k=FALLSTHRU,...})::_) = SOME i | ||
236 : | | f(_::es) = f es | ||
237 : | in f(#in_edges cfg b) | ||
238 : | end | ||
239 : | fun fallsThruTo(G.GRAPH cfg,b) = | ||
240 : | let fun f [] = NONE | ||
241 : | | f((_,j,EDGE{k=BRANCH false,...})::_) = SOME j | ||
242 : | | f((_,j,EDGE{k=FALLSTHRU,...})::_) = SOME j | ||
243 : | | f(_::es) = f es | ||
244 : | in f(#out_edges cfg b) | ||
245 : | end | ||
246 : | fun removeEdge CFG (i,j,EDGE{a,...}) = | ||
247 : | Graph.remove_edge' CFG (i,j,fn EDGE{a=a',...} => a = a') | ||
248 : | |||
249 : | fun setBranch (CFG as G.GRAPH cfg,b,cond) = | ||
250 : | let fun loop((i,j,EDGE{k=BRANCH cond',w,a})::es,es',x,y) = | ||
251 : | if cond' = cond then | ||
252 : | loop(es, (i,j,EDGE{k=JUMP,w=w,a=a})::es',j,y) | ||
253 : | else | ||
254 : | loop(es, es', x, j) | ||
255 : | | loop([],es',target,elim) = (es',target,elim) | ||
256 : | | loop _ = error "setBranch" | ||
257 : | val outEdges = #out_edges cfg b | ||
258 : | val (outEdges',target,elim) = loop(outEdges,[],~1,~1) | ||
259 : | val _ = if elim < 0 then error "setBranch: bad edges" else (); | ||
260 : | val lab = defineLabel(#node_info cfg target) | ||
261 : | val jmp = InsnProps.jump lab | ||
262 : | val insns = insns(#node_info cfg b) | ||
263 : | in #set_out_edges cfg (b,outEdges'); | ||
264 : | case !insns of | ||
265 : | [] => error "setBranch: missing branch" | ||
266 : | | branch::rest => | ||
267 : | case InsnProps.instrKind branch of | ||
268 : | InsnProps.IK_JUMP => insns := jmp::rest | ||
269 : | | _ => error "setBranch: bad branch instruction"; | ||
270 : | jmp | ||
271 : | end | ||
272 : | |||
273 : | (*======================================================================== | ||
274 : | * | ||
275 : | * Miscellaneous | ||
276 : | * | ||
277 : | *========================================================================*) | ||
278 : | fun cdgEdge(EDGE{k, ...}) = | ||
279 : | case k of | ||
280 : | (JUMP | FALLSTHRU) => false | ||
281 : | | _ => true | ||
282 : | |||
283 : | (*======================================================================== | ||
284 : | * | ||
285 : | * Pretty Printing and Viewing | ||
286 : | * | ||
287 : | *========================================================================*) | ||
288 : | |||
289 : | jhr | 1104 | structure F = Format |
290 : | george | 906 | |
291 : | jhr | 1104 | fun show_edge (EDGE{k,w,a,...}) = let |
292 : | val kind = (case k | ||
293 : | of JUMP => "jump" | ||
294 : | | FALLSTHRU => "fallsthru" | ||
295 : | | BRANCH b => Bool.toString b | ||
296 : | | SWITCH i => Int.toString i | ||
297 : | | ENTRY => "entry" | ||
298 : | | EXIT => "exit" | ||
299 : | | FLOWSTO => "flowsto" | ||
300 : | (* end case *)) | ||
301 : | in | ||
302 : | F.format "%s(%d)" [F.STR kind, F.INT(!w)] | ||
303 : | end | ||
304 : | |||
305 : | fun getString f x = let | ||
306 : | val buffer = StringOutStream.mkStreamBuf() | ||
307 : | val S = StringOutStream.openStringOut buffer | ||
308 : | val _ = AsmStream.withStream S f x | ||
309 : | in | ||
310 : | StringOutStream.getString buffer | ||
311 : | end | ||
312 : | |||
313 : | fun show_block an block = let | ||
314 : | val text = getString (emit an) block | ||
315 : | in | ||
316 : | foldr (fn (x,"") => x | (x,y) => x^" "^y) "" | ||
317 : | (String.tokens (fn #" " => true | _ => false) text) | ||
318 : | end | ||
319 : | |||
320 : | jhr | 1118 | fun dumpBlock (outS, cfg as G.GRAPH g) = let |
321 : | jhr | 1104 | fun pr str = TextIO.output(outS, str) |
322 : | fun prList [] = () | ||
323 : | | prList [i] = pr i | ||
324 : | | prList (h::t) = (pr (h ^ ", "); prList t) | ||
325 : | jhr | 1118 | val Asm.S.STREAM{emit,defineLabel,annotation,...} = |
326 : | AsmStream.withStream outS Asm.makeStream [] | ||
327 : | fun showFreq (ref w) = F.format "[%s]" [F.STR(W.toString w)] | ||
328 : | jhr | 1104 | fun showEdge (blknum,e) = |
329 : | F.format "%d:%s" [F.INT blknum, F.STR(show_edge e)] | ||
330 : | fun showSucc (_, x, e) = showEdge(x,e) | ||
331 : | fun showPred (x, _, e) = showEdge(x,e) | ||
332 : | fun showSuccs b = ( | ||
333 : | pr "\tsucc: "; | ||
334 : | prList (map showSucc (#out_edges g b)); | ||
335 : | pr "\n") | ||
336 : | fun showPreds b = ( | ||
337 : | pr "\tpred: "; | ||
338 : | prList (map showPred (#in_edges g b)); | ||
339 : | pr "\n") | ||
340 : | fun printBlock (_, BLOCK{kind=START, id, freq, ...}) = ( | ||
341 : | pr (F.format "ENTRY %d %s\n" [F.INT id, F.STR(showFreq freq)]); | ||
342 : | showSuccs id) | ||
343 : | | printBlock (_, BLOCK{kind=STOP, id, freq, ...}) = ( | ||
344 : | pr (F.format "EXIT %d %s\n" [F.INT id, F.STR(showFreq freq)]); | ||
345 : | showPreds id) | ||
346 : | | printBlock ( | ||
347 : | _, BLOCK{id, align, freq, insns, annotations, labels, ...} | ||
348 : | ) = ( | ||
349 : | pr (F.format "BLOCK %d %s\n" [F.INT id, F.STR(showFreq freq)]); | ||
350 : | case !align of NONE => () | SOME p => (pr (P.toString p ^ "\n")); | ||
351 : | jhr | 1118 | List.app annotation (!annotations); |
352 : | List.app defineLabel (!labels); | ||
353 : | jhr | 1104 | showSuccs id; |
354 : | showPreds id; | ||
355 : | List.app emit (List.rev (!insns))) | ||
356 : | jhr | 1118 | in |
357 : | printBlock | ||
358 : | end | ||
359 : | |||
360 : | fun dump (outS, title, cfg as G.GRAPH g) = let | ||
361 : | fun pr str = TextIO.output(outS, str) | ||
362 : | val annotations = !(annotations cfg) | ||
363 : | val Asm.S.STREAM{annotation, ...} = | ||
364 : | AsmStream.withStream outS Asm.makeStream annotations | ||
365 : | jhr | 1104 | fun printData () = let |
366 : | val INFO{data, ...} = #graph_info g | ||
367 : | in | ||
368 : | List.app (pr o P.toString) (rev(!data)) | ||
369 : | end | ||
370 : | in | ||
371 : | pr(F.format "[ %s ]\n" [F.STR title]); | ||
372 : | List.app annotation annotations; | ||
373 : | (* printBlock entry; *) | ||
374 : | jhr | 1118 | AsmStream.withStream outS (#forall_nodes g) (dumpBlock (outS, cfg)); |
375 : | jhr | 1104 | (* printBlock exit; *) |
376 : | AsmStream.withStream outS printData (); | ||
377 : | TextIO.flushOut outS | ||
378 : | end | ||
379 : | |||
380 : | george | 906 | end |
381 : |
root@smlnj-gforge.cs.uchicago.edu | ViewVC Help |
Powered by ViewVC 1.0.0 |