Clean up in ifconv a bit.
[libfirm] / ir / opt / cfopt.c
1 /*
2  * Copyright (C) 1995-2008 University of Karlsruhe.  All right reserved.
3  *
4  * This file is part of libFirm.
5  *
6  * This file may be distributed and/or modified under the terms of the
7  * GNU General Public License version 2 as published by the Free Software
8  * Foundation and appearing in the file LICENSE.GPL included in the
9  * packaging of this file.
10  *
11  * Licensees holding valid libFirm Professional Edition licenses may use
12  * this file in accordance with the libFirm Commercial License.
13  * Agreement provided with the Software.
14  *
15  * This file is provided AS IS with NO WARRANTY OF ANY KIND, INCLUDING THE
16  * WARRANTY OF DESIGN, MERCHANTABILITY AND FITNESS FOR A PARTICULAR
17  * PURPOSE.
18  */
19
20 /**
21  * @file
22  * @brief   Control flow optimizations.
23  * @author  Goetz Lindenmaier, Michael Beck, Sebastian Hack
24  * @version $Id$
25  *
26  * Removes Bad control flow predecessors and empty blocks.  A block is empty
27  * if it contains only a Jmp node. Blocks can only be removed if they are not
28  * needed for the semantics of Phi nodes. Further, we NEVER remove labeled
29  * blocks (even if we could move the label).
30  */
31 #include "config.h"
32
33 #include "iroptimize.h"
34
35 #include <assert.h>
36 #include <stdbool.h>
37
38 #include "xmalloc.h"
39 #include "irnode_t.h"
40 #include "irgraph_t.h"
41 #include "irprog_t.h"
42
43 #include "ircons.h"
44 #include "iropt_t.h"
45 #include "irgwalk.h"
46 #include "irgmod.h"
47 #include "irdump.h"
48 #include "irverify.h"
49 #include "iredges.h"
50
51 #include "array_t.h"
52
53 #include "irouts.h"
54 #include "irbackedge_t.h"
55
56 #include "irflag_t.h"
57 #include "firmstat.h"
58 #include "irpass.h"
59
60 #include "iropt_dbg.h"
61
62 /** An environment for merge_blocks and collect nodes. */
63 typedef struct merge_env {
64         bool      changed;      /**< Set if the graph was changed. */
65         bool      phis_moved;   /**< Set if Phi nodes were moved. */
66         ir_node **switch_conds; /**< Helper list for all found Switch Conds. */
67 } merge_env;
68
69 static void set_Block_removable(ir_node *block, bool removable)
70 {
71         set_Block_mark(block, removable);
72 }
73
74 static bool is_Block_removable(ir_node *block)
75 {
76         return get_Block_mark(block);
77 }
78
79 static void clear_link(ir_node *node, void *ctx)
80 {
81         (void) ctx;
82         set_irn_link(node, NULL);
83 }
84
85 /**
86  * Collects all Phi nodes in link list of Block.
87  * Marks all blocks "non_removable" if they contain a node other
88  * than Jmp (and Proj).
89  * Links all Proj nodes to their predecessors.
90  * Collects all switch-Conds in a list.
91  */
92 static void collect_nodes(ir_node *n, void *ctx)
93 {
94         merge_env *env = (merge_env*)ctx;
95
96         if (is_Phi(n)) {
97                 /* Collect Phi nodes to compact ins along with block's ins. */
98                 ir_node *block = get_nodes_block(n);
99                 set_irn_link(n, get_irn_link(block));
100                 set_irn_link(block, n);
101         } else if (is_Block(n)) {
102                 return;
103         } else if (!is_Jmp(n)) {  /* Check for non-empty block. */
104                 ir_node *block = get_nodes_block(n);
105                 set_Block_removable(block, false);
106
107                 if (is_Proj(n)) {
108                         /* link Proj nodes */
109                         ir_node *pred = get_Proj_pred(n);
110                         set_irn_link(n, get_irn_link(pred));
111                         set_irn_link(pred, n);
112                 } else if (is_Cond(n)) {
113                         ir_node *sel = get_Cond_selector(n);
114                         if (get_irn_mode(sel) != mode_b) {
115                                 /* found a switch-Cond, collect */
116                                 ARR_APP1(ir_node*, env->switch_conds, n);
117                         }
118                 }
119         }
120 }
121
122 /** Returns true if pred is predecessor of block. */
123 static bool is_pred_of(ir_node *pred, ir_node *b)
124 {
125         int i;
126
127         for (i = get_Block_n_cfgpreds(b) - 1; i >= 0; --i) {
128                 ir_node *b_pred = get_Block_cfgpred_block(b, i);
129                 if (b_pred == pred)
130                         return true;
131         }
132         return false;
133 }
134
135 /** Test whether we can optimize away pred block pos of b.
136  *
137  *  @param  b    A block node.
138  *  @param  pos  The position of the predecessor block to judge about.
139  *
140  *  @returns     The number of predecessors
141  *
142  *  The test is rather tricky.
143  *
144  *  The situation is something like the following:
145  *  @verbatim
146  *                 if-block
147  *                  /   \
148  *              then-b  else-b
149  *                  \   /
150  *                    b
151  *  @endverbatim
152  *
153  *  b merges the control flow of an if-then-else.  We may not remove
154  *  the 'then' _and_ the 'else' block of an 'if' if there is a Phi
155  *  node in b, even if both are empty.  The destruction of this Phi
156  *  requires that a copy is added before the merge.  We have to
157  *  keep one of the case blocks to place the copies in.
158  *
159  *  To perform the test for pos, we must regard predecessors before pos
160  *  as already removed.
161  **/
162 static unsigned test_whether_dispensable(ir_node *b, int pos)
163 {
164         int i, j, n_preds = 1;
165         ir_node *pred = get_Block_cfgpred_block(b, pos);
166
167         /* Bad blocks will be optimized away, so we don't need space for them */
168         if (is_Bad(pred))
169                 return 0;
170
171         if (is_Block_removable(pred)) {
172                 /* Seems to be empty. At least we detected this in collect_nodes. */
173                 if (get_irn_link(b) == NULL) {
174                         /* There are no Phi nodes ==> all predecessors are dispensable. */
175                         n_preds = get_Block_n_cfgpreds(pred);
176                 } else {
177                         /* b's pred blocks and pred's pred blocks must be pairwise disjunct.
178                            Handle all pred blocks with preds < pos as if they were already removed. */
179                         for (i = 0; i < pos; i++) {
180                                 ir_node *b_pred = get_Block_cfgpred_block(b, i);
181                                 if (! is_Bad(b_pred) && is_Block_removable(b_pred)) {
182                                         for (j = get_Block_n_cfgpreds(b_pred) - 1; j >= 0; --j) {
183                                                 ir_node *b_pred_pred = get_Block_cfgpred_block(b_pred, j);
184                                                 if (is_pred_of(b_pred_pred, pred))
185                                                         goto non_dispensable;
186                                         }
187                                 } else {
188                                         if (is_pred_of(b_pred, pred))
189                                                 goto non_dispensable;
190                                 }
191                         }
192                         for (i = pos +1; i < get_Block_n_cfgpreds(b); i++) {
193                                 ir_node *b_pred = get_Block_cfgpred_block(b, i);
194                                 if (is_pred_of(b_pred, pred))
195                                         goto non_dispensable;
196                         }
197                         /* if we get here, the block is dispensable */
198                         n_preds = get_Block_n_cfgpreds(pred);
199                 }
200         }
201
202         return n_preds;
203
204 non_dispensable:
205         set_Block_removable(pred, false);
206         return 1;
207 }
208
209 /**
210  * This method removed Bad cf predecessors from Blocks and Phis, and removes
211  * empty blocks.  A block is empty if it only contains Phi and Jmp nodes.
212  *
213  * We first adapt Phi nodes, then Block nodes, as we need the old ins
214  * of the Block to adapt the Phi nodes.  We do this by computing new
215  * in arrays, and then replacing the old ones.  So far we compute new in arrays
216  * for all nodes, not regarding whether there is a possibility for optimization.
217  *
218  * For each predecessor p of a Block b there are three cases:
219  *  - The predecessor p is a Bad node: just skip it. The in array of b shrinks
220  *    by one.
221  *  - The predecessor p is empty. Remove p. All predecessors of p are now
222  *    predecessors of b.
223  *  - The predecessor p is a block containing useful code. Just keep p as is.
224  *
225  * For Phi nodes f we have to check the conditions at the Block of f.
226  * For cases 1 and 3 we proceed as for Blocks.  For case 2 we can have two
227  * cases:
228  *  -2a: The old predecessor of the Phi f is a Phi pred_f IN THE BLOCK REMOVED.
229  *       In this case we proceed as for blocks. We remove pred_f.  All
230  *       predecessors of pred_f now are predecessors of f.
231  *  -2b: The old predecessor of f is NOT in the block removed. It might be a Phi
232  *       too. We have to replicate f for each predecessor of the removed block.
233  *       Or, with other words, the removed predecessor block has exactly one
234  *       predecessor.
235  *
236  * Further there is a special case for self referencing blocks:
237  * @verbatim
238  *
239  *    then_b     else_b                              then_b  else_b
240  *       \      /                                      \      /
241  *        \    /                                        |    /
242  *        pred_b                                        |   /
243  *         |   ____                                     |  /  ____
244  *         |  |    |                                    |  | |    |
245  *         |  |    |       === optimized to ===>        \  | |    |
246  *        loop_b   |                                     loop_b   |
247  *         |  |    |                                      |  |    |
248  *         |  |____|                                      |  |____|
249  *         |                                              |
250  * @endverbatim
251  *
252  * If there is a Phi in pred_b, but we remove pred_b, we have to generate a
253  * Phi in loop_b, that has the ins of the Phi in pred_b and a self referencing
254  * backedge.
255  */
256 static void optimize_blocks(ir_node *b, void *ctx)
257 {
258         int i, j, k, n, max_preds, n_preds, p_preds = -1;
259         ir_node *pred, *phi, *next;
260         ir_node **in;
261         merge_env *env = (merge_env*)ctx;
262
263         /* Count the number of predecessor if this block is merged with pred blocks
264            that are empty. */
265         max_preds = 0;
266         for (i = 0, k = get_Block_n_cfgpreds(b); i < k; ++i) {
267                 max_preds += test_whether_dispensable(b, i);
268         }
269         in = XMALLOCN(ir_node*, max_preds);
270
271         /*- Fix the Phi nodes of the current block -*/
272         for (phi = (ir_node*)get_irn_link(b); phi != NULL; phi = (ir_node*)next) {
273                 assert(is_Phi(phi));
274                 next = (ir_node*)get_irn_link(phi);
275
276                 /* Find the new predecessors for the Phi */
277                 p_preds = 0;
278                 for (i = 0, n = get_Block_n_cfgpreds(b); i < n; ++i) {
279                         pred = get_Block_cfgpred_block(b, i);
280
281                         if (is_Bad(pred)) {
282                                 /* case Phi 1: Do nothing */
283                         } else if (is_Block_removable(pred) && !Block_block_visited(pred)) {
284                                 /* case Phi 2: It's an empty block and not yet visited. */
285                                 ir_node *phi_pred = get_Phi_pred(phi, i);
286
287                                 for (j = 0, k = get_Block_n_cfgpreds(pred); j < k; j++) {
288                                         /* because of breaking loops, not all predecessors are
289                                          * Bad-clean, so we must check this here again */
290                                         if (! is_Bad(get_Block_cfgpred(pred, j))) {
291                                                 if (get_nodes_block(phi_pred) == pred) {
292                                                         /* case Phi 2a: */
293                                                         assert(is_Phi(phi_pred));  /* Block is empty!! */
294
295                                                         in[p_preds++] = get_Phi_pred(phi_pred, j);
296                                                 } else {
297                                                         /* case Phi 2b: */
298                                                         in[p_preds++] = phi_pred;
299                                                 }
300                                         }
301                                 }
302                         } else {
303                                 /* case Phi 3: */
304                                 in[p_preds++] = get_Phi_pred(phi, i);
305                         }
306                 }
307                 assert(p_preds <= max_preds);
308
309                 /* Fix the node */
310                 if (p_preds == 1)
311                         /* By removal of Bad ins the Phi might be degenerated. */
312                         exchange(phi, in[0]);
313                 else
314                         set_irn_in(phi, p_preds, in);
315                 env->changed = true;
316         }
317
318         /*- This happens only if merge between loop backedge and single loop entry.
319             Moreover, it is only needed if predb is the direct dominator of b,
320             else there can be no uses of the Phi's in predb ... -*/
321         for (k = 0, n = get_Block_n_cfgpreds(b); k < n; ++k) {
322                 ir_node *predb = get_nodes_block(get_Block_cfgpred(b, k));
323
324                 if (is_Bad(predb))
325                         continue;
326
327                 if (is_Block_removable(predb) && !Block_block_visited(predb)) {
328                         ir_node *next_phi;
329
330                         /* we found a predecessor block at position k that will be removed */
331                         for (phi = (ir_node*)get_irn_link(predb); phi; phi = next_phi) {
332                                 int q_preds = 0;
333                                 next_phi = (ir_node*)get_irn_link(phi);
334
335                                 assert(is_Phi(phi));
336
337                                 if (get_Block_idom(b) != predb) {
338                                         /* predb is not the dominator. There can't be uses of pred's Phi nodes, kill them .*/
339                                         ir_graph *irg = get_irn_irg(b);
340                                         exchange(phi, get_irg_bad(irg));
341                                 } else {
342                                         /* predb is the direct dominator of b. There might be uses of the Phi nodes from
343                                            predb in further block, so move this phi from the predecessor into the block b */
344                                         set_nodes_block(phi, b);
345                                         set_irn_link(phi, get_irn_link(b));
346                                         set_irn_link(b, phi);
347                                         env->phis_moved = true;
348
349                                         /* first, copy all 0..k-1 predecessors */
350                                         for (i = 0; i < k; i++) {
351                                                 pred = get_Block_cfgpred_block(b, i);
352
353                                                 if (is_Bad(pred)) {
354                                                         /* Do nothing */
355                                                 } else if (is_Block_removable(pred) && !Block_block_visited(pred)) {
356                                                         /* It's an empty block and not yet visited. */
357                                                         for (j = 0; j < get_Block_n_cfgpreds(pred); j++) {
358                                                                 if (! is_Bad(get_Block_cfgpred(pred, j)))
359                                                                         in[q_preds++] = phi;
360                                                         }
361                                                 } else {
362                                                         in[q_preds++] = phi;
363                                                 }
364                                         }
365
366                                         /* now we are at k, copy the phi predecessors */
367                                         pred = get_nodes_block(get_Block_cfgpred(b, k));
368                                         for (i = 0; i < get_Phi_n_preds(phi); i++) {
369                                                 if (! is_Bad(get_Block_cfgpred(pred, i)))
370                                                         in[q_preds++] = get_Phi_pred(phi, i);
371                                         }
372
373                                         /* and now all the rest */
374                                         for (i = k+1; i < get_Block_n_cfgpreds(b); i++) {
375                                                 pred = get_Block_cfgpred_block(b, i);
376
377                                                 if (is_Bad(pred)) {
378                                                         /* Do nothing */
379                                                 } else if (is_Block_removable(pred) && !Block_block_visited(pred)) {
380                                                         /* It's an empty block and not yet visited. */
381                                                         for (j = 0; j < get_Block_n_cfgpreds(pred); j++) {
382                                                                 if (! is_Bad(get_Block_cfgpred(pred, j)))
383                                                                         in[q_preds++] = phi;
384                                                         }
385                                                 } else {
386                                                         in[q_preds++] = phi;
387                                                 }
388                                         }
389
390                                         /* Fix the node */
391                                         if (q_preds == 1)
392                                                 exchange(phi, in[0]);
393                                         else
394                                                 set_irn_in(phi, q_preds, in);
395                                         env->changed = true;
396
397                                         assert(q_preds <= max_preds);
398                                         // assert(p_preds == q_preds && "Wrong Phi Fix");
399                                 }
400                         }
401                 }
402         }
403
404         /*- Fix the block -*/
405         n_preds = 0;
406         for (i = 0; i < get_Block_n_cfgpreds(b); i++) {
407                 pred = get_Block_cfgpred_block(b, i);
408
409                 if (is_Bad(pred)) {
410                         /* case 1: Do nothing */
411                 } else if (is_Block_removable(pred) && !Block_block_visited(pred)) {
412                         /* case 2: It's an empty block and not yet visited. */
413                         assert(get_Block_n_cfgpreds(b) > 1 || has_Block_entity(b));
414                         /* Else it should be optimized by equivalent_node. */
415                         for (j = 0; j < get_Block_n_cfgpreds(pred); j++) {
416                                 ir_node *pred_X = get_Block_cfgpred(pred, j);
417
418                                 /* because of breaking loops, not all predecessors are Bad-clean,
419                                  * so we must check this here again */
420                                 if (! is_Bad(pred_X))
421                                         in[n_preds++] = pred_X;
422                         }
423                         /* Remove block as it might be kept alive. */
424                         exchange(pred, b/*get_irg_bad(irg)*/);
425                 } else {
426                         /* case 3: */
427                         in[n_preds++] = get_Block_cfgpred(b, i);
428                 }
429         }
430         assert(n_preds <= max_preds);
431
432         set_irn_in(b, n_preds, in);
433         env->changed = true;
434
435         assert(get_irn_link(b) == NULL || p_preds == -1 || (n_preds == p_preds && "Wrong Phi Fix"));
436         xfree(in);
437 }
438
439 /**
440  * Block walker: optimize all blocks using the default optimizations.
441  * This removes Blocks with only a Jmp predecessor.
442  */
443 static void remove_simple_blocks(ir_node *block, void *ctx)
444 {
445         merge_env *env = (merge_env*)ctx;
446         ir_node   *new_blk = equivalent_node(block);
447
448         if (new_blk != block) {
449                 exchange(block, new_blk);
450                 env->changed = true;
451         }
452 }
453
454 /**
455  * Optimize table-switch Conds.
456  *
457  * @param cond the switch-Cond
458  * @return true if the switch-Cond was optimized
459  */
460 static bool handle_switch_cond(ir_node *cond)
461 {
462         ir_node *sel   = get_Cond_selector(cond);
463         ir_node *proj1 = (ir_node*)get_irn_link(cond);
464         ir_node *proj2 = (ir_node*)get_irn_link(proj1);
465         ir_node *blk   = get_nodes_block(cond);
466
467         /* exactly 1 Proj on the Cond node: must be the defaultProj */
468         if (proj2 == NULL) {
469                 ir_node *jmp = new_r_Jmp(blk);
470                 assert(get_Cond_default_proj(cond) == get_Proj_proj(proj1));
471                 /* convert it into a Jmp */
472                 exchange(proj1, jmp);
473                 return true;
474         }
475
476         /* handle Cond nodes with constant argument. In this case the localopt rules
477          * should have killed all obviously impossible cases.
478          * So the only case left to handle here is 1 defaultProj + 1case
479          * (this one case should be the one taken) */
480         if (get_irn_link(proj2) == NULL) {
481                 ir_tarval *tv = value_of(sel);
482
483                 if (tv != tarval_bad) {
484                         /* we have a constant switch */
485                         long      num     = get_tarval_long(tv);
486                         long      def_num = get_Cond_default_proj(cond);
487                         ir_graph *irg     = get_irn_irg(cond);
488                         ir_node  *bad     = get_irg_bad(irg);
489
490                         if (def_num == get_Proj_proj(proj1)) {
491                                 /* first one is the defProj */
492                                 if (num == get_Proj_proj(proj2)) {
493                                         ir_node *jmp = new_r_Jmp(blk);
494                                         exchange(proj2, jmp);
495                                         exchange(proj1, bad);
496                                         return true;
497                                 }
498                         } else if (def_num == get_Proj_proj(proj2)) {
499                                 /* second one is the defProj */
500                                 if (num == get_Proj_proj(proj1)) {
501                                         ir_node *jmp = new_r_Jmp(blk);
502                                         exchange(proj1, jmp);
503                                         exchange(proj2, bad);
504                                         return true;
505                                 }
506                         } else {
507                                 /* neither: strange, Cond was not optimized so far */
508                                 if (num == get_Proj_proj(proj1)) {
509                                         ir_node *jmp = new_r_Jmp(blk);
510                                         exchange(proj1, jmp);
511                                         exchange(proj2, bad);
512                                         return true;
513                                 } else if (num == get_Proj_proj(proj2)) {
514                                         ir_node *jmp = new_r_Jmp(blk);
515                                         exchange(proj2, jmp);
516                                         exchange(proj1, bad);
517                                         return true;
518                                 }
519                         }
520                 }
521         }
522         return false;
523 }
524
525 /* Optimizations of the control flow that also require changes of Phi nodes.
526  *
527  * This optimization performs two passes over the graph.
528  *
529  * The first pass collects all Phi nodes in a link list in the block
530  * nodes.  Further it performs simple control flow optimizations.
531  * Finally it marks all blocks that do not contain useful
532  * computations, i.e., these blocks might be removed.
533  *
534  * The second pass performs the optimizations intended by this algorithm.
535  * It walks only over block nodes and adapts these and the Phi nodes in these
536  * blocks, which it finds in a linked list computed by the first pass.
537  *
538  * We use the mark flag to mark removable blocks in the first phase.
539  */
540 void optimize_cf(ir_graph *irg)
541 {
542         int i, j, n;
543         ir_node **in = NULL;
544         ir_node *end = get_irg_end(irg);
545         ir_node *new_end;
546         merge_env env;
547
548         assert(get_irg_phase_state(irg) != phase_building);
549
550         /* if the graph is not pinned, we cannot determine empty blocks */
551         assert(get_irg_pinned(irg) != op_pin_state_floats &&
552                "Control flow optimization need a pinned graph");
553
554         /* FIXME: control flow opt destroys block edges. So edges are deactivated
555          * here. Fix the edges! */
556         edges_deactivate(irg);
557
558         /* we use the mark flag to mark removable blocks */
559         ir_reserve_resources(irg, IR_RESOURCE_BLOCK_MARK | IR_RESOURCE_IRN_LINK);
560 restart:
561         env.changed    = false;
562         env.phis_moved = false;
563
564         assure_doms(irg);
565
566         env.switch_conds = NEW_ARR_F(ir_node*, 0);
567         irg_walk(end, clear_link, collect_nodes, &env);
568
569         /* handle all collected switch-Conds */
570         n = ARR_LEN(env.switch_conds);
571         for (i = 0; i < n; ++i) {
572                 ir_node *cond = env.switch_conds[i];
573                 env.changed |= handle_switch_cond(cond);
574         }
575         DEL_ARR_F(env.switch_conds);
576
577         if (env.changed) {
578                 /* Handle graph state if was changed. */
579                 set_irg_outs_inconsistent(irg);
580                 set_irg_doms_inconsistent(irg);
581                 set_irg_extblk_inconsistent(irg);
582                 set_irg_loopinfo_inconsistent(irg);
583                 set_irg_entity_usage_state(irg, ir_entity_usage_not_computed);
584
585                 /* The Cond optimization might generate unreachable code, so restart if
586                    it happens. */
587                 goto restart;
588         }
589
590         /* Optimize the standard code. */
591         assure_doms(irg);
592         irg_block_walk_graph(irg, optimize_blocks, remove_simple_blocks, &env);
593
594         new_end = optimize_in_place(end);
595         if (new_end != end) {
596                 set_irg_end(irg, new_end);
597                 end = new_end;
598         }
599         remove_End_Bads_and_doublets(end);
600
601         ir_free_resources(irg, IR_RESOURCE_BLOCK_MARK | IR_RESOURCE_IRN_LINK);
602
603         if (env.phis_moved) {
604                 /* Bad: when we moved Phi's, we might produce dead Phi nodes
605                    that are kept-alive.
606                    Some other phases cannot copy with this, so will them.
607                  */
608                 n = get_End_n_keepalives(end);
609                 if (n > 0) {
610                         NEW_ARR_A(ir_node *, in, n);
611                         if (env.changed) {
612                                 /* Handle graph state if was changed. */
613                                 set_irg_outs_inconsistent(irg);
614                         }
615                         assure_irg_outs(irg);
616
617                         for (i = j = 0; i < n; ++i) {
618                                 ir_node *ka = get_End_keepalive(end, i);
619
620                                 if (is_Phi(ka)) {
621                                         int k;
622
623                                         for (k = get_irn_n_outs(ka) - 1; k >= 0; --k) {
624                                                 ir_node *user = get_irn_out(ka, k);
625
626                                                 if (user != ka && user != end) {
627                                                         /* Is it a real user or just a self loop ? */
628                                                         break;
629                                                 }
630                                         }
631                                         if (k >= 0)
632                                                 in[j++] = ka;
633                                 } else
634                                         in[j++] = ka;
635                         }
636                         if (j != n) {
637                                 set_End_keepalives(end, j, in);
638                                 env.changed = true;
639                         }
640                 }
641         }
642
643         if (env.changed) {
644                 /* Handle graph state if was changed. */
645                 set_irg_outs_inconsistent(irg);
646                 set_irg_doms_inconsistent(irg);
647                 set_irg_extblk_inconsistent(irg);
648                 set_irg_loopinfo_inconsistent(irg);
649                 set_irg_entity_usage_state(irg, ir_entity_usage_not_computed);
650         }
651
652         /* the verifier doesn't work yet with floating nodes */
653         if (get_irg_pinned(irg) == op_pin_state_pinned) {
654                 /* after optimize_cf(), only Bad data flow may remain. */
655                 if (irg_verify_bads(irg, BAD_DF | BAD_BLOCK | TUPLE)) {
656                         dump_ir_graph(irg, "-verify-cf");
657                         fprintf(stderr, "VERIFY_BAD in optimize_cf()\n");
658                 }
659         }
660 }
661
662 /* Creates an ir_graph pass for optimize_cf. */
663 ir_graph_pass_t *optimize_cf_pass(const char *name)
664 {
665         return def_graph_pass(name ? name : "optimize_cf", optimize_cf);
666 }