forgot to check for dead blocks in 1 case
[libfirm] / ir / ana / irconsconfirm.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    Construction of Confirm nodes
23  * @author   Michael Beck
24  * @date     6.2005
25  * @version  $Id$
26  */
27 #include "config.h"
28
29 #include "irgraph_t.h"
30 #include "irnode_t.h"
31 #include "ircons_t.h"
32 #include "irgmod.h"
33 #include "iropt_dbg.h"
34 #include "iredges_t.h"
35 #include "irgwalk.h"
36 #include "irprintf.h"
37 #include "irgopt.h"
38 #include "irpass.h"
39 #include "irtools.h"
40 #include "array_t.h"
41 #include "debug.h"
42 #include "irflag.h"
43
44 /**
45  * Walker environment.
46  */
47 typedef struct _env_t {
48         unsigned num_confirms;  /**< Number of inserted Confirm nodes. */
49         unsigned num_consts;    /**< Number of constants placed. */
50         unsigned num_eq;        /**< Number of equalities placed. */
51         unsigned num_non_null;  /**< Number of non-null Confirms. */
52 } env_t;
53
54 /** The debug handle. */
55 DEBUG_ONLY(static firm_dbg_module_t *dbg;)
56
57 /**
58  * Return the effective use block of a node and it's predecessor on
59  * position pos.
60  *
61  * @param node  the node
62  * @param pos   the position of the used input
63  *
64  * This handles correctly Phi nodes.
65  */
66 static ir_node *get_effective_use_block(ir_node *node, int pos)
67 {
68         if (is_Phi(node)) {
69                 /* the effective use of a Phi argument is in its predecessor block */
70                 node = get_nodes_block(node);
71                 return get_Block_cfgpred_block(node, pos);
72         }
73         return get_nodes_block(node);
74 }
75
76 /**
77  * Handle a CASE-branch.
78  *
79  * @param block   the block which is entered by the branch
80  * @param irn     the node expressing the switch value
81  * @param nr      the branch label
82  * @param env     statistical environment
83  *
84  * Branch labels are a simple case. We can replace the value
85  * by a Const with the branch label.
86  */
87 static void handle_case(ir_node *block, ir_node *irn, long nr, env_t *env)
88 {
89         const ir_edge_t *edge, *next;
90         ir_node *c = NULL;
91
92         if (is_Bad(irn))
93                 return;
94
95         for (edge = get_irn_out_edge_first(irn); edge; edge = next) {
96                 ir_node *succ = get_edge_src_irn(edge);
97                 int     pos   = get_edge_src_pos(edge);
98                 ir_node *blk  = get_effective_use_block(succ, pos);
99
100                 next = get_irn_out_edge_next(irn, edge);
101
102                 if (block_dominates(block, blk)) {
103                         /*
104                          * Ok, we found a user of irn that is placed
105                          * in a block dominated by the branch block.
106                          * We can replace the input with the Constant
107                          * branch label.
108                          */
109
110                         if (! c) {
111                                 ir_mode *mode = get_irn_mode(irn);
112                                 ir_type *tp   = get_irn_type(irn);
113                                 tarval *tv    = new_tarval_from_long(nr, mode);
114                                 c = new_r_Const_type(current_ir_graph, tv, tp);
115                         }
116
117                         set_irn_n(succ, pos, c);
118                         DBG_OPT_CONFIRM_C(irn, c);
119                         DB((dbg, LEVEL_2, "Replacing input %d of node %+F with %+F\n", pos, succ, c));
120
121                         env->num_consts += 1;
122                 }
123         }
124 }  /* handle_case */
125
126 /**
127  * Handle a mode_b input of Cond nodes.
128  *
129  * @param block     the block which is entered by the branch
130  * @param selector  the mode_b node expressing the branch condition
131  * @param pnc       the true/false condition branch
132  * @param env       statistical environment
133  */
134 static void handle_modeb(ir_node *block, ir_node *selector, pn_Cond pnc, env_t *env)
135 {
136         ir_node *cond, *old, *cond_block = NULL, *other_blk = NULL, *con = NULL;
137         ir_node *c_b = NULL, *c_o = NULL;
138         const ir_edge_t *edge, *next;
139
140         for (edge = get_irn_out_edge_first(selector); edge; edge = next) {
141                 ir_node *user     = get_edge_src_irn(edge);
142                 int     pos       = get_edge_src_pos(edge);
143                 ir_node *user_blk = get_effective_use_block(user, pos);
144
145                 next = get_irn_out_edge_next(selector, edge);
146                 if (block_dominates(block, user_blk)) {
147                         /*
148                          * Ok, we found a usage of selector in a block
149                          * dominated by the branch block.
150                          * We can replace the input with true/false.
151                          */
152                         if (con == NULL) {
153                                 con = new_Const(pnc == pn_Cond_true ? tarval_b_true : tarval_b_false);
154                         }
155                         old = get_irn_n(user, pos);
156                         set_irn_n(user, pos, con);
157                         DBG_OPT_CONFIRM_C(old, con);
158
159                         DB((dbg, LEVEL_2, "Replacing input %d of node %+F with %+F\n", pos, user, con));
160
161                         env->num_consts += 1;
162                 } else {
163                         int i, n;
164
165                         /* get the other block */
166                         if (other_blk == NULL) {
167                                 /* we have already tested, that block has only ONE Cond predecessor */
168                                 cond = get_Proj_pred(get_Block_cfgpred(block, 0));
169                                 cond_block = get_nodes_block(cond);
170                                 foreach_out_edge(cond, edge) {
171                                         ir_node *proj = get_edge_src_irn(edge);
172                                         if (get_Proj_proj(proj) == (long)pnc)
173                                                 continue;
174                                         edge = get_irn_out_edge_first(proj);
175                                         other_blk = get_edge_src_irn(edge);
176                                         break;
177                                 }
178                                 assert(other_blk);
179
180                                 /*
181                                  * Note the special case here: if block is a then, there might be no else
182                                  * block. In that case the other_block is the user_blk itself and pred_block
183                                  * is the cond_block ...
184                                  *
185                                  * Best would be to introduce a block here, removing this critical edge.
186                                  * For some reasons I cannot repair dominance here, so I have to remove
187                                  * ALL critical edges...
188                                  * FIXME: This should not be needed if we could repair dominance ...
189                                  */
190                         }
191
192                         n = get_Block_n_cfgpreds(user_blk);
193
194                         /*
195                          * We have found a user in a non-dominated block:
196                          * check, if all its block predecessors are dominated.
197                          * If yes, place a Phi.
198                          */
199                         for (i = n - 1; i >= 0; --i) {
200                                 ir_node *pred_blk = get_Block_cfgpred_block(user_blk, i);
201
202                                 if (!block_dominates(block, pred_blk) &&
203                                     !block_dominates(other_blk, pred_blk)) {
204                                         /* can't do anything */
205                                         break;
206                                 }
207                         }
208                         if (i < 0) {
209                                 ir_node *phi, **in;
210
211                                 NEW_ARR_A(ir_node *, in, n);
212                                 /* ok, ALL predecessors are either dominated by block OR other block */
213                                 if (c_b == NULL) {
214                                         ir_node *c_true  = new_Const(tarval_b_true);
215                                         ir_node *c_false = new_Const(tarval_b_false);
216                                         if (pnc == pn_Cond_true) {
217                                                 c_b = c_true;
218                                                 c_o = c_false;
219                                         } else {
220                                                 c_b = c_false;
221                                                 c_o = c_true;
222                                         }
223                                 }
224                                 for (i = n - 1; i >= 0; --i) {
225                                         ir_node *pred_blk = get_Block_cfgpred_block(user_blk, i);
226
227                                         if (block_dominates(block, pred_blk))
228                                                 in[i] = c_b;
229                                         else
230                                                 in[i] = c_o;
231                                 }
232                                 phi = new_r_Phi(user_blk, n, in, mode_b);
233                                 set_irn_n(user, pos, phi);
234                         }
235                 }
236         }
237 }
238
239 /**
240  * Handle an IF-branch.
241  *
242  * @param block   the block which is entered by the branch
243  * @param cmp     the Cmp node expressing the branch condition
244  * @param pnc     the Compare relation for taking this branch
245  * @param env     statistical environment
246  */
247 static void handle_if(ir_node *block, ir_node *cmp, pn_Cmp pnc, env_t *env)
248 {
249         ir_node *left  = get_Cmp_left(cmp);
250         ir_node *right = get_Cmp_right(cmp);
251         ir_node *cond_block;
252         ir_op *op;
253         const ir_edge_t *edge, *next;
254
255         /* Beware of Bads */
256         if (is_Bad(left) || is_Bad(right))
257                 return;
258
259         op = get_irn_op(left);
260
261         /* Do not create Confirm nodes for Cmp(Const, Const) constructs.
262            These are removed anyway */
263         if (op == op_Const && is_Const(right))
264                 return;
265
266         /* try to place the constant on the right side for a Confirm */
267         if (op == op_Const || op == op_SymConst) {
268                 ir_node *t = left;
269
270                 left  = right;
271                 right = t;
272
273                 pnc = get_inversed_pnc(pnc);
274         }
275
276         /*
277          * First case: both values are identical.
278          * replace the left one by the right (potentially const) one.
279          */
280         if (pnc == pn_Cmp_Eq) {
281                 cond_block = get_Block_cfgpred_block(block, 0);
282                 for (edge = get_irn_out_edge_first(left); edge; edge = next) {
283                         ir_node *user = get_edge_src_irn(edge);
284                         int     pos   = get_edge_src_pos(edge);
285                         ir_node *blk  = get_effective_use_block(user, pos);
286
287                         next = get_irn_out_edge_next(left, edge);
288                         if (block_dominates(block, blk)) {
289                                 /*
290                                  * Ok, we found a usage of left in a block
291                                  * dominated by the branch block.
292                                  * We can replace the input with right.
293                                  */
294                                 set_irn_n(user, pos, right);
295                                 DBG_OPT_CONFIRM(left, right);
296
297                                 DB((dbg, LEVEL_2, "Replacing input %d of node %+F with %+F\n", pos, user, right));
298
299                                 env->num_eq += 1;
300                         } else if (block_dominates(blk, cond_block)) {
301                                 if (is_Const(right) && get_irn_pinned(user) == op_pin_state_floats) {
302                                         /*
303                                          * left == Const and we found a movable user of left in a
304                                          * dominator of the Cond block
305                                          */
306                                         const ir_edge_t *edge, *next;
307                                         for (edge = get_irn_out_edge_first(user); edge; edge = next) {
308                                                 ir_node *usr_of_usr = get_edge_src_irn(edge);
309                                                 int      npos = get_edge_src_pos(edge);
310                                                 ir_node *blk  = get_effective_use_block(usr_of_usr, npos);
311
312                                                 next = get_irn_out_edge_next(user, edge);
313                                                 if (block_dominates(block, blk)) {
314                                                         /*
315                                                          * The user of the user is dominated by our true/false
316                                                          * block. So, create a copy of user WITH the constant
317                                                          * replacing it's pos'th input.
318                                                          *
319                                                          * This is always good for unop's and might be good
320                                                          * for binops.
321                                                          *
322                                                          * If user has other user in the false/true block, code
323                                                          * placement will move it down.
324                                                          * If there are users in cond block or upper, we create
325                                                          * "redundant ops", because one will have a const op,
326                                                          * the other no const ...
327                                                          */
328                                                         ir_node *new_op = exact_copy(user);
329                                                         set_nodes_block(new_op, block);
330                                                         set_irn_n(new_op, pos, right);
331                                                         set_irn_n(usr_of_usr, npos, new_op);
332                                                 }
333                                         }
334                                 }
335                         }
336                 }
337         } else { /* not pn_Cmp_Eq cases */
338                 ir_node *c = NULL;
339
340                 foreach_out_edge_safe(left, edge, next) {
341                         ir_node *succ = get_edge_src_irn(edge);
342                         int     pos   = get_edge_src_pos(edge);
343                         ir_node *blk  = get_effective_use_block(succ, pos);
344
345                         if (block_dominates(block, blk)) {
346                                 /*
347                                  * Ok, we found a usage of left in a block
348                                  * dominated by the branch block.
349                                  * We can replace the input with a Confirm(left, pnc, right).
350                                  */
351                                 if (! c)
352                                         c = new_r_Confirm(block, left, right, pnc);
353
354                                 pos = get_edge_src_pos(edge);
355                                 set_irn_n(succ, pos, c);
356                                 DB((dbg, LEVEL_2, "Replacing input %d of node %+F with %+F\n", pos, succ, c));
357
358                                 env->num_confirms += 1;
359                         }
360                 }
361
362                 if (! is_Const(right)) {
363                         /* also construct inverse Confirms */
364                         ir_node *rc = NULL;
365
366                         pnc = get_inversed_pnc(pnc);
367                         foreach_out_edge_safe(right, edge, next) {
368                                 ir_node *succ = get_edge_src_irn(edge);
369                                 int     pos;
370                                 ir_node *blk;
371
372                                 if (succ == c)
373                                         continue;
374
375                                 pos  = get_edge_src_pos(edge);
376                                 blk  = get_effective_use_block(succ, pos);
377
378                                 if (block_dominates(block, blk)) {
379                                         /*
380                                          * Ok, we found a usage of right in a block
381                                          * dominated by the branch block.
382                                          * We can replace the input with a Confirm(right, pnc^-1, left).
383                                          */
384                                         if (! rc)
385                                                 rc = new_r_Confirm(block, right, left, pnc);
386
387                                         pos = get_edge_src_pos(edge);
388                                         set_irn_n(succ, pos, rc);
389                                         DB((dbg, LEVEL_2, "Replacing input %d of node %+F with %+F\n", pos, succ, rc));
390
391                                         env->num_confirms += 1;
392                                 }
393                         }
394                 }
395         }
396 }  /* handle_if */
397
398 /**
399  * Pre-block-walker: Called for every block to insert Confirm nodes
400  */
401 static void insert_Confirm_in_block(ir_node *block, void *env)
402 {
403         ir_node *cond, *proj, *selector;
404         ir_mode *mode;
405
406         /*
407          * we can only handle blocks with only ONE control flow
408          * predecessor yet.
409          */
410         if (get_Block_n_cfgpreds(block) != 1)
411                 return;
412
413         proj = get_Block_cfgpred(block, 0);
414         if (! is_Proj(proj))
415                 return;
416
417         cond = get_Proj_pred(proj);
418         if (! is_Cond(cond))
419                 return;
420
421         selector = get_Cond_selector(cond);
422         mode = get_irn_mode(selector);
423
424         if (mode == mode_b) {
425                 ir_node *cmp;
426                 pn_Cmp pnc;
427
428                 handle_modeb(block, selector, get_Proj_proj(proj), env);
429
430                 /* this should be an IF, check this */
431                 if (! is_Proj(selector))
432                         return;
433
434                 cmp = get_Proj_pred(selector);
435                 if (! is_Cmp(cmp))
436                         return;
437
438                 pnc = get_Proj_proj(selector);
439
440                 if (get_Proj_proj(proj) != pn_Cond_true) {
441                         /* it's the false branch */
442                         mode = get_irn_mode(get_Cmp_left(cmp));
443                         pnc = get_negated_pnc(pnc, mode);
444                 }
445                 DB((dbg, LEVEL_2, "At %+F using %+F Confirm %=\n", block, cmp, pnc));
446
447                 handle_if(block, cmp, pnc, env);
448         } else if (mode_is_int(mode)) {
449                 long proj_nr = get_Proj_proj(proj);
450
451                 /* this is a CASE, but we cannot handle the default case */
452                 if (proj_nr == get_Cond_default_proj(cond))
453                         return;
454
455                 handle_case(block, get_Cond_selector(cond), proj_nr, env);
456         }
457 }  /* insert_Confirm_in_block */
458
459 /**
460  * Checks if a node is a non-null Confirm.
461  */
462 static int is_non_null_Confirm(const ir_node *ptr)
463 {
464         for (;;) {
465                 if (! is_Confirm(ptr))
466                         break;
467                 if (get_Confirm_cmp(ptr) == pn_Cmp_Lg) {
468                         ir_node *bound = get_Confirm_bound(ptr);
469
470                         if (is_Const(bound) && is_Const_null(bound))
471                                 return 1;
472                 }
473                 ptr = get_Confirm_value(ptr);
474         }
475         /*
476          * While a SymConst is not a Confirm, it is non-null
477          * anyway. This helps to reduce the number of
478          * constructed Confirms.
479          */
480         if (is_SymConst_addr_ent(ptr))
481                 return 1;
482         return 0;
483 }  /* is_non_null_Confirm */
484
485 /**
486  * The given pointer will be dereferenced, add non-null Confirms.
487  *
488  * @param ptr    a node representing an address
489  * @param block  the block of the dereferencing instruction
490  * @param env    environment
491  */
492 static void insert_non_null(ir_node *ptr, ir_node *block, env_t *env)
493 {
494         const ir_edge_t *edge, *next;
495         ir_node         *c = NULL;
496
497         foreach_out_edge_safe(ptr, edge, next) {
498                 ir_node *succ = get_edge_src_irn(edge);
499                 int     pos;
500                 ir_node *blk;
501
502
503                 /* for now, we place a Confirm only in front of a Cmp */
504                 if (! is_Cmp(succ))
505                         continue;
506
507                 pos = get_edge_src_pos(edge);
508                 blk = get_effective_use_block(succ, pos);
509
510                 if (block_dominates(block, blk)) {
511                         /*
512                          * Ok, we found a usage of ptr in a block
513                          * dominated by the Load/Store block.
514                          * We can replace the input with a Confirm(ptr, !=, NULL).
515                          */
516                         if (c == NULL) {
517                                 ir_mode *mode = get_irn_mode(ptr);
518                                 c = new_Const(get_mode_null(mode));
519
520                                 c = new_r_Confirm(block, ptr, c, pn_Cmp_Lg);
521                         }
522
523                         set_irn_n(succ, pos, c);
524                         DB((dbg, LEVEL_2, "Replacing input %d of node %+F with %+F\n", pos, succ, c));
525
526                         env->num_non_null += 1;
527                         env->num_confirms += 1;
528                 }
529         }
530 }  /* insert_non_null */
531
532 /**
533  * Pre-walker: Called for every node to insert Confirm nodes
534  */
535 static void insert_Confirm(ir_node *node, void *env)
536 {
537         ir_node *ptr;
538
539         switch (get_irn_opcode(node)) {
540         case iro_Block:
541                 insert_Confirm_in_block(node, env);
542                 break;
543         case iro_Load:
544                 ptr = get_Load_ptr(node);
545                 if (! is_non_null_Confirm(ptr))
546                         insert_non_null(ptr, get_nodes_block(node), env);
547                 break;
548         case iro_Store:
549                 ptr = get_Store_ptr(node);
550                 if (! is_non_null_Confirm(ptr))
551                         insert_non_null(ptr, get_nodes_block(node), env);
552                 break;
553         default:
554                 break;
555         }
556 }  /* insert_Confirm */
557
558 /*
559  * Construct Confirm nodes
560  */
561 void construct_confirms(ir_graph *irg)
562 {
563         env_t env;
564         int edges_active = edges_activated(irg);
565
566
567         FIRM_DBG_REGISTER(dbg, "firm.ana.confirm");
568
569         remove_critical_cf_edges(irg);
570
571         /* we need dominance info */
572         assure_doms(irg);
573
574         assert(get_irg_pinned(irg) == op_pin_state_pinned &&
575                "Nodes must be placed to insert Confirms");
576
577         if (! edges_active) {
578                 /* We need edges */
579                 edges_activate(irg);
580         }
581
582         env.num_confirms = 0;
583         env.num_consts   = 0;
584         env.num_eq       = 0;
585         env.num_non_null = 0;
586
587         if (get_opt_global_null_ptr_elimination()) {
588                 /* do global NULL test elimination */
589                 irg_walk_graph(irg, insert_Confirm, NULL, &env);
590         } else {
591                 /* now, visit all blocks and add Confirms where possible */
592                 irg_block_walk_graph(irg, insert_Confirm_in_block, NULL, &env);
593         }
594
595         if (env.num_confirms | env.num_consts | env.num_eq) {
596                 /* we have add nodes or changed DF edges */
597                 set_irg_outs_inconsistent(irg);
598
599                 /* the new nodes are not in the loop info */
600                 set_irg_loopinfo_inconsistent(irg);
601         }
602
603         DB((dbg, LEVEL_1, "# Confirms inserted : %u\n", env.num_confirms));
604         DB((dbg, LEVEL_1, "# Const replacements: %u\n", env.num_consts));
605         DB((dbg, LEVEL_1, "# node equalities   : %u\n", env.num_eq));
606         DB((dbg, LEVEL_1, "# non-null Confirms : %u\n", env.num_non_null));
607
608         /* deactivate edges if they where off */
609         if (! edges_active)
610                 edges_deactivate(irg);
611 }  /* construct_confirms */
612
613 /* Construct a pass. */
614 ir_graph_pass_t *construct_confirms_pass(const char *name)
615 {
616         return def_graph_pass(name ? name : "confirm", construct_confirms);
617 }  /* construct_confirms_pass */
618
619 #if 0
620 /**
621  * Post-walker: Remove Confirm nodes
622  */
623 static void rem_Confirm(ir_node *n, void *env)
624 {
625         (void) env;
626         if (is_Confirm(n)) {
627                 ir_node *value = get_Confirm_value(n);
628                 if (value != n)
629                         exchange(n, value);
630                 else {
631                         /*
632                          * Strange: a Confirm is its own bound. This can happen
633                          * in dead blocks when Phi nodes are already removed.
634                          */
635                         exchange(n, new_Bad());
636                 }
637         }
638 }  /* rem_Confirm */
639 #endif
640
641 /*
642  * Remove all Confirm nodes from a graph.
643  */
644 void remove_confirms(ir_graph *irg)
645 {
646         int rem = get_opt_remove_confirm();
647
648         set_opt_remove_confirm(1);
649         optimize_graph_df(irg);
650         set_opt_remove_confirm(rem);
651 }  /* remove_confirms */
652
653 /* Construct a pass. */
654 ir_graph_pass_t *remove_confirms_pass(const char *name)
655 {
656         return def_graph_pass(name ? name : "rem_confirm", remove_confirms);
657 }  /* remove_confirms_pass */