]> gcc.gnu.org Git - gcc.git/blame - gcc/tree-ssa-dom.c
loop-1.c: Add -static for *-*-darwin*.
[gcc.git] / gcc / tree-ssa-dom.c
CommitLineData
6de9cd9a
DN
1/* SSA Dominator optimizations for trees
2 Copyright (C) 2001, 2002, 2003, 2004 Free Software Foundation, Inc.
3 Contributed by Diego Novillo <dnovillo@redhat.com>
4
5This file is part of GCC.
6
7GCC is free software; you can redistribute it and/or modify
8it under the terms of the GNU General Public License as published by
9the Free Software Foundation; either version 2, or (at your option)
10any later version.
11
12GCC is distributed in the hope that it will be useful,
13but WITHOUT ANY WARRANTY; without even the implied warranty of
14MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15GNU General Public License for more details.
16
17You should have received a copy of the GNU General Public License
18along with GCC; see the file COPYING. If not, write to
19the Free Software Foundation, 59 Temple Place - Suite 330,
20Boston, MA 02111-1307, USA. */
21
22#include "config.h"
23#include "system.h"
24#include "coretypes.h"
25#include "tm.h"
26#include "tree.h"
27#include "flags.h"
28#include "rtl.h"
29#include "tm_p.h"
30#include "ggc.h"
31#include "basic-block.h"
32#include "output.h"
33#include "errors.h"
34#include "expr.h"
35#include "function.h"
36#include "diagnostic.h"
37#include "timevar.h"
38#include "tree-dump.h"
39#include "tree-flow.h"
40#include "domwalk.h"
41#include "real.h"
42#include "tree-pass.h"
c7f90219 43#include "tree-ssa-propagate.h"
6de9cd9a
DN
44#include "langhooks.h"
45
46/* This file implements optimizations on the dominator tree. */
47
48/* Hash table with expressions made available during the renaming process.
49 When an assignment of the form X_i = EXPR is found, the statement is
50 stored in this table. If the same expression EXPR is later found on the
51 RHS of another statement, it is replaced with X_i (thus performing
52 global redundancy elimination). Similarly as we pass through conditionals
53 we record the conditional itself as having either a true or false value
54 in this table. */
55static htab_t avail_exprs;
56
48732f23
JL
57/* Stack of available expressions in AVAIL_EXPRs. Each block pushes any
58 expressions it enters into the hash table along with a marker entry
b3a27618 59 (null). When we finish processing the block, we pop off entries and
48732f23
JL
60 remove the expressions from the global hash table until we hit the
61 marker. */
62static varray_type avail_exprs_stack;
63
9fae925b
JL
64/* Stack of trees used to restore the global currdefs to its original
65 state after completing optimization of a block and its dominator children.
66
67 An SSA_NAME indicates that the current definition of the underlying
68 variable should be set to the given SSA_NAME.
69
70 A _DECL node indicates that the underlying variable has no current
71 definition.
72
73 A NULL node is used to mark the last node associated with the
74 current block. */
75varray_type block_defs_stack;
76
a6e1aa26
JL
77/* Stack of statements we need to rescan during finalization for newly
78 exposed variables.
79
80 Statement rescanning must occur after the current block's available
81 expressions are removed from AVAIL_EXPRS. Else we may change the
82 hash code for an expression and be unable to find/remove it from
83 AVAIL_EXPRS. */
84varray_type stmts_to_rescan;
85
6de9cd9a
DN
86/* Structure for entries in the expression hash table.
87
88 This requires more memory for the hash table entries, but allows us
89 to avoid creating silly tree nodes and annotations for conditionals,
90 eliminates 2 global hash tables and two block local varrays.
91
92 It also allows us to reduce the number of hash table lookups we
93 have to perform in lookup_avail_expr and finally it allows us to
94 significantly reduce the number of calls into the hashing routine
95 itself. */
56b043c8 96
6de9cd9a
DN
97struct expr_hash_elt
98{
99 /* The value (lhs) of this expression. */
100 tree lhs;
101
102 /* The expression (rhs) we want to record. */
103 tree rhs;
104
105 /* The annotation if this element corresponds to a statement. */
106 stmt_ann_t ann;
107
108 /* The hash value for RHS/ann. */
109 hashval_t hash;
110};
111
b5fefcf6
JL
112/* Stack of dest,src pairs that need to be restored during finalization.
113
114 A NULL entry is used to mark the end of pairs which need to be
115 restored during finalization of this block. */
116static varray_type const_and_copies_stack;
117
6de9cd9a
DN
118/* Bitmap of SSA_NAMEs known to have a nonzero value, even if we do not
119 know their exact value. */
120static bitmap nonzero_vars;
121
fdabe5c2
JL
122/* Stack of SSA_NAMEs which need their NONZERO_VARS property cleared
123 when the current block is finalized.
124
125 A NULL entry is used to mark the end of names needing their
126 entry in NONZERO_VARS cleared during finalization of this block. */
127static varray_type nonzero_vars_stack;
128
6de9cd9a
DN
129/* Track whether or not we have changed the control flow graph. */
130static bool cfg_altered;
131
1eaba2f2 132/* Bitmap of blocks that have had EH statements cleaned. We should
f6fe65dc 133 remove their dead edges eventually. */
1eaba2f2
RH
134static bitmap need_eh_cleanup;
135
6de9cd9a
DN
136/* Statistics for dominator optimizations. */
137struct opt_stats_d
138{
139 long num_stmts;
140 long num_exprs_considered;
141 long num_re;
142};
143
23530866
JL
144static struct opt_stats_d opt_stats;
145
6de9cd9a
DN
146/* Value range propagation record. Each time we encounter a conditional
147 of the form SSA_NAME COND CONST we create a new vrp_element to record
148 how the condition affects the possible values SSA_NAME may have.
149
150 Each record contains the condition tested (COND), and the the range of
151 values the variable may legitimately have if COND is true. Note the
152 range of values may be a smaller range than COND specifies if we have
153 recorded other ranges for this variable. Each record also contains the
154 block in which the range was recorded for invalidation purposes.
155
156 Note that the current known range is computed lazily. This allows us
157 to avoid the overhead of computing ranges which are never queried.
158
159 When we encounter a conditional, we look for records which constrain
160 the SSA_NAME used in the condition. In some cases those records allow
161 us to determine the condition's result at compile time. In other cases
162 they may allow us to simplify the condition.
163
164 We also use value ranges to do things like transform signed div/mod
165 operations into unsigned div/mod or to simplify ABS_EXPRs.
166
167 Simple experiments have shown these optimizations to not be all that
168 useful on switch statements (much to my surprise). So switch statement
169 optimizations are not performed.
170
171 Note carefully we do not propagate information through each statement
454ff5cb 172 in the block. i.e., if we know variable X has a value defined of
6de9cd9a
DN
173 [0, 25] and we encounter Y = X + 1, we do not track a value range
174 for Y (which would be [1, 26] if we cared). Similarly we do not
175 constrain values as we encounter narrowing typecasts, etc. */
176
177struct vrp_element
178{
179 /* The highest and lowest values the variable in COND may contain when
180 COND is true. Note this may not necessarily be the same values
181 tested by COND if the same variable was used in earlier conditionals.
182
183 Note this is computed lazily and thus can be NULL indicating that
184 the values have not been computed yet. */
185 tree low;
186 tree high;
187
188 /* The actual conditional we recorded. This is needed since we compute
189 ranges lazily. */
190 tree cond;
191
192 /* The basic block where this record was created. We use this to determine
193 when to remove records. */
194 basic_block bb;
195};
196
23530866
JL
197/* A hash table holding value range records (VRP_ELEMENTs) for a given
198 SSA_NAME. We used to use a varray indexed by SSA_NAME_VERSION, but
199 that gets awful wasteful, particularly since the density objects
200 with useful information is very low. */
201static htab_t vrp_data;
202
203/* An entry in the VRP_DATA hash table. We record the variable and a
471854f8 204 varray of VRP_ELEMENT records associated with that variable. */
6de9cd9a 205
23530866
JL
206struct vrp_hash_elt
207{
208 tree var;
209 varray_type records;
210};
6de9cd9a 211
fdabe5c2
JL
212/* Array of variables which have their values constrained by operations
213 in this basic block. We use this during finalization to know
214 which variables need their VRP data updated. */
6de9cd9a 215
fdabe5c2
JL
216/* Stack of SSA_NAMEs which had their values constrainted by operations
217 in this basic block. During finalization of this block we use this
218 list to determine which variables need their VRP data updated.
219
220 A NULL entry marks the end of the SSA_NAMEs associated with this block. */
221static varray_type vrp_variables_stack;
6de9cd9a
DN
222
223struct eq_expr_value
224{
225 tree src;
226 tree dst;
227};
228
229/* Local functions. */
230static void optimize_stmt (struct dom_walk_data *,
231 basic_block bb,
232 block_stmt_iterator);
48732f23 233static tree lookup_avail_expr (tree, bool);
fdabe5c2 234static struct eq_expr_value get_eq_expr_value (tree, int, basic_block);
23530866
JL
235static hashval_t vrp_hash (const void *);
236static int vrp_eq (const void *, const void *);
6de9cd9a 237static hashval_t avail_expr_hash (const void *);
940db2c8 238static hashval_t real_avail_expr_hash (const void *);
6de9cd9a
DN
239static int avail_expr_eq (const void *, const void *);
240static void htab_statistics (FILE *, htab_t);
48732f23
JL
241static void record_cond (tree, tree);
242static void record_dominating_conditions (tree);
b5fefcf6
JL
243static void record_const_or_copy (tree, tree);
244static void record_equality (tree, tree);
48732f23 245static tree update_rhs_and_lookup_avail_expr (tree, tree, bool);
6de9cd9a 246static tree simplify_rhs_and_lookup_avail_expr (struct dom_walk_data *,
68b9f53b 247 tree, int);
48732f23
JL
248static tree simplify_cond_and_lookup_avail_expr (tree, stmt_ann_t, int);
249static tree simplify_switch_and_lookup_avail_expr (tree, int);
6de9cd9a 250static tree find_equivalent_equality_comparison (tree);
fdabe5c2 251static void record_range (tree, basic_block);
6de9cd9a
DN
252static bool extract_range_from_cond (tree, tree *, tree *, int *);
253static void record_equivalences_from_phis (struct dom_walk_data *, basic_block);
254static void record_equivalences_from_incoming_edge (struct dom_walk_data *,
255 basic_block);
256static bool eliminate_redundant_computations (struct dom_walk_data *,
257 tree, stmt_ann_t);
fdabe5c2 258static void record_equivalences_from_stmt (tree, int, stmt_ann_t);
6de9cd9a
DN
259static void thread_across_edge (struct dom_walk_data *, edge);
260static void dom_opt_finalize_block (struct dom_walk_data *, basic_block);
6de9cd9a
DN
261static void dom_opt_initialize_block (struct dom_walk_data *, basic_block);
262static void cprop_into_phis (struct dom_walk_data *, basic_block);
48732f23 263static void remove_local_expressions_from_table (void);
b5fefcf6 264static void restore_vars_to_original_value (void);
9fae925b
JL
265static void restore_currdefs_to_original_value (void);
266static void register_definitions_for_stmt (tree);
28c008bb 267static edge single_incoming_edge_ignoring_loop_edges (basic_block);
fdabe5c2 268static void restore_nonzero_vars_to_original_value (void);
01d8c00b 269static inline bool unsafe_associative_fp_binop (tree);
6de9cd9a
DN
270
271/* Local version of fold that doesn't introduce cruft. */
272
273static tree
274local_fold (tree t)
275{
276 t = fold (t);
277
278 /* Strip away useless type conversions. Both the NON_LVALUE_EXPR that
279 may have been added by fold, and "useless" type conversions that might
280 now be apparent due to propagation. */
6de9cd9a
DN
281 STRIP_USELESS_TYPE_CONVERSION (t);
282
283 return t;
284}
285
6de9cd9a
DN
286/* Jump threading, redundancy elimination and const/copy propagation.
287
6de9cd9a
DN
288 This pass may expose new symbols that need to be renamed into SSA. For
289 every new symbol exposed, its corresponding bit will be set in
ff2ad0f7 290 VARS_TO_RENAME. */
6de9cd9a
DN
291
292static void
293tree_ssa_dominator_optimize (void)
294{
6de9cd9a
DN
295 struct dom_walk_data walk_data;
296 unsigned int i;
297
fded8de7
DN
298 memset (&opt_stats, 0, sizeof (opt_stats));
299
6de9cd9a
DN
300 for (i = 0; i < num_referenced_vars; i++)
301 var_ann (referenced_var (i))->current_def = NULL;
302
303 /* Mark loop edges so we avoid threading across loop boundaries.
304 This may result in transforming natural loop into irreducible
305 region. */
306 mark_dfs_back_edges ();
307
308 /* Create our hash tables. */
940db2c8 309 avail_exprs = htab_create (1024, real_avail_expr_hash, avail_expr_eq, free);
23530866 310 vrp_data = htab_create (ceil_log2 (num_ssa_names), vrp_hash, vrp_eq, free);
48732f23 311 VARRAY_TREE_INIT (avail_exprs_stack, 20, "Available expression stack");
9fae925b 312 VARRAY_TREE_INIT (block_defs_stack, 20, "Block DEFS stack");
b5fefcf6 313 VARRAY_TREE_INIT (const_and_copies_stack, 20, "Block const_and_copies stack");
fdabe5c2
JL
314 VARRAY_TREE_INIT (nonzero_vars_stack, 20, "Block nonzero_vars stack");
315 VARRAY_TREE_INIT (vrp_variables_stack, 20, "Block vrp_variables stack");
23530866 316 VARRAY_TREE_INIT (stmts_to_rescan, 20, "Statements to rescan");
6de9cd9a 317 nonzero_vars = BITMAP_XMALLOC ();
1eaba2f2 318 need_eh_cleanup = BITMAP_XMALLOC ();
6de9cd9a
DN
319
320 /* Setup callbacks for the generic dominator tree walker. */
321 walk_data.walk_stmts_backward = false;
322 walk_data.dom_direction = CDI_DOMINATORS;
fdabe5c2 323 walk_data.initialize_block_local_data = NULL;
6de9cd9a
DN
324 walk_data.before_dom_children_before_stmts = dom_opt_initialize_block;
325 walk_data.before_dom_children_walk_stmts = optimize_stmt;
326 walk_data.before_dom_children_after_stmts = cprop_into_phis;
327 walk_data.after_dom_children_before_stmts = NULL;
328 walk_data.after_dom_children_walk_stmts = NULL;
329 walk_data.after_dom_children_after_stmts = dom_opt_finalize_block;
330 /* Right now we only attach a dummy COND_EXPR to the global data pointer.
331 When we attach more stuff we'll need to fill this out with a real
332 structure. */
333 walk_data.global_data = NULL;
fdabe5c2 334 walk_data.block_local_data_size = 0;
6de9cd9a
DN
335
336 /* Now initialize the dominator walker. */
337 init_walk_dominator_tree (&walk_data);
338
6de9cd9a
DN
339 calculate_dominance_info (CDI_DOMINATORS);
340
341 /* If we prove certain blocks are unreachable, then we want to
342 repeat the dominator optimization process as PHI nodes may
343 have turned into copies which allows better propagation of
344 values. So we repeat until we do not identify any new unreachable
345 blocks. */
346 do
347 {
348 /* Optimize the dominator tree. */
349 cfg_altered = false;
350
351 /* Recursively walk the dominator tree optimizing statements. */
352 walk_dominator_tree (&walk_data, ENTRY_BLOCK_PTR);
353
56b043c8
JL
354 /* If we exposed any new variables, go ahead and put them into
355 SSA form now, before we handle jump threading. This simplifies
356 interactions between rewriting of _DECL nodes into SSA form
357 and rewriting SSA_NAME nodes into SSA form after block
358 duplication and CFG manipulation. */
359 if (bitmap_first_set_bit (vars_to_rename) >= 0)
360 {
361 rewrite_into_ssa (false);
362 bitmap_clear (vars_to_rename);
363 }
6de9cd9a 364
56b043c8
JL
365 /* Thread jumps, creating duplicate blocks as needed. */
366 cfg_altered = thread_through_all_blocks ();
6de9cd9a 367
56b043c8
JL
368 /* Removal of statements may make some EH edges dead. Purge
369 such edges from the CFG as needed. */
1eaba2f2
RH
370 if (bitmap_first_set_bit (need_eh_cleanup) >= 0)
371 {
56b043c8 372 cfg_altered |= tree_purge_all_dead_eh_edges (need_eh_cleanup);
1eaba2f2
RH
373 bitmap_zero (need_eh_cleanup);
374 }
375
56b043c8
JL
376 free_dominance_info (CDI_DOMINATORS);
377 cfg_altered = cleanup_tree_cfg ();
378 calculate_dominance_info (CDI_DOMINATORS);
6de9cd9a 379
56b043c8 380 rewrite_ssa_into_ssa ();
6de9cd9a 381
6de9cd9a
DN
382 /* Reinitialize the various tables. */
383 bitmap_clear (nonzero_vars);
384 htab_empty (avail_exprs);
23530866 385 htab_empty (vrp_data);
6de9cd9a
DN
386
387 for (i = 0; i < num_referenced_vars; i++)
388 var_ann (referenced_var (i))->current_def = NULL;
389 }
390 while (cfg_altered);
391
6de9cd9a
DN
392 /* Debugging dumps. */
393 if (dump_file && (dump_flags & TDF_STATS))
394 dump_dominator_optimization_stats (dump_file);
395
61ada8ae 396 /* We emptied the hash table earlier, now delete it completely. */
6de9cd9a 397 htab_delete (avail_exprs);
23530866 398 htab_delete (vrp_data);
6de9cd9a 399
1ea7e6ad 400 /* It is not necessary to clear CURRDEFS, REDIRECTION_EDGES, VRP_DATA,
6de9cd9a
DN
401 CONST_AND_COPIES, and NONZERO_VARS as they all get cleared at the bottom
402 of the do-while loop above. */
403
404 /* And finalize the dominator walker. */
405 fini_walk_dominator_tree (&walk_data);
cfa4cb00 406
471854f8 407 /* Free nonzero_vars. */
cfa4cb00 408 BITMAP_XFREE (nonzero_vars);
1eaba2f2 409 BITMAP_XFREE (need_eh_cleanup);
3aecd08b
JL
410
411 /* Finally, remove everything except invariants in SSA_NAME_VALUE.
412
413 Long term we will be able to let everything in SSA_NAME_VALUE
414 persist. However, for now, we know this is the safe thing to
415 do. */
416 for (i = 0; i < num_ssa_names; i++)
417 {
418 tree name = ssa_name (i);
419 tree value;
420
421 if (!name)
422 continue;
423
424 value = SSA_NAME_VALUE (name);
425 if (value && !is_gimple_min_invariant (value))
426 SSA_NAME_VALUE (name) = NULL;
427 }
6de9cd9a
DN
428}
429
430static bool
431gate_dominator (void)
432{
433 return flag_tree_dom != 0;
434}
435
436struct tree_opt_pass pass_dominator =
437{
438 "dom", /* name */
439 gate_dominator, /* gate */
440 tree_ssa_dominator_optimize, /* execute */
441 NULL, /* sub */
442 NULL, /* next */
443 0, /* static_pass_number */
444 TV_TREE_SSA_DOMINATOR_OPTS, /* tv_id */
c1b763fa 445 PROP_cfg | PROP_ssa | PROP_alias, /* properties_required */
6de9cd9a
DN
446 0, /* properties_provided */
447 0, /* properties_destroyed */
448 0, /* todo_flags_start */
449 TODO_dump_func | TODO_rename_vars
9f8628ba
PB
450 | TODO_verify_ssa, /* todo_flags_finish */
451 0 /* letter */
6de9cd9a
DN
452};
453
454
455/* We are exiting BB, see if the target block begins with a conditional
456 jump which has a known value when reached via BB. */
457
458static void
459thread_across_edge (struct dom_walk_data *walk_data, edge e)
460{
6de9cd9a
DN
461 block_stmt_iterator bsi;
462 tree stmt = NULL;
463 tree phi;
464
465 /* Each PHI creates a temporary equivalence, record them. */
17192884 466 for (phi = phi_nodes (e->dest); phi; phi = PHI_CHAIN (phi))
6de9cd9a 467 {
d00ad49b 468 tree src = PHI_ARG_DEF_FROM_EDGE (phi, e);
6de9cd9a 469 tree dst = PHI_RESULT (phi);
b5fefcf6 470 record_const_or_copy (dst, src);
9fae925b 471 register_new_def (dst, &block_defs_stack);
6de9cd9a
DN
472 }
473
474 for (bsi = bsi_start (e->dest); ! bsi_end_p (bsi); bsi_next (&bsi))
475 {
476 tree lhs, cached_lhs;
477
478 stmt = bsi_stmt (bsi);
479
480 /* Ignore empty statements and labels. */
481 if (IS_EMPTY_STMT (stmt) || TREE_CODE (stmt) == LABEL_EXPR)
482 continue;
483
484 /* If this is not a MODIFY_EXPR which sets an SSA_NAME to a new
485 value, then stop our search here. Ideally when we stop a
486 search we stop on a COND_EXPR or SWITCH_EXPR. */
487 if (TREE_CODE (stmt) != MODIFY_EXPR
488 || TREE_CODE (TREE_OPERAND (stmt, 0)) != SSA_NAME)
489 break;
490
491 /* At this point we have a statement which assigns an RHS to an
492 SSA_VAR on the LHS. We want to prove that the RHS is already
493 available and that its value is held in the current definition
494 of the LHS -- meaning that this assignment is a NOP when
495 reached via edge E. */
496 if (TREE_CODE (TREE_OPERAND (stmt, 1)) == SSA_NAME)
497 cached_lhs = TREE_OPERAND (stmt, 1);
498 else
48732f23 499 cached_lhs = lookup_avail_expr (stmt, false);
6de9cd9a
DN
500
501 lhs = TREE_OPERAND (stmt, 0);
502
503 /* This can happen if we thread around to the start of a loop. */
504 if (lhs == cached_lhs)
505 break;
506
507 /* If we did not find RHS in the hash table, then try again after
508 temporarily const/copy propagating the operands. */
509 if (!cached_lhs)
510 {
511 /* Copy the operands. */
512 stmt_ann_t ann = stmt_ann (stmt);
513 use_optype uses = USE_OPS (ann);
514 vuse_optype vuses = VUSE_OPS (ann);
515 tree *uses_copy = xcalloc (NUM_USES (uses), sizeof (tree));
516 tree *vuses_copy = xcalloc (NUM_VUSES (vuses), sizeof (tree));
517 unsigned int i;
518
519 /* Make a copy of the uses into USES_COPY, then cprop into
520 the use operands. */
521 for (i = 0; i < NUM_USES (uses); i++)
522 {
523 tree tmp = NULL;
524
525 uses_copy[i] = USE_OP (uses, i);
526 if (TREE_CODE (USE_OP (uses, i)) == SSA_NAME)
3aecd08b
JL
527 tmp = SSA_NAME_VALUE (USE_OP (uses, i));
528 if (tmp && TREE_CODE (tmp) != VALUE_HANDLE)
d00ad49b 529 SET_USE_OP (uses, i, tmp);
6de9cd9a
DN
530 }
531
532 /* Similarly for virtual uses. */
533 for (i = 0; i < NUM_VUSES (vuses); i++)
534 {
535 tree tmp = NULL;
536
537 vuses_copy[i] = VUSE_OP (vuses, i);
538 if (TREE_CODE (VUSE_OP (vuses, i)) == SSA_NAME)
3aecd08b
JL
539 tmp = SSA_NAME_VALUE (VUSE_OP (vuses, i));
540 if (tmp && TREE_CODE (tmp) != VALUE_HANDLE)
d00ad49b 541 SET_VUSE_OP (vuses, i, tmp);
6de9cd9a
DN
542 }
543
544 /* Try to lookup the new expression. */
48732f23 545 cached_lhs = lookup_avail_expr (stmt, false);
6de9cd9a
DN
546
547 /* Restore the statement's original uses/defs. */
548 for (i = 0; i < NUM_USES (uses); i++)
d00ad49b 549 SET_USE_OP (uses, i, uses_copy[i]);
6de9cd9a
DN
550
551 for (i = 0; i < NUM_VUSES (vuses); i++)
d00ad49b 552 SET_VUSE_OP (vuses, i, vuses_copy[i]);
6de9cd9a
DN
553
554 free (uses_copy);
555 free (vuses_copy);
556
557 /* If we still did not find the expression in the hash table,
558 then we can not ignore this statement. */
559 if (! cached_lhs)
560 break;
561 }
562
563 /* If the expression in the hash table was not assigned to an
564 SSA_NAME, then we can not ignore this statement. */
565 if (TREE_CODE (cached_lhs) != SSA_NAME)
566 break;
567
568 /* If we have different underlying variables, then we can not
569 ignore this statement. */
570 if (SSA_NAME_VAR (cached_lhs) != SSA_NAME_VAR (lhs))
571 break;
572
573 /* If CACHED_LHS does not represent the current value of the undering
574 variable in CACHED_LHS/LHS, then we can not ignore this statement. */
575 if (var_ann (SSA_NAME_VAR (lhs))->current_def != cached_lhs)
576 break;
577
578 /* If we got here, then we can ignore this statement and continue
579 walking through the statements in the block looking for a threadable
580 COND_EXPR.
581
582 We want to record an equivalence lhs = cache_lhs so that if
583 the result of this statement is used later we can copy propagate
584 suitably. */
b5fefcf6 585 record_const_or_copy (lhs, cached_lhs);
9fae925b 586 register_new_def (lhs, &block_defs_stack);
6de9cd9a
DN
587 }
588
589 /* If we stopped at a COND_EXPR or SWITCH_EXPR, then see if we know which
590 arm will be taken. */
591 if (stmt
592 && (TREE_CODE (stmt) == COND_EXPR
593 || TREE_CODE (stmt) == SWITCH_EXPR))
594 {
595 tree cond, cached_lhs;
596 edge e1;
628f6a4e 597 edge_iterator ei;
6de9cd9a
DN
598
599 /* Do not forward entry edges into the loop. In the case loop
600 has multiple entry edges we may end up in constructing irreducible
601 region.
602 ??? We may consider forwarding the edges in the case all incoming
603 edges forward to the same destination block. */
604 if (!e->flags & EDGE_DFS_BACK)
605 {
628f6a4e 606 FOR_EACH_EDGE (e1, ei, e->dest->preds)
6de9cd9a
DN
607 if (e1->flags & EDGE_DFS_BACK)
608 break;
609 if (e1)
610 return;
611 }
612
613 /* Now temporarily cprop the operands and try to find the resulting
614 expression in the hash tables. */
615 if (TREE_CODE (stmt) == COND_EXPR)
616 cond = COND_EXPR_COND (stmt);
617 else
618 cond = SWITCH_COND (stmt);
619
6615c446 620 if (COMPARISON_CLASS_P (cond))
6de9cd9a
DN
621 {
622 tree dummy_cond, op0, op1;
623 enum tree_code cond_code;
624
625 op0 = TREE_OPERAND (cond, 0);
626 op1 = TREE_OPERAND (cond, 1);
627 cond_code = TREE_CODE (cond);
628
629 /* Get the current value of both operands. */
630 if (TREE_CODE (op0) == SSA_NAME)
631 {
3aecd08b
JL
632 tree tmp = SSA_NAME_VALUE (op0);
633 if (tmp && TREE_CODE (tmp) != VALUE_HANDLE)
6de9cd9a
DN
634 op0 = tmp;
635 }
636
637 if (TREE_CODE (op1) == SSA_NAME)
638 {
3aecd08b
JL
639 tree tmp = SSA_NAME_VALUE (op1);
640 if (tmp && TREE_CODE (tmp) != VALUE_HANDLE)
6de9cd9a
DN
641 op1 = tmp;
642 }
643
644 /* Stuff the operator and operands into our dummy conditional
645 expression, creating the dummy conditional if necessary. */
646 dummy_cond = walk_data->global_data;
647 if (! dummy_cond)
648 {
649 dummy_cond = build (cond_code, boolean_type_node, op0, op1);
650 dummy_cond = build (COND_EXPR, void_type_node,
651 dummy_cond, NULL, NULL);
652 walk_data->global_data = dummy_cond;
653 }
654 else
655 {
656 TREE_SET_CODE (TREE_OPERAND (dummy_cond, 0), cond_code);
657 TREE_OPERAND (TREE_OPERAND (dummy_cond, 0), 0) = op0;
658 TREE_OPERAND (TREE_OPERAND (dummy_cond, 0), 1) = op1;
659 }
660
661 /* If the conditional folds to an invariant, then we are done,
662 otherwise look it up in the hash tables. */
663 cached_lhs = local_fold (COND_EXPR_COND (dummy_cond));
664 if (! is_gimple_min_invariant (cached_lhs))
48732f23 665 cached_lhs = lookup_avail_expr (dummy_cond, false);
6de9cd9a
DN
666 if (!cached_lhs || ! is_gimple_min_invariant (cached_lhs))
667 {
6de9cd9a 668 cached_lhs = simplify_cond_and_lookup_avail_expr (dummy_cond,
68b9f53b 669 NULL,
6de9cd9a
DN
670 false);
671 }
672 }
673 /* We can have conditionals which just test the state of a
674 variable rather than use a relational operator. These are
675 simpler to handle. */
676 else if (TREE_CODE (cond) == SSA_NAME)
677 {
678 cached_lhs = cond;
3aecd08b 679 cached_lhs = SSA_NAME_VALUE (cached_lhs);
6de9cd9a
DN
680 if (cached_lhs && ! is_gimple_min_invariant (cached_lhs))
681 cached_lhs = 0;
682 }
683 else
48732f23 684 cached_lhs = lookup_avail_expr (stmt, false);
6de9cd9a
DN
685
686 if (cached_lhs)
687 {
688 edge taken_edge = find_taken_edge (e->dest, cached_lhs);
689 basic_block dest = (taken_edge ? taken_edge->dest : NULL);
690
8a78744f 691 if (dest == e->dest)
6de9cd9a
DN
692 return;
693
694 /* If we have a known destination for the conditional, then
695 we can perform this optimization, which saves at least one
696 conditional jump each time it applies since we get to
471854f8 697 bypass the conditional at our original destination. */
6de9cd9a
DN
698 if (dest)
699 {
15db5571
JH
700 update_bb_profile_for_threading (e->dest, EDGE_FREQUENCY (e),
701 e->count, taken_edge);
56b043c8
JL
702 e->aux = taken_edge;
703 bb_ann (e->dest)->incoming_edge_threaded = true;
6de9cd9a
DN
704 }
705 }
706 }
707}
708
709
6de9cd9a
DN
710/* Initialize local stacks for this optimizer and record equivalences
711 upon entry to BB. Equivalences can come from the edge traversed to
712 reach BB or they may come from PHI nodes at the start of BB. */
713
714static void
715dom_opt_initialize_block (struct dom_walk_data *walk_data, basic_block bb)
716{
717 if (dump_file && (dump_flags & TDF_DETAILS))
718 fprintf (dump_file, "\n\nOptimizing block #%d\n\n", bb->index);
719
9fae925b
JL
720 /* Push a marker on the stacks of local information so that we know how
721 far to unwind when we finalize this block. */
48732f23 722 VARRAY_PUSH_TREE (avail_exprs_stack, NULL_TREE);
9fae925b 723 VARRAY_PUSH_TREE (block_defs_stack, NULL_TREE);
b5fefcf6 724 VARRAY_PUSH_TREE (const_and_copies_stack, NULL_TREE);
fdabe5c2
JL
725 VARRAY_PUSH_TREE (nonzero_vars_stack, NULL_TREE);
726 VARRAY_PUSH_TREE (vrp_variables_stack, NULL_TREE);
48732f23 727
6de9cd9a
DN
728 record_equivalences_from_incoming_edge (walk_data, bb);
729
730 /* PHI nodes can create equivalences too. */
731 record_equivalences_from_phis (walk_data, bb);
732}
733
734/* Given an expression EXPR (a relational expression or a statement),
735 initialize the hash table element pointed by by ELEMENT. */
736
737static void
738initialize_hash_element (tree expr, tree lhs, struct expr_hash_elt *element)
739{
740 /* Hash table elements may be based on conditional expressions or statements.
741
742 For the former case, we have no annotation and we want to hash the
743 conditional expression. In the latter case we have an annotation and
744 we want to record the expression the statement evaluates. */
6615c446 745 if (COMPARISON_CLASS_P (expr) || TREE_CODE (expr) == TRUTH_NOT_EXPR)
6de9cd9a
DN
746 {
747 element->ann = NULL;
748 element->rhs = expr;
749 }
750 else if (TREE_CODE (expr) == COND_EXPR)
751 {
752 element->ann = stmt_ann (expr);
753 element->rhs = COND_EXPR_COND (expr);
754 }
755 else if (TREE_CODE (expr) == SWITCH_EXPR)
756 {
757 element->ann = stmt_ann (expr);
758 element->rhs = SWITCH_COND (expr);
759 }
760 else if (TREE_CODE (expr) == RETURN_EXPR && TREE_OPERAND (expr, 0))
761 {
762 element->ann = stmt_ann (expr);
763 element->rhs = TREE_OPERAND (TREE_OPERAND (expr, 0), 1);
764 }
765 else
766 {
767 element->ann = stmt_ann (expr);
768 element->rhs = TREE_OPERAND (expr, 1);
769 }
770
771 element->lhs = lhs;
772 element->hash = avail_expr_hash (element);
773}
774
775/* Remove all the expressions in LOCALS from TABLE, stopping when there are
776 LIMIT entries left in LOCALs. */
777
778static void
48732f23 779remove_local_expressions_from_table (void)
6de9cd9a 780{
6de9cd9a 781 /* Remove all the expressions made available in this block. */
48732f23 782 while (VARRAY_ACTIVE_SIZE (avail_exprs_stack) > 0)
6de9cd9a
DN
783 {
784 struct expr_hash_elt element;
48732f23
JL
785 tree expr = VARRAY_TOP_TREE (avail_exprs_stack);
786 VARRAY_POP (avail_exprs_stack);
787
788 if (expr == NULL_TREE)
789 break;
6de9cd9a
DN
790
791 initialize_hash_element (expr, NULL, &element);
48732f23 792 htab_remove_elt_with_hash (avail_exprs, &element, element.hash);
6de9cd9a
DN
793 }
794}
795
796/* Use the SSA_NAMES in LOCALS to restore TABLE to its original
1ea7e6ad 797 state, stopping when there are LIMIT entries left in LOCALs. */
6de9cd9a
DN
798
799static void
76fd4fd7 800restore_nonzero_vars_to_original_value (void)
6de9cd9a 801{
fdabe5c2 802 while (VARRAY_ACTIVE_SIZE (nonzero_vars_stack) > 0)
6de9cd9a 803 {
fdabe5c2
JL
804 tree name = VARRAY_TOP_TREE (nonzero_vars_stack);
805 VARRAY_POP (nonzero_vars_stack);
806
807 if (name == NULL)
808 break;
809
810 bitmap_clear_bit (nonzero_vars, SSA_NAME_VERSION (name));
6de9cd9a
DN
811 }
812}
813
b5fefcf6
JL
814/* Use the source/dest pairs in CONST_AND_COPIES_STACK to restore
815 CONST_AND_COPIES to its original state, stopping when we hit a
816 NULL marker. */
6de9cd9a
DN
817
818static void
b5fefcf6 819restore_vars_to_original_value (void)
6de9cd9a 820{
b5fefcf6 821 while (VARRAY_ACTIVE_SIZE (const_and_copies_stack) > 0)
6de9cd9a
DN
822 {
823 tree prev_value, dest;
824
b5fefcf6
JL
825 dest = VARRAY_TOP_TREE (const_and_copies_stack);
826 VARRAY_POP (const_and_copies_stack);
6de9cd9a 827
b5fefcf6
JL
828 if (dest == NULL)
829 break;
830
831 prev_value = VARRAY_TOP_TREE (const_and_copies_stack);
832 VARRAY_POP (const_and_copies_stack);
833
3aecd08b 834 SSA_NAME_VALUE (dest) = prev_value;
6de9cd9a
DN
835 }
836}
837
838/* Similar to restore_vars_to_original_value, except that it restores
839 CURRDEFS to its original value. */
840static void
9fae925b 841restore_currdefs_to_original_value (void)
6de9cd9a 842{
6de9cd9a 843 /* Restore CURRDEFS to its original state. */
9fae925b 844 while (VARRAY_ACTIVE_SIZE (block_defs_stack) > 0)
6de9cd9a 845 {
9fae925b 846 tree tmp = VARRAY_TOP_TREE (block_defs_stack);
6de9cd9a
DN
847 tree saved_def, var;
848
9fae925b
JL
849 VARRAY_POP (block_defs_stack);
850
851 if (tmp == NULL_TREE)
852 break;
6de9cd9a
DN
853
854 /* If we recorded an SSA_NAME, then make the SSA_NAME the current
855 definition of its underlying variable. If we recorded anything
856 else, it must have been an _DECL node and its current reaching
857 definition must have been NULL. */
858 if (TREE_CODE (tmp) == SSA_NAME)
859 {
860 saved_def = tmp;
861 var = SSA_NAME_VAR (saved_def);
862 }
863 else
864 {
865 saved_def = NULL;
866 var = tmp;
867 }
868
869 var_ann (var)->current_def = saved_def;
870 }
871}
872
873/* We have finished processing the dominator children of BB, perform
874 any finalization actions in preparation for leaving this node in
875 the dominator tree. */
876
877static void
878dom_opt_finalize_block (struct dom_walk_data *walk_data, basic_block bb)
879{
6de9cd9a
DN
880 tree last;
881
882 /* If we are at a leaf node in the dominator graph, see if we can thread
883 the edge from BB through its successor.
884
885 Do this before we remove entries from our equivalence tables. */
628f6a4e
BE
886 if (EDGE_COUNT (bb->succs) == 1
887 && (EDGE_SUCC (bb, 0)->flags & EDGE_ABNORMAL) == 0
888 && (get_immediate_dominator (CDI_DOMINATORS, EDGE_SUCC (bb, 0)->dest) != bb
889 || phi_nodes (EDGE_SUCC (bb, 0)->dest)))
6de9cd9a
DN
890
891 {
628f6a4e 892 thread_across_edge (walk_data, EDGE_SUCC (bb, 0));
6de9cd9a
DN
893 }
894 else if ((last = last_stmt (bb))
895 && TREE_CODE (last) == COND_EXPR
6615c446 896 && (COMPARISON_CLASS_P (COND_EXPR_COND (last))
6de9cd9a 897 || TREE_CODE (COND_EXPR_COND (last)) == SSA_NAME)
628f6a4e
BE
898 && EDGE_COUNT (bb->succs) == 2
899 && (EDGE_SUCC (bb, 0)->flags & EDGE_ABNORMAL) == 0
900 && (EDGE_SUCC (bb, 1)->flags & EDGE_ABNORMAL) == 0)
6de9cd9a
DN
901 {
902 edge true_edge, false_edge;
903 tree cond, inverted = NULL;
904 enum tree_code cond_code;
905
906 extract_true_false_edges_from_block (bb, &true_edge, &false_edge);
907
908 cond = COND_EXPR_COND (last);
909 cond_code = TREE_CODE (cond);
910
6615c446 911 if (TREE_CODE_CLASS (cond_code) == tcc_comparison)
6de9cd9a
DN
912 inverted = invert_truthvalue (cond);
913
914 /* If the THEN arm is the end of a dominator tree or has PHI nodes,
915 then try to thread through its edge. */
916 if (get_immediate_dominator (CDI_DOMINATORS, true_edge->dest) != bb
917 || phi_nodes (true_edge->dest))
918 {
48732f23
JL
919 /* Push a marker onto the available expression stack so that we
920 unwind any expressions related to the TRUE arm before processing
921 the false arm below. */
922 VARRAY_PUSH_TREE (avail_exprs_stack, NULL_TREE);
9fae925b 923 VARRAY_PUSH_TREE (block_defs_stack, NULL_TREE);
b5fefcf6 924 VARRAY_PUSH_TREE (const_and_copies_stack, NULL_TREE);
48732f23 925
6de9cd9a 926 /* Record any equivalences created by following this edge. */
6615c446 927 if (TREE_CODE_CLASS (cond_code) == tcc_comparison)
6de9cd9a 928 {
48732f23
JL
929 record_cond (cond, boolean_true_node);
930 record_dominating_conditions (cond);
931 record_cond (inverted, boolean_false_node);
6de9cd9a
DN
932 }
933 else if (cond_code == SSA_NAME)
b5fefcf6 934 record_const_or_copy (cond, boolean_true_node);
6de9cd9a
DN
935
936 /* Now thread the edge. */
937 thread_across_edge (walk_data, true_edge);
938
939 /* And restore the various tables to their state before
940 we threaded this edge. */
48732f23 941 remove_local_expressions_from_table ();
b5fefcf6 942 restore_vars_to_original_value ();
9fae925b 943 restore_currdefs_to_original_value ();
6de9cd9a
DN
944 }
945
946 /* Similarly for the ELSE arm. */
947 if (get_immediate_dominator (CDI_DOMINATORS, false_edge->dest) != bb
948 || phi_nodes (false_edge->dest))
949 {
950 /* Record any equivalences created by following this edge. */
6615c446 951 if (TREE_CODE_CLASS (cond_code) == tcc_comparison)
6de9cd9a 952 {
48732f23
JL
953 record_cond (cond, boolean_false_node);
954 record_cond (inverted, boolean_true_node);
955 record_dominating_conditions (inverted);
6de9cd9a
DN
956 }
957 else if (cond_code == SSA_NAME)
b5fefcf6 958 record_const_or_copy (cond, boolean_false_node);
6de9cd9a
DN
959
960 thread_across_edge (walk_data, false_edge);
961
962 /* No need to remove local expressions from our tables
963 or restore vars to their original value as that will
964 be done immediately below. */
965 }
966 }
967
48732f23 968 remove_local_expressions_from_table ();
fdabe5c2 969 restore_nonzero_vars_to_original_value ();
b5fefcf6 970 restore_vars_to_original_value ();
9fae925b 971 restore_currdefs_to_original_value ();
6de9cd9a
DN
972
973 /* Remove VRP records associated with this basic block. They are no
974 longer valid.
975
976 To be efficient, we note which variables have had their values
977 constrained in this block. So walk over each variable in the
978 VRP_VARIABLEs array. */
fdabe5c2 979 while (VARRAY_ACTIVE_SIZE (vrp_variables_stack) > 0)
6de9cd9a 980 {
fdabe5c2 981 tree var = VARRAY_TOP_TREE (vrp_variables_stack);
b8545fbf 982 struct vrp_hash_elt vrp_hash_elt, *vrp_hash_elt_p;
23530866 983 void **slot;
6de9cd9a
DN
984
985 /* Each variable has a stack of value range records. We want to
986 invalidate those associated with our basic block. So we walk
987 the array backwards popping off records associated with our
988 block. Once we hit a record not associated with our block
989 we are done. */
fdabe5c2
JL
990 varray_type var_vrp_records;
991
992 VARRAY_POP (vrp_variables_stack);
993
994 if (var == NULL)
995 break;
6de9cd9a 996
23530866
JL
997 vrp_hash_elt.var = var;
998 vrp_hash_elt.records = NULL;
999
1000 slot = htab_find_slot (vrp_data, &vrp_hash_elt, NO_INSERT);
1001
b8545fbf
JL
1002 vrp_hash_elt_p = (struct vrp_hash_elt *) *slot;
1003 var_vrp_records = vrp_hash_elt_p->records;
1004
6de9cd9a
DN
1005 while (VARRAY_ACTIVE_SIZE (var_vrp_records) > 0)
1006 {
1007 struct vrp_element *element
1008 = (struct vrp_element *)VARRAY_TOP_GENERIC_PTR (var_vrp_records);
1009
1010 if (element->bb != bb)
1011 break;
1012
1013 VARRAY_POP (var_vrp_records);
1014 }
6de9cd9a
DN
1015 }
1016
a6e1aa26
JL
1017 /* If we queued any statements to rescan in this block, then
1018 go ahead and rescan them now. */
1019 while (VARRAY_ACTIVE_SIZE (stmts_to_rescan) > 0)
6de9cd9a 1020 {
a6e1aa26
JL
1021 tree stmt = VARRAY_TOP_TREE (stmts_to_rescan);
1022 basic_block stmt_bb = bb_for_stmt (stmt);
1023
1024 if (stmt_bb != bb)
1025 break;
1026
1027 VARRAY_POP (stmts_to_rescan);
6de9cd9a
DN
1028 mark_new_vars_to_rename (stmt, vars_to_rename);
1029 }
1030}
1031
1032/* PHI nodes can create equivalences too.
1033
1034 Ignoring any alternatives which are the same as the result, if
1035 all the alternatives are equal, then the PHI node creates an
dd747311
JL
1036 equivalence.
1037
1038 Additionally, if all the PHI alternatives are known to have a nonzero
1039 value, then the result of this PHI is known to have a nonzero value,
1040 even if we do not know its exact value. */
1041
6de9cd9a 1042static void
9fae925b
JL
1043record_equivalences_from_phis (struct dom_walk_data *walk_data ATTRIBUTE_UNUSED,
1044 basic_block bb)
6de9cd9a 1045{
6de9cd9a
DN
1046 tree phi;
1047
17192884 1048 for (phi = phi_nodes (bb); phi; phi = PHI_CHAIN (phi))
6de9cd9a
DN
1049 {
1050 tree lhs = PHI_RESULT (phi);
1051 tree rhs = NULL;
1052 int i;
1053
1054 for (i = 0; i < PHI_NUM_ARGS (phi); i++)
1055 {
1056 tree t = PHI_ARG_DEF (phi, i);
1057
1058 if (TREE_CODE (t) == SSA_NAME || is_gimple_min_invariant (t))
1059 {
1060 /* Ignore alternatives which are the same as our LHS. */
1061 if (operand_equal_p (lhs, t, 0))
1062 continue;
1063
1064 /* If we have not processed an alternative yet, then set
1065 RHS to this alternative. */
1066 if (rhs == NULL)
1067 rhs = t;
1068 /* If we have processed an alternative (stored in RHS), then
1069 see if it is equal to this one. If it isn't, then stop
1070 the search. */
1071 else if (! operand_equal_p (rhs, t, 0))
1072 break;
1073 }
1074 else
1075 break;
1076 }
1077
1078 /* If we had no interesting alternatives, then all the RHS alternatives
1079 must have been the same as LHS. */
1080 if (!rhs)
1081 rhs = lhs;
1082
1083 /* If we managed to iterate through each PHI alternative without
1084 breaking out of the loop, then we have a PHI which may create
1085 a useful equivalence. We do not need to record unwind data for
1086 this, since this is a true assignment and not an equivalence
1ea7e6ad 1087 inferred from a comparison. All uses of this ssa name are dominated
6de9cd9a
DN
1088 by this assignment, so unwinding just costs time and space. */
1089 if (i == PHI_NUM_ARGS (phi)
1090 && may_propagate_copy (lhs, rhs))
3aecd08b 1091 SSA_NAME_VALUE (lhs) = rhs;
6de9cd9a 1092
dd747311
JL
1093 /* Now see if we know anything about the nonzero property for the
1094 result of this PHI. */
1095 for (i = 0; i < PHI_NUM_ARGS (phi); i++)
1096 {
1097 if (!PHI_ARG_NONZERO (phi, i))
1098 break;
1099 }
1100
1101 if (i == PHI_NUM_ARGS (phi))
1102 bitmap_set_bit (nonzero_vars, SSA_NAME_VERSION (PHI_RESULT (phi)));
1103
9fae925b 1104 register_new_def (lhs, &block_defs_stack);
6de9cd9a
DN
1105 }
1106}
1107
28c008bb
JL
1108/* Ignoring loop backedges, if BB has precisely one incoming edge then
1109 return that edge. Otherwise return NULL. */
1110static edge
1111single_incoming_edge_ignoring_loop_edges (basic_block bb)
1112{
1113 edge retval = NULL;
1114 edge e;
628f6a4e 1115 edge_iterator ei;
28c008bb 1116
628f6a4e 1117 FOR_EACH_EDGE (e, ei, bb->preds)
28c008bb
JL
1118 {
1119 /* A loop back edge can be identified by the destination of
1120 the edge dominating the source of the edge. */
1121 if (dominated_by_p (CDI_DOMINATORS, e->src, e->dest))
1122 continue;
1123
1124 /* If we have already seen a non-loop edge, then we must have
1125 multiple incoming non-loop edges and thus we return NULL. */
1126 if (retval)
1127 return NULL;
1128
1129 /* This is the first non-loop incoming edge we have found. Record
1130 it. */
1131 retval = e;
1132 }
1133
1134 return retval;
1135}
1136
6de9cd9a
DN
1137/* Record any equivalences created by the incoming edge to BB. If BB
1138 has more than one incoming edge, then no equivalence is created. */
1139
1140static void
fdabe5c2 1141record_equivalences_from_incoming_edge (struct dom_walk_data *walk_data ATTRIBUTE_UNUSED,
6de9cd9a
DN
1142 basic_block bb)
1143{
1144 int edge_flags;
1145 basic_block parent;
1146 struct eq_expr_value eq_expr_value;
1147 tree parent_block_last_stmt = NULL;
6de9cd9a
DN
1148
1149 /* If our parent block ended with a control statment, then we may be
1150 able to record some equivalences based on which outgoing edge from
1151 the parent was followed. */
1152 parent = get_immediate_dominator (CDI_DOMINATORS, bb);
1153 if (parent)
1154 {
1155 parent_block_last_stmt = last_stmt (parent);
1156 if (parent_block_last_stmt && !is_ctrl_stmt (parent_block_last_stmt))
1157 parent_block_last_stmt = NULL;
1158 }
1159
1160 eq_expr_value.src = NULL;
1161 eq_expr_value.dst = NULL;
1162
28c008bb
JL
1163 /* If we have a single predecessor (ignoring loop backedges), then extract
1164 EDGE_FLAGS from the single incoming edge. Otherwise just return as
1165 there is nothing to do. */
628f6a4e 1166 if (EDGE_COUNT (bb->preds) >= 1
28c008bb 1167 && parent_block_last_stmt)
6de9cd9a 1168 {
28c008bb
JL
1169 edge e = single_incoming_edge_ignoring_loop_edges (bb);
1170 if (e && bb_for_stmt (parent_block_last_stmt) == e->src)
1171 edge_flags = e->flags;
1172 else
1173 return;
6de9cd9a
DN
1174 }
1175 else
28c008bb 1176 return;
6de9cd9a
DN
1177
1178 /* If our parent block ended in a COND_EXPR, add any equivalences
1179 created by the COND_EXPR to the hash table and initialize
1180 EQ_EXPR_VALUE appropriately.
1181
1182 EQ_EXPR_VALUE is an assignment expression created when BB's immediate
1183 dominator ends in a COND_EXPR statement whose predicate is of the form
1184 'VAR == VALUE', where VALUE may be another variable or a constant.
1185 This is used to propagate VALUE on the THEN_CLAUSE of that
1186 conditional. This assignment is inserted in CONST_AND_COPIES so that
1187 the copy and constant propagator can find more propagation
1188 opportunities. */
28c008bb 1189 if (TREE_CODE (parent_block_last_stmt) == COND_EXPR
6de9cd9a
DN
1190 && (edge_flags & (EDGE_TRUE_VALUE | EDGE_FALSE_VALUE)))
1191 eq_expr_value = get_eq_expr_value (parent_block_last_stmt,
1192 (edge_flags & EDGE_TRUE_VALUE) != 0,
fdabe5c2 1193 bb);
1c052514
SB
1194 /* Similarly when the parent block ended in a SWITCH_EXPR.
1195 We can only know the value of the switch's condition if the dominator
1196 parent is also the only predecessor of this block. */
628f6a4e 1197 else if (EDGE_PRED (bb, 0)->src == parent
6de9cd9a
DN
1198 && TREE_CODE (parent_block_last_stmt) == SWITCH_EXPR)
1199 {
1200 tree switch_cond = SWITCH_COND (parent_block_last_stmt);
1201
1202 /* If the switch's condition is an SSA variable, then we may
1203 know its value at each of the case labels. */
1204 if (TREE_CODE (switch_cond) == SSA_NAME)
1205 {
1206 tree switch_vec = SWITCH_LABELS (parent_block_last_stmt);
1207 size_t i, n = TREE_VEC_LENGTH (switch_vec);
1208 int case_count = 0;
1209 tree match_case = NULL_TREE;
1210
1211 /* Search the case labels for those whose destination is
1212 the current basic block. */
1213 for (i = 0; i < n; ++i)
1214 {
1215 tree elt = TREE_VEC_ELT (switch_vec, i);
1216 if (label_to_block (CASE_LABEL (elt)) == bb)
1217 {
1c052514 1218 if (++case_count > 1 || CASE_HIGH (elt))
6de9cd9a
DN
1219 break;
1220 match_case = elt;
1221 }
1222 }
1223
1224 /* If we encountered precisely one CASE_LABEL_EXPR and it
1225 was not the default case, or a case range, then we know
1226 the exact value of SWITCH_COND which caused us to get to
1227 this block. Record that equivalence in EQ_EXPR_VALUE. */
1228 if (case_count == 1
1c052514 1229 && match_case
6de9cd9a
DN
1230 && CASE_LOW (match_case)
1231 && !CASE_HIGH (match_case))
1232 {
1233 eq_expr_value.dst = switch_cond;
e9ea8bd5
RS
1234 eq_expr_value.src = fold_convert (TREE_TYPE (switch_cond),
1235 CASE_LOW (match_case));
6de9cd9a
DN
1236 }
1237 }
1238 }
1239
1240 /* If EQ_EXPR_VALUE (VAR == VALUE) is given, register the VALUE as a
1241 new value for VAR, so that occurrences of VAR can be replaced with
1242 VALUE while re-writing the THEN arm of a COND_EXPR. */
1243 if (eq_expr_value.src && eq_expr_value.dst)
b5fefcf6 1244 record_equality (eq_expr_value.dst, eq_expr_value.src);
6de9cd9a
DN
1245}
1246
1247/* Dump SSA statistics on FILE. */
1248
1249void
1250dump_dominator_optimization_stats (FILE *file)
1251{
1252 long n_exprs;
1253
1254 fprintf (file, "Total number of statements: %6ld\n\n",
1255 opt_stats.num_stmts);
1256 fprintf (file, "Exprs considered for dominator optimizations: %6ld\n",
1257 opt_stats.num_exprs_considered);
1258
1259 n_exprs = opt_stats.num_exprs_considered;
1260 if (n_exprs == 0)
1261 n_exprs = 1;
1262
1263 fprintf (file, " Redundant expressions eliminated: %6ld (%.0f%%)\n",
1264 opt_stats.num_re, PERCENT (opt_stats.num_re,
1265 n_exprs));
1266
1267 fprintf (file, "\nHash table statistics:\n");
1268
1269 fprintf (file, " avail_exprs: ");
1270 htab_statistics (file, avail_exprs);
1271}
1272
1273
1274/* Dump SSA statistics on stderr. */
1275
1276void
1277debug_dominator_optimization_stats (void)
1278{
1279 dump_dominator_optimization_stats (stderr);
1280}
1281
1282
1283/* Dump statistics for the hash table HTAB. */
1284
1285static void
1286htab_statistics (FILE *file, htab_t htab)
1287{
1288 fprintf (file, "size %ld, %ld elements, %f collision/search ratio\n",
1289 (long) htab_size (htab),
1290 (long) htab_elements (htab),
1291 htab_collisions (htab));
1292}
1293
1294/* Record the fact that VAR has a nonzero value, though we may not know
1295 its exact value. Note that if VAR is already known to have a nonzero
1296 value, then we do nothing. */
1297
1298static void
fdabe5c2 1299record_var_is_nonzero (tree var)
6de9cd9a
DN
1300{
1301 int indx = SSA_NAME_VERSION (var);
1302
1303 if (bitmap_bit_p (nonzero_vars, indx))
1304 return;
1305
1306 /* Mark it in the global table. */
1307 bitmap_set_bit (nonzero_vars, indx);
1308
1309 /* Record this SSA_NAME so that we can reset the global table
1310 when we leave this block. */
fdabe5c2 1311 VARRAY_PUSH_TREE (nonzero_vars_stack, var);
6de9cd9a
DN
1312}
1313
1314/* Enter a statement into the true/false expression hash table indicating
1315 that the condition COND has the value VALUE. */
1316
1317static void
48732f23 1318record_cond (tree cond, tree value)
6de9cd9a
DN
1319{
1320 struct expr_hash_elt *element = xmalloc (sizeof (struct expr_hash_elt));
1321 void **slot;
1322
1323 initialize_hash_element (cond, value, element);
1324
1325 slot = htab_find_slot_with_hash (avail_exprs, (void *)element,
1326 element->hash, true);
1327 if (*slot == NULL)
1328 {
1329 *slot = (void *) element;
48732f23 1330 VARRAY_PUSH_TREE (avail_exprs_stack, cond);
6de9cd9a
DN
1331 }
1332 else
1333 free (element);
1334}
1335
d2d8936f
JL
1336/* COND is a condition which is known to be true. Record variants of
1337 COND which must also be true.
1338
1339 For example, if a < b is true, then a <= b must also be true. */
1340
1341static void
48732f23 1342record_dominating_conditions (tree cond)
d2d8936f
JL
1343{
1344 switch (TREE_CODE (cond))
1345 {
1346 case LT_EXPR:
1347 record_cond (build2 (LE_EXPR, boolean_type_node,
1348 TREE_OPERAND (cond, 0),
1349 TREE_OPERAND (cond, 1)),
48732f23 1350 boolean_true_node);
d2d8936f
JL
1351 record_cond (build2 (ORDERED_EXPR, boolean_type_node,
1352 TREE_OPERAND (cond, 0),
1353 TREE_OPERAND (cond, 1)),
48732f23 1354 boolean_true_node);
d2d8936f
JL
1355 record_cond (build2 (NE_EXPR, boolean_type_node,
1356 TREE_OPERAND (cond, 0),
1357 TREE_OPERAND (cond, 1)),
48732f23 1358 boolean_true_node);
d2d8936f
JL
1359 record_cond (build2 (LTGT_EXPR, boolean_type_node,
1360 TREE_OPERAND (cond, 0),
1361 TREE_OPERAND (cond, 1)),
48732f23 1362 boolean_true_node);
d2d8936f
JL
1363 break;
1364
1365 case GT_EXPR:
1366 record_cond (build2 (GE_EXPR, boolean_type_node,
1367 TREE_OPERAND (cond, 0),
1368 TREE_OPERAND (cond, 1)),
48732f23 1369 boolean_true_node);
d2d8936f
JL
1370 record_cond (build2 (ORDERED_EXPR, boolean_type_node,
1371 TREE_OPERAND (cond, 0),
1372 TREE_OPERAND (cond, 1)),
48732f23 1373 boolean_true_node);
d2d8936f
JL
1374 record_cond (build2 (NE_EXPR, boolean_type_node,
1375 TREE_OPERAND (cond, 0),
1376 TREE_OPERAND (cond, 1)),
48732f23 1377 boolean_true_node);
d2d8936f
JL
1378 record_cond (build2 (LTGT_EXPR, boolean_type_node,
1379 TREE_OPERAND (cond, 0),
1380 TREE_OPERAND (cond, 1)),
48732f23 1381 boolean_true_node);
d2d8936f
JL
1382 break;
1383
1384 case GE_EXPR:
1385 case LE_EXPR:
1386 record_cond (build2 (ORDERED_EXPR, boolean_type_node,
1387 TREE_OPERAND (cond, 0),
1388 TREE_OPERAND (cond, 1)),
48732f23 1389 boolean_true_node);
d2d8936f
JL
1390 break;
1391
1392 case EQ_EXPR:
1393 record_cond (build2 (ORDERED_EXPR, boolean_type_node,
1394 TREE_OPERAND (cond, 0),
1395 TREE_OPERAND (cond, 1)),
48732f23 1396 boolean_true_node);
d2d8936f
JL
1397 record_cond (build2 (LE_EXPR, boolean_type_node,
1398 TREE_OPERAND (cond, 0),
1399 TREE_OPERAND (cond, 1)),
48732f23 1400 boolean_true_node);
d2d8936f
JL
1401 record_cond (build2 (GE_EXPR, boolean_type_node,
1402 TREE_OPERAND (cond, 0),
1403 TREE_OPERAND (cond, 1)),
48732f23 1404 boolean_true_node);
d2d8936f
JL
1405 break;
1406
1407 case UNORDERED_EXPR:
1408 record_cond (build2 (NE_EXPR, boolean_type_node,
1409 TREE_OPERAND (cond, 0),
1410 TREE_OPERAND (cond, 1)),
48732f23 1411 boolean_true_node);
d2d8936f
JL
1412 record_cond (build2 (UNLE_EXPR, boolean_type_node,
1413 TREE_OPERAND (cond, 0),
1414 TREE_OPERAND (cond, 1)),
48732f23 1415 boolean_true_node);
d2d8936f
JL
1416 record_cond (build2 (UNGE_EXPR, boolean_type_node,
1417 TREE_OPERAND (cond, 0),
1418 TREE_OPERAND (cond, 1)),
48732f23 1419 boolean_true_node);
d2d8936f
JL
1420 record_cond (build2 (UNEQ_EXPR, boolean_type_node,
1421 TREE_OPERAND (cond, 0),
1422 TREE_OPERAND (cond, 1)),
48732f23 1423 boolean_true_node);
d2d8936f
JL
1424 record_cond (build2 (UNLT_EXPR, boolean_type_node,
1425 TREE_OPERAND (cond, 0),
1426 TREE_OPERAND (cond, 1)),
48732f23 1427 boolean_true_node);
d2d8936f
JL
1428 record_cond (build2 (UNGT_EXPR, boolean_type_node,
1429 TREE_OPERAND (cond, 0),
1430 TREE_OPERAND (cond, 1)),
48732f23 1431 boolean_true_node);
d2d8936f
JL
1432 break;
1433
1434 case UNLT_EXPR:
1435 record_cond (build2 (UNLE_EXPR, boolean_type_node,
1436 TREE_OPERAND (cond, 0),
1437 TREE_OPERAND (cond, 1)),
48732f23 1438 boolean_true_node);
d2d8936f
JL
1439 record_cond (build2 (NE_EXPR, boolean_type_node,
1440 TREE_OPERAND (cond, 0),
1441 TREE_OPERAND (cond, 1)),
48732f23 1442 boolean_true_node);
d2d8936f
JL
1443 break;
1444
1445 case UNGT_EXPR:
1446 record_cond (build2 (UNGE_EXPR, boolean_type_node,
1447 TREE_OPERAND (cond, 0),
1448 TREE_OPERAND (cond, 1)),
48732f23 1449 boolean_true_node);
d2d8936f
JL
1450 record_cond (build2 (NE_EXPR, boolean_type_node,
1451 TREE_OPERAND (cond, 0),
1452 TREE_OPERAND (cond, 1)),
48732f23 1453 boolean_true_node);
d2d8936f
JL
1454 break;
1455
1456 case UNEQ_EXPR:
1457 record_cond (build2 (UNLE_EXPR, boolean_type_node,
1458 TREE_OPERAND (cond, 0),
1459 TREE_OPERAND (cond, 1)),
48732f23 1460 boolean_true_node);
d2d8936f
JL
1461 record_cond (build2 (UNGE_EXPR, boolean_type_node,
1462 TREE_OPERAND (cond, 0),
1463 TREE_OPERAND (cond, 1)),
48732f23 1464 boolean_true_node);
d2d8936f
JL
1465 break;
1466
1467 case LTGT_EXPR:
1468 record_cond (build2 (NE_EXPR, boolean_type_node,
1469 TREE_OPERAND (cond, 0),
1470 TREE_OPERAND (cond, 1)),
48732f23 1471 boolean_true_node);
d2d8936f
JL
1472 record_cond (build2 (ORDERED_EXPR, boolean_type_node,
1473 TREE_OPERAND (cond, 0),
1474 TREE_OPERAND (cond, 1)),
48732f23 1475 boolean_true_node);
d2d8936f
JL
1476
1477 default:
1478 break;
1479 }
1480}
1481
6de9cd9a
DN
1482/* A helper function for record_const_or_copy and record_equality.
1483 Do the work of recording the value and undo info. */
1484
1485static void
b5fefcf6 1486record_const_or_copy_1 (tree x, tree y, tree prev_x)
6de9cd9a 1487{
3aecd08b 1488 SSA_NAME_VALUE (x) = y;
6de9cd9a 1489
b5fefcf6
JL
1490 VARRAY_PUSH_TREE (const_and_copies_stack, prev_x);
1491 VARRAY_PUSH_TREE (const_and_copies_stack, x);
6de9cd9a
DN
1492}
1493
1494/* Record that X is equal to Y in const_and_copies. Record undo
1495 information in the block-local varray. */
1496
1497static void
b5fefcf6 1498record_const_or_copy (tree x, tree y)
6de9cd9a 1499{
3aecd08b 1500 tree prev_x = SSA_NAME_VALUE (x);
6de9cd9a
DN
1501
1502 if (TREE_CODE (y) == SSA_NAME)
1503 {
3aecd08b 1504 tree tmp = SSA_NAME_VALUE (y);
6de9cd9a
DN
1505 if (tmp)
1506 y = tmp;
1507 }
1508
b5fefcf6 1509 record_const_or_copy_1 (x, y, prev_x);
6de9cd9a
DN
1510}
1511
1512/* Similarly, but assume that X and Y are the two operands of an EQ_EXPR.
1513 This constrains the cases in which we may treat this as assignment. */
1514
1515static void
b5fefcf6 1516record_equality (tree x, tree y)
6de9cd9a
DN
1517{
1518 tree prev_x = NULL, prev_y = NULL;
1519
1520 if (TREE_CODE (x) == SSA_NAME)
3aecd08b 1521 prev_x = SSA_NAME_VALUE (x);
6de9cd9a 1522 if (TREE_CODE (y) == SSA_NAME)
3aecd08b 1523 prev_y = SSA_NAME_VALUE (y);
6de9cd9a
DN
1524
1525 /* If one of the previous values is invariant, then use that.
1526 Otherwise it doesn't matter which value we choose, just so
1527 long as we canonicalize on one value. */
1528 if (TREE_INVARIANT (y))
1529 ;
1530 else if (TREE_INVARIANT (x))
1531 prev_x = x, x = y, y = prev_x, prev_x = prev_y;
1532 else if (prev_x && TREE_INVARIANT (prev_x))
1533 x = y, y = prev_x, prev_x = prev_y;
3aecd08b 1534 else if (prev_y && TREE_CODE (prev_y) != VALUE_HANDLE)
6de9cd9a
DN
1535 y = prev_y;
1536
1537 /* After the swapping, we must have one SSA_NAME. */
1538 if (TREE_CODE (x) != SSA_NAME)
1539 return;
1540
1541 /* For IEEE, -0.0 == 0.0, so we don't necessarily know the sign of a
1542 variable compared against zero. If we're honoring signed zeros,
1543 then we cannot record this value unless we know that the value is
1ea7e6ad 1544 nonzero. */
6de9cd9a
DN
1545 if (HONOR_SIGNED_ZEROS (TYPE_MODE (TREE_TYPE (x)))
1546 && (TREE_CODE (y) != REAL_CST
1547 || REAL_VALUES_EQUAL (dconst0, TREE_REAL_CST (y))))
1548 return;
1549
b5fefcf6 1550 record_const_or_copy_1 (x, y, prev_x);
6de9cd9a
DN
1551}
1552
01d8c00b
FJ
1553/* Return true, if it is ok to do folding of an associative expression.
1554 EXP is the tree for the associative expression. */
1555
1556static inline bool
1557unsafe_associative_fp_binop (tree exp)
1558{
1559 enum tree_code code = TREE_CODE (exp);
1560 return !(!flag_unsafe_math_optimizations
1561 && (code == MULT_EXPR || code == PLUS_EXPR)
1562 && FLOAT_TYPE_P (TREE_TYPE (exp)));
1563}
1564
6de9cd9a
DN
1565/* STMT is a MODIFY_EXPR for which we were unable to find RHS in the
1566 hash tables. Try to simplify the RHS using whatever equivalences
1567 we may have recorded.
1568
1569 If we are able to simplify the RHS, then lookup the simplified form in
1570 the hash table and return the result. Otherwise return NULL. */
1571
1572static tree
1573simplify_rhs_and_lookup_avail_expr (struct dom_walk_data *walk_data,
68b9f53b 1574 tree stmt, int insert)
6de9cd9a
DN
1575{
1576 tree rhs = TREE_OPERAND (stmt, 1);
1577 enum tree_code rhs_code = TREE_CODE (rhs);
1578 tree result = NULL;
6de9cd9a
DN
1579
1580 /* If we have lhs = ~x, look and see if we earlier had x = ~y.
1581 In which case we can change this statement to be lhs = y.
1582 Which can then be copy propagated.
1583
1584 Similarly for negation. */
1585 if ((rhs_code == BIT_NOT_EXPR || rhs_code == NEGATE_EXPR)
1586 && TREE_CODE (TREE_OPERAND (rhs, 0)) == SSA_NAME)
1587 {
1588 /* Get the definition statement for our RHS. */
1589 tree rhs_def_stmt = SSA_NAME_DEF_STMT (TREE_OPERAND (rhs, 0));
1590
1591 /* See if the RHS_DEF_STMT has the same form as our statement. */
1592 if (TREE_CODE (rhs_def_stmt) == MODIFY_EXPR
1593 && TREE_CODE (TREE_OPERAND (rhs_def_stmt, 1)) == rhs_code)
1594 {
1595 tree rhs_def_operand;
1596
1597 rhs_def_operand = TREE_OPERAND (TREE_OPERAND (rhs_def_stmt, 1), 0);
1598
1599 /* Verify that RHS_DEF_OPERAND is a suitable SSA variable. */
1600 if (TREE_CODE (rhs_def_operand) == SSA_NAME
1601 && ! SSA_NAME_OCCURS_IN_ABNORMAL_PHI (rhs_def_operand))
1602 result = update_rhs_and_lookup_avail_expr (stmt,
1603 rhs_def_operand,
6de9cd9a
DN
1604 insert);
1605 }
1606 }
1607
1608 /* If we have z = (x OP C1), see if we earlier had x = y OP C2.
1609 If OP is associative, create and fold (y OP C2) OP C1 which
1610 should result in (y OP C3), use that as the RHS for the
1611 assignment. Add minus to this, as we handle it specially below. */
1612 if ((associative_tree_code (rhs_code) || rhs_code == MINUS_EXPR)
1613 && TREE_CODE (TREE_OPERAND (rhs, 0)) == SSA_NAME
1614 && is_gimple_min_invariant (TREE_OPERAND (rhs, 1)))
1615 {
1616 tree rhs_def_stmt = SSA_NAME_DEF_STMT (TREE_OPERAND (rhs, 0));
1617
1618 /* See if the RHS_DEF_STMT has the same form as our statement. */
1619 if (TREE_CODE (rhs_def_stmt) == MODIFY_EXPR)
1620 {
1621 tree rhs_def_rhs = TREE_OPERAND (rhs_def_stmt, 1);
1622 enum tree_code rhs_def_code = TREE_CODE (rhs_def_rhs);
1623
01d8c00b 1624 if ((rhs_code == rhs_def_code && unsafe_associative_fp_binop (rhs))
6de9cd9a
DN
1625 || (rhs_code == PLUS_EXPR && rhs_def_code == MINUS_EXPR)
1626 || (rhs_code == MINUS_EXPR && rhs_def_code == PLUS_EXPR))
1627 {
1628 tree def_stmt_op0 = TREE_OPERAND (rhs_def_rhs, 0);
1629 tree def_stmt_op1 = TREE_OPERAND (rhs_def_rhs, 1);
1630
1631 if (TREE_CODE (def_stmt_op0) == SSA_NAME
1632 && ! SSA_NAME_OCCURS_IN_ABNORMAL_PHI (def_stmt_op0)
1633 && is_gimple_min_invariant (def_stmt_op1))
1634 {
1635 tree outer_const = TREE_OPERAND (rhs, 1);
1636 tree type = TREE_TYPE (TREE_OPERAND (stmt, 0));
1637 tree t;
1638
f05ef422
RH
1639 /* If we care about correct floating point results, then
1640 don't fold x + c1 - c2. Note that we need to take both
1641 the codes and the signs to figure this out. */
1642 if (FLOAT_TYPE_P (type)
1643 && !flag_unsafe_math_optimizations
1644 && (rhs_def_code == PLUS_EXPR
1645 || rhs_def_code == MINUS_EXPR))
1646 {
1647 bool neg = false;
1648
1649 neg ^= (rhs_code == MINUS_EXPR);
1650 neg ^= (rhs_def_code == MINUS_EXPR);
1651 neg ^= real_isneg (TREE_REAL_CST_PTR (outer_const));
1652 neg ^= real_isneg (TREE_REAL_CST_PTR (def_stmt_op1));
1653
1654 if (neg)
1655 goto dont_fold_assoc;
1656 }
1657
6de9cd9a
DN
1658 /* Ho hum. So fold will only operate on the outermost
1659 thingy that we give it, so we have to build the new
1660 expression in two pieces. This requires that we handle
1661 combinations of plus and minus. */
1662 if (rhs_def_code != rhs_code)
1663 {
1664 if (rhs_def_code == MINUS_EXPR)
1665 t = build (MINUS_EXPR, type, outer_const, def_stmt_op1);
1666 else
1667 t = build (MINUS_EXPR, type, def_stmt_op1, outer_const);
1668 rhs_code = PLUS_EXPR;
1669 }
1670 else if (rhs_def_code == MINUS_EXPR)
1671 t = build (PLUS_EXPR, type, def_stmt_op1, outer_const);
1672 else
1673 t = build (rhs_def_code, type, def_stmt_op1, outer_const);
1674 t = local_fold (t);
1675 t = build (rhs_code, type, def_stmt_op0, t);
1676 t = local_fold (t);
1677
1678 /* If the result is a suitable looking gimple expression,
1679 then use it instead of the original for STMT. */
1680 if (TREE_CODE (t) == SSA_NAME
6615c446 1681 || (UNARY_CLASS_P (t)
6de9cd9a 1682 && TREE_CODE (TREE_OPERAND (t, 0)) == SSA_NAME)
6615c446 1683 || ((BINARY_CLASS_P (t) || COMPARISON_CLASS_P (t))
6de9cd9a
DN
1684 && TREE_CODE (TREE_OPERAND (t, 0)) == SSA_NAME
1685 && is_gimple_val (TREE_OPERAND (t, 1))))
48732f23 1686 result = update_rhs_and_lookup_avail_expr (stmt, t, insert);
6de9cd9a
DN
1687 }
1688 }
1689 }
f05ef422 1690 dont_fold_assoc:;
6de9cd9a
DN
1691 }
1692
1693 /* Transform TRUNC_DIV_EXPR and TRUNC_MOD_EXPR into RSHIFT_EXPR
1694 and BIT_AND_EXPR respectively if the first operand is greater
1695 than zero and the second operand is an exact power of two. */
1696 if ((rhs_code == TRUNC_DIV_EXPR || rhs_code == TRUNC_MOD_EXPR)
1697 && INTEGRAL_TYPE_P (TREE_TYPE (TREE_OPERAND (rhs, 0)))
1698 && integer_pow2p (TREE_OPERAND (rhs, 1)))
1699 {
1700 tree val;
1701 tree op = TREE_OPERAND (rhs, 0);
1702
1703 if (TYPE_UNSIGNED (TREE_TYPE (op)))
1704 {
1705 val = integer_one_node;
1706 }
1707 else
1708 {
1709 tree dummy_cond = walk_data->global_data;
1710
1711 if (! dummy_cond)
1712 {
1713 dummy_cond = build (GT_EXPR, boolean_type_node,
1714 op, integer_zero_node);
1715 dummy_cond = build (COND_EXPR, void_type_node,
1716 dummy_cond, NULL, NULL);
1717 walk_data->global_data = dummy_cond;
1718 }
1719 else
1720 {
1721 TREE_SET_CODE (TREE_OPERAND (dummy_cond, 0), GT_EXPR);
1722 TREE_OPERAND (TREE_OPERAND (dummy_cond, 0), 0) = op;
1723 TREE_OPERAND (TREE_OPERAND (dummy_cond, 0), 1)
1724 = integer_zero_node;
1725 }
48732f23 1726 val = simplify_cond_and_lookup_avail_expr (dummy_cond, NULL, false);
6de9cd9a
DN
1727 }
1728
1729 if (val && integer_onep (val))
1730 {
1731 tree t;
1732 tree op0 = TREE_OPERAND (rhs, 0);
1733 tree op1 = TREE_OPERAND (rhs, 1);
1734
1735 if (rhs_code == TRUNC_DIV_EXPR)
1736 t = build (RSHIFT_EXPR, TREE_TYPE (op0), op0,
7d60be94 1737 build_int_cst (NULL_TREE, tree_log2 (op1)));
6de9cd9a
DN
1738 else
1739 t = build (BIT_AND_EXPR, TREE_TYPE (op0), op0,
1740 local_fold (build (MINUS_EXPR, TREE_TYPE (op1),
1741 op1, integer_one_node)));
1742
48732f23 1743 result = update_rhs_and_lookup_avail_expr (stmt, t, insert);
6de9cd9a
DN
1744 }
1745 }
1746
1747 /* Transform ABS (X) into X or -X as appropriate. */
1748 if (rhs_code == ABS_EXPR
1749 && INTEGRAL_TYPE_P (TREE_TYPE (TREE_OPERAND (rhs, 0))))
1750 {
1751 tree val;
1752 tree op = TREE_OPERAND (rhs, 0);
1753 tree type = TREE_TYPE (op);
1754
1755 if (TYPE_UNSIGNED (type))
1756 {
1757 val = integer_zero_node;
1758 }
1759 else
1760 {
1761 tree dummy_cond = walk_data->global_data;
1762
1763 if (! dummy_cond)
1764 {
14bc8dc2 1765 dummy_cond = build (LE_EXPR, boolean_type_node,
6de9cd9a
DN
1766 op, integer_zero_node);
1767 dummy_cond = build (COND_EXPR, void_type_node,
1768 dummy_cond, NULL, NULL);
1769 walk_data->global_data = dummy_cond;
1770 }
1771 else
1772 {
14bc8dc2 1773 TREE_SET_CODE (TREE_OPERAND (dummy_cond, 0), LE_EXPR);
6de9cd9a
DN
1774 TREE_OPERAND (TREE_OPERAND (dummy_cond, 0), 0) = op;
1775 TREE_OPERAND (TREE_OPERAND (dummy_cond, 0), 1)
5212068f 1776 = build_int_cst (type, 0);
6de9cd9a 1777 }
48732f23 1778 val = simplify_cond_and_lookup_avail_expr (dummy_cond, NULL, false);
14bc8dc2
JL
1779
1780 if (!val)
1781 {
1782 TREE_SET_CODE (TREE_OPERAND (dummy_cond, 0), GE_EXPR);
1783 TREE_OPERAND (TREE_OPERAND (dummy_cond, 0), 0) = op;
1784 TREE_OPERAND (TREE_OPERAND (dummy_cond, 0), 1)
5212068f 1785 = build_int_cst (type, 0);
14bc8dc2
JL
1786
1787 val = simplify_cond_and_lookup_avail_expr (dummy_cond,
14bc8dc2
JL
1788 NULL, false);
1789
1790 if (val)
1791 {
1792 if (integer_zerop (val))
1793 val = integer_one_node;
1794 else if (integer_onep (val))
1795 val = integer_zero_node;
1796 }
1797 }
6de9cd9a
DN
1798 }
1799
1800 if (val
1801 && (integer_onep (val) || integer_zerop (val)))
1802 {
1803 tree t;
1804
1805 if (integer_onep (val))
1806 t = build1 (NEGATE_EXPR, TREE_TYPE (op), op);
1807 else
1808 t = op;
1809
48732f23 1810 result = update_rhs_and_lookup_avail_expr (stmt, t, insert);
6de9cd9a
DN
1811 }
1812 }
1813
1814 /* Optimize *"foo" into 'f'. This is done here rather than
1815 in fold to avoid problems with stuff like &*"foo". */
1816 if (TREE_CODE (rhs) == INDIRECT_REF || TREE_CODE (rhs) == ARRAY_REF)
1817 {
1818 tree t = fold_read_from_constant_string (rhs);
1819
1820 if (t)
48732f23 1821 result = update_rhs_and_lookup_avail_expr (stmt, t, insert);
6de9cd9a
DN
1822 }
1823
1824 return result;
1825}
1826
1827/* COND is a condition of the form:
1828
1829 x == const or x != const
1830
1831 Look back to x's defining statement and see if x is defined as
1832
1833 x = (type) y;
1834
1835 If const is unchanged if we convert it to type, then we can build
1836 the equivalent expression:
1837
1838
1839 y == const or y != const
1840
1841 Which may allow further optimizations.
1842
1843 Return the equivalent comparison or NULL if no such equivalent comparison
1844 was found. */
1845
1846static tree
1847find_equivalent_equality_comparison (tree cond)
1848{
1849 tree op0 = TREE_OPERAND (cond, 0);
1850 tree op1 = TREE_OPERAND (cond, 1);
1851 tree def_stmt = SSA_NAME_DEF_STMT (op0);
1852
1853 /* OP0 might have been a parameter, so first make sure it
1854 was defined by a MODIFY_EXPR. */
1855 if (def_stmt && TREE_CODE (def_stmt) == MODIFY_EXPR)
1856 {
1857 tree def_rhs = TREE_OPERAND (def_stmt, 1);
1858
1859 /* Now make sure the RHS of the MODIFY_EXPR is a typecast. */
1860 if ((TREE_CODE (def_rhs) == NOP_EXPR
1861 || TREE_CODE (def_rhs) == CONVERT_EXPR)
1862 && TREE_CODE (TREE_OPERAND (def_rhs, 0)) == SSA_NAME)
1863 {
1864 tree def_rhs_inner = TREE_OPERAND (def_rhs, 0);
1865 tree def_rhs_inner_type = TREE_TYPE (def_rhs_inner);
1866 tree new;
1867
1868 if (TYPE_PRECISION (def_rhs_inner_type)
1869 > TYPE_PRECISION (TREE_TYPE (def_rhs)))
1870 return NULL;
1871
1872 /* What we want to prove is that if we convert OP1 to
1873 the type of the object inside the NOP_EXPR that the
1874 result is still equivalent to SRC.
1875
1876 If that is true, the build and return new equivalent
1877 condition which uses the source of the typecast and the
1878 new constant (which has only changed its type). */
1879 new = build1 (TREE_CODE (def_rhs), def_rhs_inner_type, op1);
1880 new = local_fold (new);
1881 if (is_gimple_val (new) && tree_int_cst_equal (new, op1))
1882 return build (TREE_CODE (cond), TREE_TYPE (cond),
1883 def_rhs_inner, new);
1884 }
1885 }
1886 return NULL;
1887}
1888
1889/* STMT is a COND_EXPR for which we could not trivially determine its
1890 result. This routine attempts to find equivalent forms of the
1891 condition which we may be able to optimize better. It also
1892 uses simple value range propagation to optimize conditionals. */
1893
1894static tree
1895simplify_cond_and_lookup_avail_expr (tree stmt,
6de9cd9a
DN
1896 stmt_ann_t ann,
1897 int insert)
1898{
1899 tree cond = COND_EXPR_COND (stmt);
1900
6615c446 1901 if (COMPARISON_CLASS_P (cond))
6de9cd9a
DN
1902 {
1903 tree op0 = TREE_OPERAND (cond, 0);
1904 tree op1 = TREE_OPERAND (cond, 1);
1905
1906 if (TREE_CODE (op0) == SSA_NAME && is_gimple_min_invariant (op1))
1907 {
1908 int limit;
1909 tree low, high, cond_low, cond_high;
1910 int lowequal, highequal, swapped, no_overlap, subset, cond_inverted;
1911 varray_type vrp_records;
1912 struct vrp_element *element;
b8545fbf 1913 struct vrp_hash_elt vrp_hash_elt, *vrp_hash_elt_p;
23530866 1914 void **slot;
6de9cd9a
DN
1915
1916 /* First see if we have test of an SSA_NAME against a constant
1917 where the SSA_NAME is defined by an earlier typecast which
1918 is irrelevant when performing tests against the given
1919 constant. */
1920 if (TREE_CODE (cond) == EQ_EXPR || TREE_CODE (cond) == NE_EXPR)
1921 {
1922 tree new_cond = find_equivalent_equality_comparison (cond);
1923
1924 if (new_cond)
1925 {
1926 /* Update the statement to use the new equivalent
1927 condition. */
1928 COND_EXPR_COND (stmt) = new_cond;
68b9f53b
AM
1929
1930 /* If this is not a real stmt, ann will be NULL and we
1931 avoid processing the operands. */
1932 if (ann)
1933 modify_stmt (stmt);
6de9cd9a
DN
1934
1935 /* Lookup the condition and return its known value if it
1936 exists. */
48732f23 1937 new_cond = lookup_avail_expr (stmt, insert);
6de9cd9a
DN
1938 if (new_cond)
1939 return new_cond;
1940
1941 /* The operands have changed, so update op0 and op1. */
1942 op0 = TREE_OPERAND (cond, 0);
1943 op1 = TREE_OPERAND (cond, 1);
1944 }
1945 }
1946
1947 /* Consult the value range records for this variable (if they exist)
1948 to see if we can eliminate or simplify this conditional.
1949
1950 Note two tests are necessary to determine no records exist.
1951 First we have to see if the virtual array exists, if it
1952 exists, then we have to check its active size.
1953
1954 Also note the vast majority of conditionals are not testing
1955 a variable which has had its range constrained by an earlier
1956 conditional. So this filter avoids a lot of unnecessary work. */
23530866
JL
1957 vrp_hash_elt.var = op0;
1958 vrp_hash_elt.records = NULL;
1959 slot = htab_find_slot (vrp_data, &vrp_hash_elt, NO_INSERT);
1960 if (slot == NULL)
1961 return NULL;
1962
b8545fbf
JL
1963 vrp_hash_elt_p = (struct vrp_hash_elt *) *slot;
1964 vrp_records = vrp_hash_elt_p->records;
6de9cd9a
DN
1965 if (vrp_records == NULL)
1966 return NULL;
1967
1968 limit = VARRAY_ACTIVE_SIZE (vrp_records);
1969
1970 /* If we have no value range records for this variable, or we are
1971 unable to extract a range for this condition, then there is
1972 nothing to do. */
1973 if (limit == 0
1974 || ! extract_range_from_cond (cond, &cond_high,
1975 &cond_low, &cond_inverted))
1976 return NULL;
1977
1978 /* We really want to avoid unnecessary computations of range
1979 info. So all ranges are computed lazily; this avoids a
454ff5cb 1980 lot of unnecessary work. i.e., we record the conditional,
6de9cd9a
DN
1981 but do not process how it constrains the variable's
1982 potential values until we know that processing the condition
1983 could be helpful.
1984
1985 However, we do not want to have to walk a potentially long
1986 list of ranges, nor do we want to compute a variable's
1987 range more than once for a given path.
1988
1989 Luckily, each time we encounter a conditional that can not
1990 be otherwise optimized we will end up here and we will
1991 compute the necessary range information for the variable
1992 used in this condition.
1993
1994 Thus you can conclude that there will never be more than one
1995 conditional associated with a variable which has not been
1996 processed. So we never need to merge more than one new
1997 conditional into the current range.
1998
1999 These properties also help us avoid unnecessary work. */
2000 element
2001 = (struct vrp_element *)VARRAY_GENERIC_PTR (vrp_records, limit - 1);
2002
2003 if (element->high && element->low)
2004 {
2005 /* The last element has been processed, so there is no range
2006 merging to do, we can simply use the high/low values
2007 recorded in the last element. */
2008 low = element->low;
2009 high = element->high;
2010 }
2011 else
2012 {
2013 tree tmp_high, tmp_low;
2014 int dummy;
2015
2016 /* The last element has not been processed. Process it now. */
2017 extract_range_from_cond (element->cond, &tmp_high,
2018 &tmp_low, &dummy);
2019
2020 /* If this is the only element, then no merging is necessary,
2021 the high/low values from extract_range_from_cond are all
2022 we need. */
2023 if (limit == 1)
2024 {
2025 low = tmp_low;
2026 high = tmp_high;
2027 }
2028 else
2029 {
2030 /* Get the high/low value from the previous element. */
2031 struct vrp_element *prev
2032 = (struct vrp_element *)VARRAY_GENERIC_PTR (vrp_records,
2033 limit - 2);
2034 low = prev->low;
2035 high = prev->high;
2036
2037 /* Merge in this element's range with the range from the
2038 previous element.
2039
2040 The low value for the merged range is the maximum of
2041 the previous low value and the low value of this record.
2042
2043 Similarly the high value for the merged range is the
2044 minimum of the previous high value and the high value of
2045 this record. */
2046 low = (tree_int_cst_compare (low, tmp_low) == 1
2047 ? low : tmp_low);
2048 high = (tree_int_cst_compare (high, tmp_high) == -1
2049 ? high : tmp_high);
2050 }
2051
2052 /* And record the computed range. */
2053 element->low = low;
2054 element->high = high;
2055
2056 }
2057
2058 /* After we have constrained this variable's potential values,
2059 we try to determine the result of the given conditional.
2060
2061 To simplify later tests, first determine if the current
2062 low value is the same low value as the conditional.
2063 Similarly for the current high value and the high value
2064 for the conditional. */
2065 lowequal = tree_int_cst_equal (low, cond_low);
2066 highequal = tree_int_cst_equal (high, cond_high);
2067
2068 if (lowequal && highequal)
2069 return (cond_inverted ? boolean_false_node : boolean_true_node);
2070
2071 /* To simplify the overlap/subset tests below we may want
2072 to swap the two ranges so that the larger of the two
2073 ranges occurs "first". */
2074 swapped = 0;
2075 if (tree_int_cst_compare (low, cond_low) == 1
2076 || (lowequal
2077 && tree_int_cst_compare (cond_high, high) == 1))
2078 {
2079 tree temp;
2080
2081 swapped = 1;
2082 temp = low;
2083 low = cond_low;
2084 cond_low = temp;
2085 temp = high;
2086 high = cond_high;
2087 cond_high = temp;
2088 }
2089
2090 /* Now determine if there is no overlap in the ranges
2091 or if the second range is a subset of the first range. */
2092 no_overlap = tree_int_cst_lt (high, cond_low);
2093 subset = tree_int_cst_compare (cond_high, high) != 1;
2094
2095 /* If there was no overlap in the ranges, then this conditional
2096 always has a false value (unless we had to invert this
2097 conditional, in which case it always has a true value). */
2098 if (no_overlap)
2099 return (cond_inverted ? boolean_true_node : boolean_false_node);
2100
2101 /* If the current range is a subset of the condition's range,
2102 then this conditional always has a true value (unless we
2103 had to invert this conditional, in which case it always
2104 has a true value). */
2105 if (subset && swapped)
2106 return (cond_inverted ? boolean_false_node : boolean_true_node);
2107
2108 /* We were unable to determine the result of the conditional.
2109 However, we may be able to simplify the conditional. First
2110 merge the ranges in the same manner as range merging above. */
2111 low = tree_int_cst_compare (low, cond_low) == 1 ? low : cond_low;
2112 high = tree_int_cst_compare (high, cond_high) == -1 ? high : cond_high;
2113
2114 /* If the range has converged to a single point, then turn this
2115 into an equality comparison. */
2116 if (TREE_CODE (cond) != EQ_EXPR
2117 && TREE_CODE (cond) != NE_EXPR
2118 && tree_int_cst_equal (low, high))
2119 {
2120 TREE_SET_CODE (cond, EQ_EXPR);
2121 TREE_OPERAND (cond, 1) = high;
2122 }
2123 }
2124 }
2125 return 0;
2126}
2127
2128/* STMT is a SWITCH_EXPR for which we could not trivially determine its
2129 result. This routine attempts to find equivalent forms of the
2130 condition which we may be able to optimize better. */
2131
2132static tree
48732f23 2133simplify_switch_and_lookup_avail_expr (tree stmt, int insert)
6de9cd9a
DN
2134{
2135 tree cond = SWITCH_COND (stmt);
2136 tree def, to, ti;
2137
2138 /* The optimization that we really care about is removing unnecessary
2139 casts. That will let us do much better in propagating the inferred
2140 constant at the switch target. */
2141 if (TREE_CODE (cond) == SSA_NAME)
2142 {
2143 def = SSA_NAME_DEF_STMT (cond);
2144 if (TREE_CODE (def) == MODIFY_EXPR)
2145 {
2146 def = TREE_OPERAND (def, 1);
2147 if (TREE_CODE (def) == NOP_EXPR)
2148 {
d969ee71
RH
2149 int need_precision;
2150 bool fail;
2151
6de9cd9a 2152 def = TREE_OPERAND (def, 0);
d969ee71
RH
2153
2154#ifdef ENABLE_CHECKING
2155 /* ??? Why was Jeff testing this? We are gimple... */
1e128c5f 2156 gcc_assert (is_gimple_val (def));
d969ee71
RH
2157#endif
2158
6de9cd9a
DN
2159 to = TREE_TYPE (cond);
2160 ti = TREE_TYPE (def);
2161
d969ee71 2162 /* If we have an extension that preserves value, then we
6de9cd9a 2163 can copy the source value into the switch. */
d969ee71
RH
2164
2165 need_precision = TYPE_PRECISION (ti);
2166 fail = false;
2167 if (TYPE_UNSIGNED (to) && !TYPE_UNSIGNED (ti))
2168 fail = true;
2169 else if (!TYPE_UNSIGNED (to) && TYPE_UNSIGNED (ti))
2170 need_precision += 1;
2171 if (TYPE_PRECISION (to) < need_precision)
2172 fail = true;
2173
2174 if (!fail)
6de9cd9a
DN
2175 {
2176 SWITCH_COND (stmt) = def;
68b9f53b 2177 modify_stmt (stmt);
6de9cd9a 2178
48732f23 2179 return lookup_avail_expr (stmt, insert);
6de9cd9a
DN
2180 }
2181 }
2182 }
2183 }
2184
2185 return 0;
2186}
2187
ff2ad0f7
DN
2188
2189/* CONST_AND_COPIES is a table which maps an SSA_NAME to the current
2190 known value for that SSA_NAME (or NULL if no value is known).
2191
2192 NONZERO_VARS is the set SSA_NAMES known to have a nonzero value,
2193 even if we don't know their precise value.
2194
2195 Propagate values from CONST_AND_COPIES and NONZERO_VARS into the PHI
2196 nodes of the successors of BB. */
2197
2198static void
6f2aec07 2199cprop_into_successor_phis (basic_block bb, bitmap nonzero_vars)
ff2ad0f7
DN
2200{
2201 edge e;
628f6a4e 2202 edge_iterator ei;
ff2ad0f7
DN
2203
2204 /* This can get rather expensive if the implementation is naive in
2205 how it finds the phi alternative associated with a particular edge. */
628f6a4e 2206 FOR_EACH_EDGE (e, ei, bb->succs)
ff2ad0f7
DN
2207 {
2208 tree phi;
2209 int phi_num_args;
2210 int hint;
2211
2212 /* If this is an abnormal edge, then we do not want to copy propagate
2213 into the PHI alternative associated with this edge. */
2214 if (e->flags & EDGE_ABNORMAL)
2215 continue;
2216
2217 phi = phi_nodes (e->dest);
2218 if (! phi)
2219 continue;
2220
2221 /* There is no guarantee that for any two PHI nodes in a block that
2222 the phi alternative associated with a particular edge will be
2223 at the same index in the phi alternative array.
2224
2225 However, it is very likely they will be the same. So we keep
2226 track of the index of the alternative where we found the edge in
2227 the previous phi node and check that index first in the next
2228 phi node. If that hint fails, then we actually search all
2229 the entries. */
2230 phi_num_args = PHI_NUM_ARGS (phi);
2231 hint = phi_num_args;
2232 for ( ; phi; phi = PHI_CHAIN (phi))
2233 {
2234 int i;
2235 tree new;
2236 use_operand_p orig_p;
2237 tree orig;
2238
2239 /* If the hint is valid (!= phi_num_args), see if it points
2240 us to the desired phi alternative. */
2241 if (hint != phi_num_args && PHI_ARG_EDGE (phi, hint) == e)
2242 ;
2243 else
2244 {
2245 /* The hint was either invalid or did not point to the
2246 correct phi alternative. Search all the alternatives
2247 for the correct one. Update the hint. */
2248 for (i = 0; i < phi_num_args; i++)
2249 if (PHI_ARG_EDGE (phi, i) == e)
2250 break;
2251 hint = i;
2252 }
2253
ff2ad0f7
DN
2254 /* If we did not find the proper alternative, then something is
2255 horribly wrong. */
1e128c5f 2256 gcc_assert (hint != phi_num_args);
ff2ad0f7
DN
2257
2258 /* The alternative may be associated with a constant, so verify
2259 it is an SSA_NAME before doing anything with it. */
2260 orig_p = PHI_ARG_DEF_PTR (phi, hint);
2261 orig = USE_FROM_PTR (orig_p);
2262 if (TREE_CODE (orig) != SSA_NAME)
2263 continue;
2264
2265 /* If the alternative is known to have a nonzero value, record
2266 that fact in the PHI node itself for future use. */
2267 if (bitmap_bit_p (nonzero_vars, SSA_NAME_VERSION (orig)))
2268 PHI_ARG_NONZERO (phi, hint) = true;
2269
2270 /* If we have *ORIG_P in our constant/copy table, then replace
2271 ORIG_P with its value in our constant/copy table. */
3aecd08b 2272 new = SSA_NAME_VALUE (orig);
ff2ad0f7
DN
2273 if (new
2274 && (TREE_CODE (new) == SSA_NAME
2275 || is_gimple_min_invariant (new))
2276 && may_propagate_copy (orig, new))
2277 {
2278 propagate_value (orig_p, new);
2279 }
2280 }
2281 }
2282}
2283
2284
6de9cd9a
DN
2285/* Propagate known constants/copies into PHI nodes of BB's successor
2286 blocks. */
2287
2288static void
2289cprop_into_phis (struct dom_walk_data *walk_data ATTRIBUTE_UNUSED,
2290 basic_block bb)
2291{
6f2aec07 2292 cprop_into_successor_phis (bb, nonzero_vars);
6de9cd9a
DN
2293}
2294
2295/* Search for redundant computations in STMT. If any are found, then
2296 replace them with the variable holding the result of the computation.
2297
2298 If safe, record this expression into the available expression hash
2299 table. */
2300
2301static bool
2302eliminate_redundant_computations (struct dom_walk_data *walk_data,
2303 tree stmt, stmt_ann_t ann)
2304{
a32b97a2 2305 v_may_def_optype v_may_defs = V_MAY_DEF_OPS (ann);
6de9cd9a
DN
2306 tree *expr_p, def = NULL_TREE;
2307 bool insert = true;
2308 tree cached_lhs;
2309 bool retval = false;
6de9cd9a
DN
2310
2311 if (TREE_CODE (stmt) == MODIFY_EXPR)
2312 def = TREE_OPERAND (stmt, 0);
2313
2314 /* Certain expressions on the RHS can be optimized away, but can not
471854f8 2315 themselves be entered into the hash tables. */
6de9cd9a
DN
2316 if (ann->makes_aliased_stores
2317 || ! def
2318 || TREE_CODE (def) != SSA_NAME
2319 || SSA_NAME_OCCURS_IN_ABNORMAL_PHI (def)
a32b97a2 2320 || NUM_V_MAY_DEFS (v_may_defs) != 0)
6de9cd9a
DN
2321 insert = false;
2322
2323 /* Check if the expression has been computed before. */
48732f23 2324 cached_lhs = lookup_avail_expr (stmt, insert);
6de9cd9a
DN
2325
2326 /* If this is an assignment and the RHS was not in the hash table,
2327 then try to simplify the RHS and lookup the new RHS in the
2328 hash table. */
2329 if (! cached_lhs && TREE_CODE (stmt) == MODIFY_EXPR)
48732f23 2330 cached_lhs = simplify_rhs_and_lookup_avail_expr (walk_data, stmt, insert);
6de9cd9a
DN
2331 /* Similarly if this is a COND_EXPR and we did not find its
2332 expression in the hash table, simplify the condition and
2333 try again. */
2334 else if (! cached_lhs && TREE_CODE (stmt) == COND_EXPR)
48732f23 2335 cached_lhs = simplify_cond_and_lookup_avail_expr (stmt, ann, insert);
6de9cd9a
DN
2336 /* Similarly for a SWITCH_EXPR. */
2337 else if (!cached_lhs && TREE_CODE (stmt) == SWITCH_EXPR)
48732f23 2338 cached_lhs = simplify_switch_and_lookup_avail_expr (stmt, insert);
6de9cd9a
DN
2339
2340 opt_stats.num_exprs_considered++;
2341
2342 /* Get a pointer to the expression we are trying to optimize. */
2343 if (TREE_CODE (stmt) == COND_EXPR)
2344 expr_p = &COND_EXPR_COND (stmt);
2345 else if (TREE_CODE (stmt) == SWITCH_EXPR)
2346 expr_p = &SWITCH_COND (stmt);
2347 else if (TREE_CODE (stmt) == RETURN_EXPR && TREE_OPERAND (stmt, 0))
2348 expr_p = &TREE_OPERAND (TREE_OPERAND (stmt, 0), 1);
2349 else
2350 expr_p = &TREE_OPERAND (stmt, 1);
2351
2352 /* It is safe to ignore types here since we have already done
2353 type checking in the hashing and equality routines. In fact
2354 type checking here merely gets in the way of constant
2355 propagation. Also, make sure that it is safe to propagate
2356 CACHED_LHS into *EXPR_P. */
2357 if (cached_lhs
2358 && (TREE_CODE (cached_lhs) != SSA_NAME
ff2ad0f7 2359 || may_propagate_copy (*expr_p, cached_lhs)))
6de9cd9a
DN
2360 {
2361 if (dump_file && (dump_flags & TDF_DETAILS))
2362 {
2363 fprintf (dump_file, " Replaced redundant expr '");
2364 print_generic_expr (dump_file, *expr_p, dump_flags);
2365 fprintf (dump_file, "' with '");
2366 print_generic_expr (dump_file, cached_lhs, dump_flags);
2367 fprintf (dump_file, "'\n");
2368 }
2369
2370 opt_stats.num_re++;
2371
2372#if defined ENABLE_CHECKING
1e128c5f
GB
2373 gcc_assert (TREE_CODE (cached_lhs) == SSA_NAME
2374 || is_gimple_min_invariant (cached_lhs));
6de9cd9a
DN
2375#endif
2376
2377 if (TREE_CODE (cached_lhs) == ADDR_EXPR
2378 || (POINTER_TYPE_P (TREE_TYPE (*expr_p))
2379 && is_gimple_min_invariant (cached_lhs)))
2380 retval = true;
2381
d00ad49b 2382 propagate_tree_value (expr_p, cached_lhs);
68b9f53b 2383 modify_stmt (stmt);
6de9cd9a
DN
2384 }
2385 return retval;
2386}
2387
2388/* STMT, a MODIFY_EXPR, may create certain equivalences, in either
2389 the available expressions table or the const_and_copies table.
2390 Detect and record those equivalences. */
2391
2392static void
2393record_equivalences_from_stmt (tree stmt,
6de9cd9a
DN
2394 int may_optimize_p,
2395 stmt_ann_t ann)
2396{
2397 tree lhs = TREE_OPERAND (stmt, 0);
2398 enum tree_code lhs_code = TREE_CODE (lhs);
2399 int i;
2400
2401 if (lhs_code == SSA_NAME)
2402 {
2403 tree rhs = TREE_OPERAND (stmt, 1);
2404
2405 /* Strip away any useless type conversions. */
2406 STRIP_USELESS_TYPE_CONVERSION (rhs);
2407
2408 /* If the RHS of the assignment is a constant or another variable that
2409 may be propagated, register it in the CONST_AND_COPIES table. We
2410 do not need to record unwind data for this, since this is a true
1ea7e6ad 2411 assignment and not an equivalence inferred from a comparison. All
6de9cd9a
DN
2412 uses of this ssa name are dominated by this assignment, so unwinding
2413 just costs time and space. */
2414 if (may_optimize_p
2415 && (TREE_CODE (rhs) == SSA_NAME
2416 || is_gimple_min_invariant (rhs)))
3aecd08b 2417 SSA_NAME_VALUE (lhs) = rhs;
6de9cd9a
DN
2418
2419 /* alloca never returns zero and the address of a non-weak symbol
2420 is never zero. NOP_EXPRs and CONVERT_EXPRs can be completely
2421 stripped as they do not affect this equivalence. */
2422 while (TREE_CODE (rhs) == NOP_EXPR
2423 || TREE_CODE (rhs) == CONVERT_EXPR)
2424 rhs = TREE_OPERAND (rhs, 0);
2425
2426 if (alloca_call_p (rhs)
2427 || (TREE_CODE (rhs) == ADDR_EXPR
2428 && DECL_P (TREE_OPERAND (rhs, 0))
2429 && ! DECL_WEAK (TREE_OPERAND (rhs, 0))))
fdabe5c2 2430 record_var_is_nonzero (lhs);
6de9cd9a
DN
2431
2432 /* IOR of any value with a nonzero value will result in a nonzero
2433 value. Even if we do not know the exact result recording that
2434 the result is nonzero is worth the effort. */
2435 if (TREE_CODE (rhs) == BIT_IOR_EXPR
2436 && integer_nonzerop (TREE_OPERAND (rhs, 1)))
fdabe5c2 2437 record_var_is_nonzero (lhs);
6de9cd9a
DN
2438 }
2439
2440 /* Look at both sides for pointer dereferences. If we find one, then
2441 the pointer must be nonnull and we can enter that equivalence into
2442 the hash tables. */
dd747311
JL
2443 if (flag_delete_null_pointer_checks)
2444 for (i = 0; i < 2; i++)
2445 {
2446 tree t = TREE_OPERAND (stmt, i);
2447
2448 /* Strip away any COMPONENT_REFs. */
2449 while (TREE_CODE (t) == COMPONENT_REF)
2450 t = TREE_OPERAND (t, 0);
2451
2452 /* Now see if this is a pointer dereference. */
1b096a0a 2453 if (INDIRECT_REF_P (t))
dd747311
JL
2454 {
2455 tree op = TREE_OPERAND (t, 0);
2456
2457 /* If the pointer is a SSA variable, then enter new
2458 equivalences into the hash table. */
2459 while (TREE_CODE (op) == SSA_NAME)
2460 {
2461 tree def = SSA_NAME_DEF_STMT (op);
2462
fdabe5c2 2463 record_var_is_nonzero (op);
dd747311
JL
2464
2465 /* And walk up the USE-DEF chains noting other SSA_NAMEs
2466 which are known to have a nonzero value. */
2467 if (def
2468 && TREE_CODE (def) == MODIFY_EXPR
2469 && TREE_CODE (TREE_OPERAND (def, 1)) == NOP_EXPR)
2470 op = TREE_OPERAND (TREE_OPERAND (def, 1), 0);
2471 else
2472 break;
2473 }
2474 }
2475 }
6de9cd9a
DN
2476
2477 /* A memory store, even an aliased store, creates a useful
2478 equivalence. By exchanging the LHS and RHS, creating suitable
2479 vops and recording the result in the available expression table,
2480 we may be able to expose more redundant loads. */
2481 if (!ann->has_volatile_ops
2482 && (TREE_CODE (TREE_OPERAND (stmt, 1)) == SSA_NAME
2483 || is_gimple_min_invariant (TREE_OPERAND (stmt, 1)))
2484 && !is_gimple_reg (lhs))
2485 {
2486 tree rhs = TREE_OPERAND (stmt, 1);
2487 tree new;
6de9cd9a
DN
2488
2489 /* FIXME: If the LHS of the assignment is a bitfield and the RHS
2490 is a constant, we need to adjust the constant to fit into the
2491 type of the LHS. If the LHS is a bitfield and the RHS is not
2492 a constant, then we can not record any equivalences for this
2493 statement since we would need to represent the widening or
2494 narrowing of RHS. This fixes gcc.c-torture/execute/921016-1.c
2495 and should not be necessary if GCC represented bitfields
2496 properly. */
2497 if (lhs_code == COMPONENT_REF
2498 && DECL_BIT_FIELD (TREE_OPERAND (lhs, 1)))
2499 {
2500 if (TREE_CONSTANT (rhs))
2501 rhs = widen_bitfield (rhs, TREE_OPERAND (lhs, 1), lhs);
2502 else
2503 rhs = NULL;
2504
2505 /* If the value overflowed, then we can not use this equivalence. */
2506 if (rhs && ! is_gimple_min_invariant (rhs))
2507 rhs = NULL;
2508 }
2509
2510 if (rhs)
2511 {
6de9cd9a
DN
2512 /* Build a new statement with the RHS and LHS exchanged. */
2513 new = build (MODIFY_EXPR, TREE_TYPE (stmt), rhs, lhs);
2514
1a24f92f 2515 create_ssa_artficial_load_stmt (&(ann->operands), new);
6de9cd9a
DN
2516
2517 /* Finally enter the statement into the available expression
2518 table. */
48732f23 2519 lookup_avail_expr (new, true);
6de9cd9a
DN
2520 }
2521 }
2522}
2523
ff2ad0f7
DN
2524/* Replace *OP_P in STMT with any known equivalent value for *OP_P from
2525 CONST_AND_COPIES. */
2526
2527static bool
6f2aec07 2528cprop_operand (tree stmt, use_operand_p op_p)
ff2ad0f7
DN
2529{
2530 bool may_have_exposed_new_symbols = false;
2531 tree val;
2532 tree op = USE_FROM_PTR (op_p);
2533
2534 /* If the operand has a known constant value or it is known to be a
2535 copy of some other variable, use the value or copy stored in
2536 CONST_AND_COPIES. */
3aecd08b
JL
2537 val = SSA_NAME_VALUE (op);
2538 if (val && TREE_CODE (val) != VALUE_HANDLE)
ff2ad0f7
DN
2539 {
2540 tree op_type, val_type;
2541
2542 /* Do not change the base variable in the virtual operand
2543 tables. That would make it impossible to reconstruct
2544 the renamed virtual operand if we later modify this
2545 statement. Also only allow the new value to be an SSA_NAME
2546 for propagation into virtual operands. */
2547 if (!is_gimple_reg (op)
2548 && (get_virtual_var (val) != get_virtual_var (op)
2549 || TREE_CODE (val) != SSA_NAME))
2550 return false;
2551
aa24864c
RH
2552 /* Do not replace hard register operands in asm statements. */
2553 if (TREE_CODE (stmt) == ASM_EXPR
2554 && !may_propagate_copy_into_asm (op))
2555 return false;
2556
ff2ad0f7
DN
2557 /* Get the toplevel type of each operand. */
2558 op_type = TREE_TYPE (op);
2559 val_type = TREE_TYPE (val);
2560
2561 /* While both types are pointers, get the type of the object
2562 pointed to. */
2563 while (POINTER_TYPE_P (op_type) && POINTER_TYPE_P (val_type))
2564 {
2565 op_type = TREE_TYPE (op_type);
2566 val_type = TREE_TYPE (val_type);
2567 }
2568
63b88252
RH
2569 /* Make sure underlying types match before propagating a constant by
2570 converting the constant to the proper type. Note that convert may
2571 return a non-gimple expression, in which case we ignore this
2572 propagation opportunity. */
2573 if (TREE_CODE (val) != SSA_NAME)
ff2ad0f7 2574 {
63b88252
RH
2575 if (!lang_hooks.types_compatible_p (op_type, val_type))
2576 {
2577 val = fold_convert (TREE_TYPE (op), val);
2578 if (!is_gimple_min_invariant (val))
2579 return false;
2580 }
ff2ad0f7
DN
2581 }
2582
2583 /* Certain operands are not allowed to be copy propagated due
2584 to their interaction with exception handling and some GCC
2585 extensions. */
63b88252 2586 else if (!may_propagate_copy (op, val))
ff2ad0f7
DN
2587 return false;
2588
2589 /* Dump details. */
2590 if (dump_file && (dump_flags & TDF_DETAILS))
2591 {
2592 fprintf (dump_file, " Replaced '");
2593 print_generic_expr (dump_file, op, dump_flags);
2594 fprintf (dump_file, "' with %s '",
2595 (TREE_CODE (val) != SSA_NAME ? "constant" : "variable"));
2596 print_generic_expr (dump_file, val, dump_flags);
2597 fprintf (dump_file, "'\n");
2598 }
2599
2600 /* If VAL is an ADDR_EXPR or a constant of pointer type, note
2601 that we may have exposed a new symbol for SSA renaming. */
2602 if (TREE_CODE (val) == ADDR_EXPR
2603 || (POINTER_TYPE_P (TREE_TYPE (op))
2604 && is_gimple_min_invariant (val)))
2605 may_have_exposed_new_symbols = true;
2606
2607 propagate_value (op_p, val);
2608
2609 /* And note that we modified this statement. This is now
2610 safe, even if we changed virtual operands since we will
2611 rescan the statement and rewrite its operands again. */
68b9f53b 2612 modify_stmt (stmt);
ff2ad0f7
DN
2613 }
2614 return may_have_exposed_new_symbols;
2615}
2616
2617/* CONST_AND_COPIES is a table which maps an SSA_NAME to the current
2618 known value for that SSA_NAME (or NULL if no value is known).
2619
2620 Propagate values from CONST_AND_COPIES into the uses, vuses and
2621 v_may_def_ops of STMT. */
2622
2623static bool
6f2aec07 2624cprop_into_stmt (tree stmt)
ff2ad0f7
DN
2625{
2626 bool may_have_exposed_new_symbols = false;
4c124b4c
AM
2627 use_operand_p op_p;
2628 ssa_op_iter iter;
c7f90219 2629 tree rhs;
ff2ad0f7 2630
4c124b4c 2631 FOR_EACH_SSA_USE_OPERAND (op_p, stmt, iter, SSA_OP_ALL_USES)
ff2ad0f7 2632 {
ff2ad0f7 2633 if (TREE_CODE (USE_FROM_PTR (op_p)) == SSA_NAME)
6f2aec07 2634 may_have_exposed_new_symbols |= cprop_operand (stmt, op_p);
ff2ad0f7
DN
2635 }
2636
c7f90219
SB
2637 if (may_have_exposed_new_symbols)
2638 {
2639 rhs = get_rhs (stmt);
2640 if (rhs && TREE_CODE (rhs) == ADDR_EXPR)
2641 recompute_tree_invarant_for_addr_expr (rhs);
2642 }
2643
ff2ad0f7
DN
2644 return may_have_exposed_new_symbols;
2645}
2646
2647
6de9cd9a
DN
2648/* Optimize the statement pointed by iterator SI.
2649
2650 We try to perform some simplistic global redundancy elimination and
2651 constant propagation:
2652
2653 1- To detect global redundancy, we keep track of expressions that have
2654 been computed in this block and its dominators. If we find that the
2655 same expression is computed more than once, we eliminate repeated
2656 computations by using the target of the first one.
2657
2658 2- Constant values and copy assignments. This is used to do very
2659 simplistic constant and copy propagation. When a constant or copy
2660 assignment is found, we map the value on the RHS of the assignment to
2661 the variable in the LHS in the CONST_AND_COPIES table. */
2662
2663static void
1eaba2f2 2664optimize_stmt (struct dom_walk_data *walk_data, basic_block bb,
6de9cd9a
DN
2665 block_stmt_iterator si)
2666{
2667 stmt_ann_t ann;
2668 tree stmt;
6de9cd9a
DN
2669 bool may_optimize_p;
2670 bool may_have_exposed_new_symbols = false;
6de9cd9a
DN
2671
2672 stmt = bsi_stmt (si);
2673
2674 get_stmt_operands (stmt);
2675 ann = stmt_ann (stmt);
6de9cd9a
DN
2676 opt_stats.num_stmts++;
2677 may_have_exposed_new_symbols = false;
2678
2679 if (dump_file && (dump_flags & TDF_DETAILS))
2680 {
2681 fprintf (dump_file, "Optimizing statement ");
2682 print_generic_stmt (dump_file, stmt, TDF_SLIM);
2683 }
2684
a32b97a2 2685 /* Const/copy propagate into USES, VUSES and the RHS of V_MAY_DEFs. */
6f2aec07 2686 may_have_exposed_new_symbols = cprop_into_stmt (stmt);
6de9cd9a
DN
2687
2688 /* If the statement has been modified with constant replacements,
2689 fold its RHS before checking for redundant computations. */
2690 if (ann->modified)
2691 {
2692 /* Try to fold the statement making sure that STMT is kept
2693 up to date. */
2694 if (fold_stmt (bsi_stmt_ptr (si)))
2695 {
2696 stmt = bsi_stmt (si);
2697 ann = stmt_ann (stmt);
2698
2699 if (dump_file && (dump_flags & TDF_DETAILS))
2700 {
2701 fprintf (dump_file, " Folded to: ");
2702 print_generic_stmt (dump_file, stmt, TDF_SLIM);
2703 }
2704 }
2705
2706 /* Constant/copy propagation above may change the set of
2707 virtual operands associated with this statement. Folding
2708 may remove the need for some virtual operands.
2709
2710 Indicate we will need to rescan and rewrite the statement. */
2711 may_have_exposed_new_symbols = true;
2712 }
2713
2714 /* Check for redundant computations. Do this optimization only
2715 for assignments that have no volatile ops and conditionals. */
2716 may_optimize_p = (!ann->has_volatile_ops
2717 && ((TREE_CODE (stmt) == RETURN_EXPR
2718 && TREE_OPERAND (stmt, 0)
2719 && TREE_CODE (TREE_OPERAND (stmt, 0)) == MODIFY_EXPR
2720 && ! (TREE_SIDE_EFFECTS
2721 (TREE_OPERAND (TREE_OPERAND (stmt, 0), 1))))
2722 || (TREE_CODE (stmt) == MODIFY_EXPR
2723 && ! TREE_SIDE_EFFECTS (TREE_OPERAND (stmt, 1)))
2724 || TREE_CODE (stmt) == COND_EXPR
2725 || TREE_CODE (stmt) == SWITCH_EXPR));
2726
2727 if (may_optimize_p)
2728 may_have_exposed_new_symbols
2729 |= eliminate_redundant_computations (walk_data, stmt, ann);
2730
2731 /* Record any additional equivalences created by this statement. */
2732 if (TREE_CODE (stmt) == MODIFY_EXPR)
2733 record_equivalences_from_stmt (stmt,
6de9cd9a
DN
2734 may_optimize_p,
2735 ann);
2736
9fae925b 2737 register_definitions_for_stmt (stmt);
6de9cd9a
DN
2738
2739 /* If STMT is a COND_EXPR and it was modified, then we may know
2740 where it goes. If that is the case, then mark the CFG as altered.
2741
2742 This will cause us to later call remove_unreachable_blocks and
2743 cleanup_tree_cfg when it is safe to do so. It is not safe to
2744 clean things up here since removal of edges and such can trigger
2745 the removal of PHI nodes, which in turn can release SSA_NAMEs to
2746 the manager.
2747
2748 That's all fine and good, except that once SSA_NAMEs are released
2749 to the manager, we must not call create_ssa_name until all references
2750 to released SSA_NAMEs have been eliminated.
2751
2752 All references to the deleted SSA_NAMEs can not be eliminated until
2753 we remove unreachable blocks.
2754
2755 We can not remove unreachable blocks until after we have completed
2756 any queued jump threading.
2757
2758 We can not complete any queued jump threads until we have taken
2759 appropriate variables out of SSA form. Taking variables out of
2760 SSA form can call create_ssa_name and thus we lose.
2761
2762 Ultimately I suspect we're going to need to change the interface
2763 into the SSA_NAME manager. */
2764
2765 if (ann->modified)
2766 {
2767 tree val = NULL;
2768
2769 if (TREE_CODE (stmt) == COND_EXPR)
2770 val = COND_EXPR_COND (stmt);
2771 else if (TREE_CODE (stmt) == SWITCH_EXPR)
2772 val = SWITCH_COND (stmt);
2773
1eaba2f2 2774 if (val && TREE_CODE (val) == INTEGER_CST && find_taken_edge (bb, val))
6de9cd9a 2775 cfg_altered = true;
1eaba2f2
RH
2776
2777 /* If we simplified a statement in such a way as to be shown that it
2778 cannot trap, update the eh information and the cfg to match. */
2779 if (maybe_clean_eh_stmt (stmt))
2780 {
2781 bitmap_set_bit (need_eh_cleanup, bb->index);
2782 if (dump_file && (dump_flags & TDF_DETAILS))
2783 fprintf (dump_file, " Flagged to clear EH edges.\n");
2784 }
6de9cd9a 2785 }
1eaba2f2 2786
6de9cd9a 2787 if (may_have_exposed_new_symbols)
a6e1aa26 2788 VARRAY_PUSH_TREE (stmts_to_rescan, bsi_stmt (si));
6de9cd9a
DN
2789}
2790
2791/* Replace the RHS of STMT with NEW_RHS. If RHS can be found in the
2792 available expression hashtable, then return the LHS from the hash
2793 table.
2794
2795 If INSERT is true, then we also update the available expression
2796 hash table to account for the changes made to STMT. */
2797
2798static tree
48732f23 2799update_rhs_and_lookup_avail_expr (tree stmt, tree new_rhs, bool insert)
6de9cd9a
DN
2800{
2801 tree cached_lhs = NULL;
2802
2803 /* Remove the old entry from the hash table. */
2804 if (insert)
2805 {
2806 struct expr_hash_elt element;
2807
2808 initialize_hash_element (stmt, NULL, &element);
2809 htab_remove_elt_with_hash (avail_exprs, &element, element.hash);
2810 }
2811
2812 /* Now update the RHS of the assignment. */
2813 TREE_OPERAND (stmt, 1) = new_rhs;
2814
2815 /* Now lookup the updated statement in the hash table. */
48732f23 2816 cached_lhs = lookup_avail_expr (stmt, insert);
6de9cd9a
DN
2817
2818 /* We have now called lookup_avail_expr twice with two different
2819 versions of this same statement, once in optimize_stmt, once here.
2820
2821 We know the call in optimize_stmt did not find an existing entry
2822 in the hash table, so a new entry was created. At the same time
2823 this statement was pushed onto the BLOCK_AVAIL_EXPRS varray.
2824
2825 If this call failed to find an existing entry on the hash table,
2826 then the new version of this statement was entered into the
2827 hash table. And this statement was pushed onto BLOCK_AVAIL_EXPR
2828 for the second time. So there are two copies on BLOCK_AVAIL_EXPRs
2829
2830 If this call succeeded, we still have one copy of this statement
2831 on the BLOCK_AVAIL_EXPRs varray.
2832
2833 For both cases, we need to pop the most recent entry off the
2834 BLOCK_AVAIL_EXPRs varray. For the case where we never found this
2835 statement in the hash tables, that will leave precisely one
2836 copy of this statement on BLOCK_AVAIL_EXPRs. For the case where
2837 we found a copy of this statement in the second hash table lookup
2838 we want _no_ copies of this statement in BLOCK_AVAIL_EXPRs. */
2839 if (insert)
48732f23 2840 VARRAY_POP (avail_exprs_stack);
6de9cd9a
DN
2841
2842 /* And make sure we record the fact that we modified this
2843 statement. */
68b9f53b 2844 modify_stmt (stmt);
6de9cd9a
DN
2845
2846 return cached_lhs;
2847}
2848
2849/* Search for an existing instance of STMT in the AVAIL_EXPRS table. If
2850 found, return its LHS. Otherwise insert STMT in the table and return
2851 NULL_TREE.
2852
2853 Also, when an expression is first inserted in the AVAIL_EXPRS table, it
2854 is also added to the stack pointed by BLOCK_AVAIL_EXPRS_P, so that they
2855 can be removed when we finish processing this block and its children.
2856
2857 NOTE: This function assumes that STMT is a MODIFY_EXPR node that
2858 contains no CALL_EXPR on its RHS and makes no volatile nor
2859 aliased references. */
2860
2861static tree
48732f23 2862lookup_avail_expr (tree stmt, bool insert)
6de9cd9a
DN
2863{
2864 void **slot;
2865 tree lhs;
2866 tree temp;
2867 struct expr_hash_elt *element = xcalloc (sizeof (struct expr_hash_elt), 1);
2868
2869 lhs = TREE_CODE (stmt) == MODIFY_EXPR ? TREE_OPERAND (stmt, 0) : NULL;
2870
2871 initialize_hash_element (stmt, lhs, element);
2872
2873 /* Don't bother remembering constant assignments and copy operations.
2874 Constants and copy operations are handled by the constant/copy propagator
2875 in optimize_stmt. */
2876 if (TREE_CODE (element->rhs) == SSA_NAME
2877 || is_gimple_min_invariant (element->rhs))
2878 {
2879 free (element);
2880 return NULL_TREE;
2881 }
2882
2883 /* If this is an equality test against zero, see if we have recorded a
2884 nonzero value for the variable in question. */
2885 if ((TREE_CODE (element->rhs) == EQ_EXPR
2886 || TREE_CODE (element->rhs) == NE_EXPR)
2887 && TREE_CODE (TREE_OPERAND (element->rhs, 0)) == SSA_NAME
2888 && integer_zerop (TREE_OPERAND (element->rhs, 1)))
2889 {
2890 int indx = SSA_NAME_VERSION (TREE_OPERAND (element->rhs, 0));
2891
2892 if (bitmap_bit_p (nonzero_vars, indx))
2893 {
2894 tree t = element->rhs;
2895 free (element);
2896
2897 if (TREE_CODE (t) == EQ_EXPR)
2898 return boolean_false_node;
2899 else
2900 return boolean_true_node;
2901 }
2902 }
2903
2904 /* Finally try to find the expression in the main expression hash table. */
2905 slot = htab_find_slot_with_hash (avail_exprs, element, element->hash,
2906 (insert ? INSERT : NO_INSERT));
2907 if (slot == NULL)
2908 {
2909 free (element);
2910 return NULL_TREE;
2911 }
2912
2913 if (*slot == NULL)
2914 {
2915 *slot = (void *) element;
48732f23 2916 VARRAY_PUSH_TREE (avail_exprs_stack, stmt ? stmt : element->rhs);
6de9cd9a
DN
2917 return NULL_TREE;
2918 }
2919
2920 /* Extract the LHS of the assignment so that it can be used as the current
2921 definition of another variable. */
2922 lhs = ((struct expr_hash_elt *)*slot)->lhs;
2923
2924 /* See if the LHS appears in the CONST_AND_COPIES table. If it does, then
2925 use the value from the const_and_copies table. */
2926 if (TREE_CODE (lhs) == SSA_NAME)
2927 {
3aecd08b
JL
2928 temp = SSA_NAME_VALUE (lhs);
2929 if (temp && TREE_CODE (temp) != VALUE_HANDLE)
6de9cd9a
DN
2930 lhs = temp;
2931 }
2932
2933 free (element);
2934 return lhs;
2935}
2936
2937/* Given a condition COND, record into HI_P, LO_P and INVERTED_P the
2938 range of values that result in the conditional having a true value.
2939
2940 Return true if we are successful in extracting a range from COND and
2941 false if we are unsuccessful. */
2942
2943static bool
2944extract_range_from_cond (tree cond, tree *hi_p, tree *lo_p, int *inverted_p)
2945{
2946 tree op1 = TREE_OPERAND (cond, 1);
2947 tree high, low, type;
2948 int inverted;
2949
2950 /* Experiments have shown that it's rarely, if ever useful to
2951 record ranges for enumerations. Presumably this is due to
2952 the fact that they're rarely used directly. They are typically
2953 cast into an integer type and used that way. */
2954 if (TREE_CODE (TREE_TYPE (op1)) != INTEGER_TYPE)
2955 return 0;
2956
2957 type = TREE_TYPE (op1);
2958
2959 switch (TREE_CODE (cond))
2960 {
2961 case EQ_EXPR:
2962 high = low = op1;
2963 inverted = 0;
2964 break;
2965
2966 case NE_EXPR:
2967 high = low = op1;
2968 inverted = 1;
2969 break;
2970
2971 case GE_EXPR:
2972 low = op1;
2973 high = TYPE_MAX_VALUE (type);
2974 inverted = 0;
2975 break;
2976
2977 case GT_EXPR:
2978 low = int_const_binop (PLUS_EXPR, op1, integer_one_node, 1);
2979 high = TYPE_MAX_VALUE (type);
2980 inverted = 0;
2981 break;
2982
2983 case LE_EXPR:
2984 high = op1;
2985 low = TYPE_MIN_VALUE (type);
2986 inverted = 0;
2987 break;
2988
2989 case LT_EXPR:
2990 high = int_const_binop (MINUS_EXPR, op1, integer_one_node, 1);
2991 low = TYPE_MIN_VALUE (type);
2992 inverted = 0;
2993 break;
2994
2995 default:
2996 return 0;
2997 }
2998
2999 *hi_p = high;
3000 *lo_p = low;
3001 *inverted_p = inverted;
3002 return 1;
3003}
3004
3005/* Record a range created by COND for basic block BB. */
3006
3007static void
fdabe5c2 3008record_range (tree cond, basic_block bb)
6de9cd9a
DN
3009{
3010 /* We explicitly ignore NE_EXPRs. They rarely allow for meaningful
3011 range optimizations and significantly complicate the implementation. */
6615c446 3012 if (COMPARISON_CLASS_P (cond)
6de9cd9a
DN
3013 && TREE_CODE (cond) != NE_EXPR
3014 && TREE_CODE (TREE_TYPE (TREE_OPERAND (cond, 1))) == INTEGER_TYPE)
3015 {
23530866
JL
3016 struct vrp_hash_elt *vrp_hash_elt;
3017 struct vrp_element *element;
3018 varray_type *vrp_records_p;
3019 void **slot;
3020
6de9cd9a 3021
23530866
JL
3022 vrp_hash_elt = xmalloc (sizeof (struct vrp_hash_elt));
3023 vrp_hash_elt->var = TREE_OPERAND (cond, 0);
3024 vrp_hash_elt->records = NULL;
3025 slot = htab_find_slot (vrp_data, vrp_hash_elt, INSERT);
6de9cd9a 3026
23530866 3027 if (*slot == NULL)
4a198dea 3028 *slot = (void *) vrp_hash_elt;
163075a0
AP
3029 else
3030 free (vrp_hash_elt);
23530866 3031
4a198dea 3032 vrp_hash_elt = (struct vrp_hash_elt *) *slot;
23530866
JL
3033 vrp_records_p = &vrp_hash_elt->records;
3034
3035 element = ggc_alloc (sizeof (struct vrp_element));
6de9cd9a
DN
3036 element->low = NULL;
3037 element->high = NULL;
3038 element->cond = cond;
3039 element->bb = bb;
3040
3041 if (*vrp_records_p == NULL)
23530866 3042 VARRAY_GENERIC_PTR_INIT (*vrp_records_p, 2, "vrp records");
6de9cd9a
DN
3043
3044 VARRAY_PUSH_GENERIC_PTR (*vrp_records_p, element);
fdabe5c2 3045 VARRAY_PUSH_TREE (vrp_variables_stack, TREE_OPERAND (cond, 0));
6de9cd9a
DN
3046 }
3047}
3048
3049/* Given a conditional statement IF_STMT, return the assignment 'X = Y'
3050 known to be true depending on which arm of IF_STMT is taken.
3051
3052 Not all conditional statements will result in a useful assignment.
3053 Return NULL_TREE in that case.
3054
3055 Also enter into the available expression table statements of
3056 the form:
3057
3058 TRUE ARM FALSE ARM
3059 1 = cond 1 = cond'
3060 0 = cond' 0 = cond
3061
3062 This allows us to lookup the condition in a dominated block and
3063 get back a constant indicating if the condition is true. */
3064
3065static struct eq_expr_value
3066get_eq_expr_value (tree if_stmt,
3067 int true_arm,
fdabe5c2 3068 basic_block bb)
6de9cd9a
DN
3069{
3070 tree cond;
3071 struct eq_expr_value retval;
3072
3073 cond = COND_EXPR_COND (if_stmt);
3074 retval.src = NULL;
3075 retval.dst = NULL;
3076
3077 /* If the conditional is a single variable 'X', return 'X = 1' for
471854f8 3078 the true arm and 'X = 0' on the false arm. */
6de9cd9a
DN
3079 if (TREE_CODE (cond) == SSA_NAME)
3080 {
3081 retval.dst = cond;
e9ea8bd5 3082 retval.src = constant_boolean_node (true_arm, TREE_TYPE (cond));
6de9cd9a
DN
3083 return retval;
3084 }
3085
3086 /* If we have a comparison expression, then record its result into
3087 the available expression table. */
6615c446 3088 if (COMPARISON_CLASS_P (cond))
6de9cd9a
DN
3089 {
3090 tree op0 = TREE_OPERAND (cond, 0);
3091 tree op1 = TREE_OPERAND (cond, 1);
3092
3093 /* Special case comparing booleans against a constant as we know
454ff5cb 3094 the value of OP0 on both arms of the branch. i.e., we can record
6de9cd9a
DN
3095 an equivalence for OP0 rather than COND. */
3096 if ((TREE_CODE (cond) == EQ_EXPR || TREE_CODE (cond) == NE_EXPR)
3097 && TREE_CODE (op0) == SSA_NAME
3098 && TREE_CODE (TREE_TYPE (op0)) == BOOLEAN_TYPE
3099 && is_gimple_min_invariant (op1))
3100 {
3101 if ((TREE_CODE (cond) == EQ_EXPR && true_arm)
3102 || (TREE_CODE (cond) == NE_EXPR && ! true_arm))
3103 {
3104 retval.src = op1;
3105 }
3106 else
3107 {
3108 if (integer_zerop (op1))
3109 retval.src = boolean_true_node;
3110 else
3111 retval.src = boolean_false_node;
3112 }
3113 retval.dst = op0;
3114 return retval;
3115 }
3116
3117 if (TREE_CODE (op0) == SSA_NAME
3118 && (is_gimple_min_invariant (op1) || TREE_CODE (op1) == SSA_NAME))
3119 {
3120 tree inverted = invert_truthvalue (cond);
3121
3122 /* When we find an available expression in the hash table, we replace
3123 the expression with the LHS of the statement in the hash table.
3124
3125 So, we want to build statements such as "1 = <condition>" on the
3126 true arm and "0 = <condition>" on the false arm. That way if we
3127 find the expression in the table, we will replace it with its
3128 known constant value. Also insert inversions of the result and
3129 condition into the hash table. */
3130 if (true_arm)
3131 {
48732f23
JL
3132 record_cond (cond, boolean_true_node);
3133 record_dominating_conditions (cond);
3134 record_cond (inverted, boolean_false_node);
6de9cd9a
DN
3135
3136 if (TREE_CONSTANT (op1))
fdabe5c2 3137 record_range (cond, bb);
6de9cd9a
DN
3138
3139 /* If the conditional is of the form 'X == Y', return 'X = Y'
3140 for the true arm. */
3141 if (TREE_CODE (cond) == EQ_EXPR)
3142 {
3143 retval.dst = op0;
3144 retval.src = op1;
3145 return retval;
3146 }
3147 }
3148 else
3149 {
3150
48732f23
JL
3151 record_cond (inverted, boolean_true_node);
3152 record_dominating_conditions (inverted);
3153 record_cond (cond, boolean_false_node);
6de9cd9a
DN
3154
3155 if (TREE_CONSTANT (op1))
fdabe5c2 3156 record_range (inverted, bb);
6de9cd9a
DN
3157
3158 /* If the conditional is of the form 'X != Y', return 'X = Y'
3159 for the false arm. */
3160 if (TREE_CODE (cond) == NE_EXPR)
3161 {
3162 retval.dst = op0;
3163 retval.src = op1;
3164 return retval;
3165 }
3166 }
3167 }
3168 }
3169
3170 return retval;
3171}
3172
23530866
JL
3173/* Hashing and equality functions for VRP_DATA.
3174
3175 Since this hash table is addressed by SSA_NAMEs, we can hash on
3176 their version number and equality can be determined with a
3177 pointer comparison. */
3178
3179static hashval_t
3180vrp_hash (const void *p)
3181{
3182 tree var = ((struct vrp_hash_elt *)p)->var;
3183
3184 return SSA_NAME_VERSION (var);
3185}
3186
3187static int
3188vrp_eq (const void *p1, const void *p2)
3189{
3190 tree var1 = ((struct vrp_hash_elt *)p1)->var;
3191 tree var2 = ((struct vrp_hash_elt *)p2)->var;
3192
3193 return var1 == var2;
3194}
3195
6de9cd9a
DN
3196/* Hashing and equality functions for AVAIL_EXPRS. The table stores
3197 MODIFY_EXPR statements. We compute a value number for expressions using
3198 the code of the expression and the SSA numbers of its operands. */
3199
3200static hashval_t
3201avail_expr_hash (const void *p)
3202{
3203 stmt_ann_t ann = ((struct expr_hash_elt *)p)->ann;
3204 tree rhs = ((struct expr_hash_elt *)p)->rhs;
3205 hashval_t val = 0;
3206 size_t i;
3207 vuse_optype vuses;
3208
3209 /* iterative_hash_expr knows how to deal with any expression and
3210 deals with commutative operators as well, so just use it instead
3211 of duplicating such complexities here. */
3212 val = iterative_hash_expr (rhs, val);
3213
3214 /* If the hash table entry is not associated with a statement, then we
3215 can just hash the expression and not worry about virtual operands
3216 and such. */
3217 if (!ann)
3218 return val;
3219
3220 /* Add the SSA version numbers of every vuse operand. This is important
3221 because compound variables like arrays are not renamed in the
3222 operands. Rather, the rename is done on the virtual variable
3223 representing all the elements of the array. */
3224 vuses = VUSE_OPS (ann);
3225 for (i = 0; i < NUM_VUSES (vuses); i++)
3226 val = iterative_hash_expr (VUSE_OP (vuses, i), val);
3227
3228 return val;
3229}
3230
940db2c8
RH
3231static hashval_t
3232real_avail_expr_hash (const void *p)
3233{
3234 return ((const struct expr_hash_elt *)p)->hash;
3235}
6de9cd9a
DN
3236
3237static int
3238avail_expr_eq (const void *p1, const void *p2)
3239{
3240 stmt_ann_t ann1 = ((struct expr_hash_elt *)p1)->ann;
3241 tree rhs1 = ((struct expr_hash_elt *)p1)->rhs;
3242 stmt_ann_t ann2 = ((struct expr_hash_elt *)p2)->ann;
3243 tree rhs2 = ((struct expr_hash_elt *)p2)->rhs;
3244
3245 /* If they are the same physical expression, return true. */
3246 if (rhs1 == rhs2 && ann1 == ann2)
3247 return true;
3248
3249 /* If their codes are not equal, then quit now. */
3250 if (TREE_CODE (rhs1) != TREE_CODE (rhs2))
3251 return false;
3252
3253 /* In case of a collision, both RHS have to be identical and have the
3254 same VUSE operands. */
3255 if ((TREE_TYPE (rhs1) == TREE_TYPE (rhs2)
3256 || lang_hooks.types_compatible_p (TREE_TYPE (rhs1), TREE_TYPE (rhs2)))
3257 && operand_equal_p (rhs1, rhs2, OEP_PURE_SAME))
3258 {
3259 vuse_optype ops1 = NULL;
3260 vuse_optype ops2 = NULL;
3261 size_t num_ops1 = 0;
3262 size_t num_ops2 = 0;
3263 size_t i;
3264
3265 if (ann1)
3266 {
3267 ops1 = VUSE_OPS (ann1);
3268 num_ops1 = NUM_VUSES (ops1);
3269 }
3270
3271 if (ann2)
3272 {
3273 ops2 = VUSE_OPS (ann2);
3274 num_ops2 = NUM_VUSES (ops2);
3275 }
3276
3277 /* If the number of virtual uses is different, then we consider
3278 them not equal. */
3279 if (num_ops1 != num_ops2)
3280 return false;
3281
3282 for (i = 0; i < num_ops1; i++)
3283 if (VUSE_OP (ops1, i) != VUSE_OP (ops2, i))
3284 return false;
3285
1e128c5f
GB
3286 gcc_assert (((struct expr_hash_elt *)p1)->hash
3287 == ((struct expr_hash_elt *)p2)->hash);
6de9cd9a
DN
3288 return true;
3289 }
3290
3291 return false;
3292}
3293
61ada8ae 3294/* Given STMT and a pointer to the block local definitions BLOCK_DEFS_P,
6de9cd9a
DN
3295 register register all objects set by this statement into BLOCK_DEFS_P
3296 and CURRDEFS. */
3297
3298static void
9fae925b 3299register_definitions_for_stmt (tree stmt)
6de9cd9a 3300{
4c124b4c
AM
3301 tree def;
3302 ssa_op_iter iter;
6de9cd9a 3303
4c124b4c 3304 FOR_EACH_SSA_TREE_OPERAND (def, stmt, iter, SSA_OP_ALL_DEFS)
6de9cd9a 3305 {
6de9cd9a
DN
3306
3307 /* FIXME: We shouldn't be registering new defs if the variable
3308 doesn't need to be renamed. */
9fae925b 3309 register_new_def (def, &block_defs_stack);
6de9cd9a 3310 }
6de9cd9a
DN
3311}
3312
This page took 0.646662 seconds and 5 git commands to generate.