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