xref: /openbsd/gnu/gcc/gcc/tree-ssa-dom.c (revision 404b540a)
1*404b540aSrobert /* SSA Dominator optimizations for trees
2*404b540aSrobert    Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006
3*404b540aSrobert    Free Software Foundation, Inc.
4*404b540aSrobert    Contributed by Diego Novillo <dnovillo@redhat.com>
5*404b540aSrobert 
6*404b540aSrobert This file is part of GCC.
7*404b540aSrobert 
8*404b540aSrobert GCC is free software; you can redistribute it and/or modify
9*404b540aSrobert it under the terms of the GNU General Public License as published by
10*404b540aSrobert the Free Software Foundation; either version 2, or (at your option)
11*404b540aSrobert any later version.
12*404b540aSrobert 
13*404b540aSrobert GCC is distributed in the hope that it will be useful,
14*404b540aSrobert but WITHOUT ANY WARRANTY; without even the implied warranty of
15*404b540aSrobert MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
16*404b540aSrobert GNU General Public License for more details.
17*404b540aSrobert 
18*404b540aSrobert You should have received a copy of the GNU General Public License
19*404b540aSrobert along with GCC; see the file COPYING.  If not, write to
20*404b540aSrobert the Free Software Foundation, 51 Franklin Street, Fifth Floor,
21*404b540aSrobert Boston, MA 02110-1301, USA.  */
22*404b540aSrobert 
23*404b540aSrobert #include "config.h"
24*404b540aSrobert #include "system.h"
25*404b540aSrobert #include "coretypes.h"
26*404b540aSrobert #include "tm.h"
27*404b540aSrobert #include "tree.h"
28*404b540aSrobert #include "flags.h"
29*404b540aSrobert #include "rtl.h"
30*404b540aSrobert #include "tm_p.h"
31*404b540aSrobert #include "ggc.h"
32*404b540aSrobert #include "basic-block.h"
33*404b540aSrobert #include "cfgloop.h"
34*404b540aSrobert #include "output.h"
35*404b540aSrobert #include "expr.h"
36*404b540aSrobert #include "function.h"
37*404b540aSrobert #include "diagnostic.h"
38*404b540aSrobert #include "timevar.h"
39*404b540aSrobert #include "tree-dump.h"
40*404b540aSrobert #include "tree-flow.h"
41*404b540aSrobert #include "domwalk.h"
42*404b540aSrobert #include "real.h"
43*404b540aSrobert #include "tree-pass.h"
44*404b540aSrobert #include "tree-ssa-propagate.h"
45*404b540aSrobert #include "langhooks.h"
46*404b540aSrobert #include "params.h"
47*404b540aSrobert 
48*404b540aSrobert /* This file implements optimizations on the dominator tree.  */
49*404b540aSrobert 
50*404b540aSrobert 
51*404b540aSrobert /* Structure for recording edge equivalences as well as any pending
52*404b540aSrobert    edge redirections during the dominator optimizer.
53*404b540aSrobert 
54*404b540aSrobert    Computing and storing the edge equivalences instead of creating
55*404b540aSrobert    them on-demand can save significant amounts of time, particularly
56*404b540aSrobert    for pathological cases involving switch statements.
57*404b540aSrobert 
58*404b540aSrobert    These structures live for a single iteration of the dominator
59*404b540aSrobert    optimizer in the edge's AUX field.  At the end of an iteration we
60*404b540aSrobert    free each of these structures and update the AUX field to point
61*404b540aSrobert    to any requested redirection target (the code for updating the
62*404b540aSrobert    CFG and SSA graph for edge redirection expects redirection edge
63*404b540aSrobert    targets to be in the AUX field for each edge.  */
64*404b540aSrobert 
65*404b540aSrobert struct edge_info
66*404b540aSrobert {
67*404b540aSrobert   /* If this edge creates a simple equivalence, the LHS and RHS of
68*404b540aSrobert      the equivalence will be stored here.  */
69*404b540aSrobert   tree lhs;
70*404b540aSrobert   tree rhs;
71*404b540aSrobert 
72*404b540aSrobert   /* Traversing an edge may also indicate one or more particular conditions
73*404b540aSrobert      are true or false.  The number of recorded conditions can vary, but
74*404b540aSrobert      can be determined by the condition's code.  So we have an array
75*404b540aSrobert      and its maximum index rather than use a varray.  */
76*404b540aSrobert   tree *cond_equivalences;
77*404b540aSrobert   unsigned int max_cond_equivalences;
78*404b540aSrobert };
79*404b540aSrobert 
80*404b540aSrobert 
81*404b540aSrobert /* Hash table with expressions made available during the renaming process.
82*404b540aSrobert    When an assignment of the form X_i = EXPR is found, the statement is
83*404b540aSrobert    stored in this table.  If the same expression EXPR is later found on the
84*404b540aSrobert    RHS of another statement, it is replaced with X_i (thus performing
85*404b540aSrobert    global redundancy elimination).  Similarly as we pass through conditionals
86*404b540aSrobert    we record the conditional itself as having either a true or false value
87*404b540aSrobert    in this table.  */
88*404b540aSrobert static htab_t avail_exprs;
89*404b540aSrobert 
90*404b540aSrobert /* Stack of available expressions in AVAIL_EXPRs.  Each block pushes any
91*404b540aSrobert    expressions it enters into the hash table along with a marker entry
92*404b540aSrobert    (null).  When we finish processing the block, we pop off entries and
93*404b540aSrobert    remove the expressions from the global hash table until we hit the
94*404b540aSrobert    marker.  */
VEC(tree,heap)95*404b540aSrobert static VEC(tree,heap) *avail_exprs_stack;
96*404b540aSrobert 
97*404b540aSrobert /* Stack of statements we need to rescan during finalization for newly
98*404b540aSrobert    exposed variables.
99*404b540aSrobert 
100*404b540aSrobert    Statement rescanning must occur after the current block's available
101*404b540aSrobert    expressions are removed from AVAIL_EXPRS.  Else we may change the
102*404b540aSrobert    hash code for an expression and be unable to find/remove it from
103*404b540aSrobert    AVAIL_EXPRS.  */
104*404b540aSrobert static VEC(tree,heap) *stmts_to_rescan;
105*404b540aSrobert 
106*404b540aSrobert /* Structure for entries in the expression hash table.
107*404b540aSrobert 
108*404b540aSrobert    This requires more memory for the hash table entries, but allows us
109*404b540aSrobert    to avoid creating silly tree nodes and annotations for conditionals,
110*404b540aSrobert    eliminates 2 global hash tables and two block local varrays.
111*404b540aSrobert 
112*404b540aSrobert    It also allows us to reduce the number of hash table lookups we
113*404b540aSrobert    have to perform in lookup_avail_expr and finally it allows us to
114*404b540aSrobert    significantly reduce the number of calls into the hashing routine
115*404b540aSrobert    itself.  */
116*404b540aSrobert 
117*404b540aSrobert struct expr_hash_elt
118*404b540aSrobert {
119*404b540aSrobert   /* The value (lhs) of this expression.  */
120*404b540aSrobert   tree lhs;
121*404b540aSrobert 
122*404b540aSrobert   /* The expression (rhs) we want to record.  */
123*404b540aSrobert   tree rhs;
124*404b540aSrobert 
125*404b540aSrobert   /* The stmt pointer if this element corresponds to a statement.  */
126*404b540aSrobert   tree stmt;
127*404b540aSrobert 
128*404b540aSrobert   /* The hash value for RHS/ann.  */
129*404b540aSrobert   hashval_t hash;
130*404b540aSrobert };
131*404b540aSrobert 
132*404b540aSrobert /* Stack of dest,src pairs that need to be restored during finalization.
133*404b540aSrobert 
134*404b540aSrobert    A NULL entry is used to mark the end of pairs which need to be
135*404b540aSrobert    restored during finalization of this block.  */
136*404b540aSrobert static VEC(tree,heap) *const_and_copies_stack;
137*404b540aSrobert 
138*404b540aSrobert /* Track whether or not we have changed the control flow graph.  */
139*404b540aSrobert static bool cfg_altered;
140*404b540aSrobert 
141*404b540aSrobert /* Bitmap of blocks that have had EH statements cleaned.  We should
142*404b540aSrobert    remove their dead edges eventually.  */
143*404b540aSrobert static bitmap need_eh_cleanup;
144*404b540aSrobert 
145*404b540aSrobert /* Statistics for dominator optimizations.  */
146*404b540aSrobert struct opt_stats_d
147*404b540aSrobert {
148*404b540aSrobert   long num_stmts;
149*404b540aSrobert   long num_exprs_considered;
150*404b540aSrobert   long num_re;
151*404b540aSrobert   long num_const_prop;
152*404b540aSrobert   long num_copy_prop;
153*404b540aSrobert };
154*404b540aSrobert 
155*404b540aSrobert static struct opt_stats_d opt_stats;
156*404b540aSrobert 
157*404b540aSrobert struct eq_expr_value
158*404b540aSrobert {
159*404b540aSrobert   tree src;
160*404b540aSrobert   tree dst;
161*404b540aSrobert };
162*404b540aSrobert 
163*404b540aSrobert /* Local functions.  */
164*404b540aSrobert static void optimize_stmt (struct dom_walk_data *,
165*404b540aSrobert 			   basic_block bb,
166*404b540aSrobert 			   block_stmt_iterator);
167*404b540aSrobert static tree lookup_avail_expr (tree, bool);
168*404b540aSrobert static hashval_t avail_expr_hash (const void *);
169*404b540aSrobert static hashval_t real_avail_expr_hash (const void *);
170*404b540aSrobert static int avail_expr_eq (const void *, const void *);
171*404b540aSrobert static void htab_statistics (FILE *, htab_t);
172*404b540aSrobert static void record_cond (tree, tree);
173*404b540aSrobert static void record_const_or_copy (tree, tree);
174*404b540aSrobert static void record_equality (tree, tree);
175*404b540aSrobert static void record_equivalences_from_phis (basic_block);
176*404b540aSrobert static void record_equivalences_from_incoming_edge (basic_block);
177*404b540aSrobert static bool eliminate_redundant_computations (tree);
178*404b540aSrobert static void record_equivalences_from_stmt (tree, int, stmt_ann_t);
179*404b540aSrobert static void dom_thread_across_edge (struct dom_walk_data *, edge);
180*404b540aSrobert static void dom_opt_finalize_block (struct dom_walk_data *, basic_block);
181*404b540aSrobert static void dom_opt_initialize_block (struct dom_walk_data *, basic_block);
182*404b540aSrobert static void propagate_to_outgoing_edges (struct dom_walk_data *, basic_block);
183*404b540aSrobert static void remove_local_expressions_from_table (void);
184*404b540aSrobert static void restore_vars_to_original_value (void);
185*404b540aSrobert static edge single_incoming_edge_ignoring_loop_edges (basic_block);
186*404b540aSrobert 
187*404b540aSrobert 
188*404b540aSrobert /* Allocate an EDGE_INFO for edge E and attach it to E.
189*404b540aSrobert    Return the new EDGE_INFO structure.  */
190*404b540aSrobert 
191*404b540aSrobert static struct edge_info *
allocate_edge_info(edge e)192*404b540aSrobert allocate_edge_info (edge e)
193*404b540aSrobert {
194*404b540aSrobert   struct edge_info *edge_info;
195*404b540aSrobert 
196*404b540aSrobert   edge_info = XCNEW (struct edge_info);
197*404b540aSrobert 
198*404b540aSrobert   e->aux = edge_info;
199*404b540aSrobert   return edge_info;
200*404b540aSrobert }
201*404b540aSrobert 
202*404b540aSrobert /* Free all EDGE_INFO structures associated with edges in the CFG.
203*404b540aSrobert    If a particular edge can be threaded, copy the redirection
204*404b540aSrobert    target from the EDGE_INFO structure into the edge's AUX field
205*404b540aSrobert    as required by code to update the CFG and SSA graph for
206*404b540aSrobert    jump threading.  */
207*404b540aSrobert 
208*404b540aSrobert static void
free_all_edge_infos(void)209*404b540aSrobert free_all_edge_infos (void)
210*404b540aSrobert {
211*404b540aSrobert   basic_block bb;
212*404b540aSrobert   edge_iterator ei;
213*404b540aSrobert   edge e;
214*404b540aSrobert 
215*404b540aSrobert   FOR_EACH_BB (bb)
216*404b540aSrobert     {
217*404b540aSrobert       FOR_EACH_EDGE (e, ei, bb->preds)
218*404b540aSrobert         {
219*404b540aSrobert 	 struct edge_info *edge_info = (struct edge_info *) e->aux;
220*404b540aSrobert 
221*404b540aSrobert 	  if (edge_info)
222*404b540aSrobert 	    {
223*404b540aSrobert 	      if (edge_info->cond_equivalences)
224*404b540aSrobert 		free (edge_info->cond_equivalences);
225*404b540aSrobert 	      free (edge_info);
226*404b540aSrobert 	      e->aux = NULL;
227*404b540aSrobert 	    }
228*404b540aSrobert 	}
229*404b540aSrobert     }
230*404b540aSrobert }
231*404b540aSrobert 
232*404b540aSrobert /* Jump threading, redundancy elimination and const/copy propagation.
233*404b540aSrobert 
234*404b540aSrobert    This pass may expose new symbols that need to be renamed into SSA.  For
235*404b540aSrobert    every new symbol exposed, its corresponding bit will be set in
236*404b540aSrobert    VARS_TO_RENAME.  */
237*404b540aSrobert 
238*404b540aSrobert static unsigned int
tree_ssa_dominator_optimize(void)239*404b540aSrobert tree_ssa_dominator_optimize (void)
240*404b540aSrobert {
241*404b540aSrobert   struct dom_walk_data walk_data;
242*404b540aSrobert   unsigned int i;
243*404b540aSrobert   struct loops loops_info;
244*404b540aSrobert 
245*404b540aSrobert   memset (&opt_stats, 0, sizeof (opt_stats));
246*404b540aSrobert 
247*404b540aSrobert   /* Create our hash tables.  */
248*404b540aSrobert   avail_exprs = htab_create (1024, real_avail_expr_hash, avail_expr_eq, free);
249*404b540aSrobert   avail_exprs_stack = VEC_alloc (tree, heap, 20);
250*404b540aSrobert   const_and_copies_stack = VEC_alloc (tree, heap, 20);
251*404b540aSrobert   stmts_to_rescan = VEC_alloc (tree, heap, 20);
252*404b540aSrobert   need_eh_cleanup = BITMAP_ALLOC (NULL);
253*404b540aSrobert 
254*404b540aSrobert   /* Setup callbacks for the generic dominator tree walker.  */
255*404b540aSrobert   walk_data.walk_stmts_backward = false;
256*404b540aSrobert   walk_data.dom_direction = CDI_DOMINATORS;
257*404b540aSrobert   walk_data.initialize_block_local_data = NULL;
258*404b540aSrobert   walk_data.before_dom_children_before_stmts = dom_opt_initialize_block;
259*404b540aSrobert   walk_data.before_dom_children_walk_stmts = optimize_stmt;
260*404b540aSrobert   walk_data.before_dom_children_after_stmts = propagate_to_outgoing_edges;
261*404b540aSrobert   walk_data.after_dom_children_before_stmts = NULL;
262*404b540aSrobert   walk_data.after_dom_children_walk_stmts = NULL;
263*404b540aSrobert   walk_data.after_dom_children_after_stmts = dom_opt_finalize_block;
264*404b540aSrobert   /* Right now we only attach a dummy COND_EXPR to the global data pointer.
265*404b540aSrobert      When we attach more stuff we'll need to fill this out with a real
266*404b540aSrobert      structure.  */
267*404b540aSrobert   walk_data.global_data = NULL;
268*404b540aSrobert   walk_data.block_local_data_size = 0;
269*404b540aSrobert   walk_data.interesting_blocks = NULL;
270*404b540aSrobert 
271*404b540aSrobert   /* Now initialize the dominator walker.  */
272*404b540aSrobert   init_walk_dominator_tree (&walk_data);
273*404b540aSrobert 
274*404b540aSrobert   calculate_dominance_info (CDI_DOMINATORS);
275*404b540aSrobert 
276*404b540aSrobert   /* We need to know which edges exit loops so that we can
277*404b540aSrobert      aggressively thread through loop headers to an exit
278*404b540aSrobert      edge.  */
279*404b540aSrobert   flow_loops_find (&loops_info);
280*404b540aSrobert   mark_loop_exit_edges (&loops_info);
281*404b540aSrobert   flow_loops_free (&loops_info);
282*404b540aSrobert 
283*404b540aSrobert   /* Clean up the CFG so that any forwarder blocks created by loop
284*404b540aSrobert      canonicalization are removed.  */
285*404b540aSrobert   cleanup_tree_cfg ();
286*404b540aSrobert   calculate_dominance_info (CDI_DOMINATORS);
287*404b540aSrobert 
288*404b540aSrobert   /* We need accurate information regarding back edges in the CFG
289*404b540aSrobert      for jump threading.  */
290*404b540aSrobert   mark_dfs_back_edges ();
291*404b540aSrobert 
292*404b540aSrobert   /* Recursively walk the dominator tree optimizing statements.  */
293*404b540aSrobert   walk_dominator_tree (&walk_data, ENTRY_BLOCK_PTR);
294*404b540aSrobert 
295*404b540aSrobert   {
296*404b540aSrobert     block_stmt_iterator bsi;
297*404b540aSrobert     basic_block bb;
298*404b540aSrobert     FOR_EACH_BB (bb)
299*404b540aSrobert       {
300*404b540aSrobert 	for (bsi = bsi_start (bb); !bsi_end_p (bsi); bsi_next (&bsi))
301*404b540aSrobert 	  update_stmt_if_modified (bsi_stmt (bsi));
302*404b540aSrobert       }
303*404b540aSrobert   }
304*404b540aSrobert 
305*404b540aSrobert   /* If we exposed any new variables, go ahead and put them into
306*404b540aSrobert      SSA form now, before we handle jump threading.  This simplifies
307*404b540aSrobert      interactions between rewriting of _DECL nodes into SSA form
308*404b540aSrobert      and rewriting SSA_NAME nodes into SSA form after block
309*404b540aSrobert      duplication and CFG manipulation.  */
310*404b540aSrobert   update_ssa (TODO_update_ssa);
311*404b540aSrobert 
312*404b540aSrobert   free_all_edge_infos ();
313*404b540aSrobert 
314*404b540aSrobert   /* Thread jumps, creating duplicate blocks as needed.  */
315*404b540aSrobert   cfg_altered |= thread_through_all_blocks ();
316*404b540aSrobert 
317*404b540aSrobert   /* Removal of statements may make some EH edges dead.  Purge
318*404b540aSrobert      such edges from the CFG as needed.  */
319*404b540aSrobert   if (!bitmap_empty_p (need_eh_cleanup))
320*404b540aSrobert     {
321*404b540aSrobert       cfg_altered |= tree_purge_all_dead_eh_edges (need_eh_cleanup);
322*404b540aSrobert       bitmap_zero (need_eh_cleanup);
323*404b540aSrobert     }
324*404b540aSrobert 
325*404b540aSrobert   if (cfg_altered)
326*404b540aSrobert     free_dominance_info (CDI_DOMINATORS);
327*404b540aSrobert 
328*404b540aSrobert   /* Finally, remove everything except invariants in SSA_NAME_VALUE.
329*404b540aSrobert 
330*404b540aSrobert      Long term we will be able to let everything in SSA_NAME_VALUE
331*404b540aSrobert      persist.  However, for now, we know this is the safe thing to do.  */
332*404b540aSrobert   for (i = 0; i < num_ssa_names; i++)
333*404b540aSrobert    {
334*404b540aSrobert       tree name = ssa_name (i);
335*404b540aSrobert       tree value;
336*404b540aSrobert 
337*404b540aSrobert       if (!name)
338*404b540aSrobert         continue;
339*404b540aSrobert 
340*404b540aSrobert       value = SSA_NAME_VALUE (name);
341*404b540aSrobert       if (value && !is_gimple_min_invariant (value))
342*404b540aSrobert 	SSA_NAME_VALUE (name) = NULL;
343*404b540aSrobert     }
344*404b540aSrobert 
345*404b540aSrobert   /* Debugging dumps.  */
346*404b540aSrobert   if (dump_file && (dump_flags & TDF_STATS))
347*404b540aSrobert     dump_dominator_optimization_stats (dump_file);
348*404b540aSrobert 
349*404b540aSrobert   /* Delete our main hashtable.  */
350*404b540aSrobert   htab_delete (avail_exprs);
351*404b540aSrobert 
352*404b540aSrobert   /* And finalize the dominator walker.  */
353*404b540aSrobert   fini_walk_dominator_tree (&walk_data);
354*404b540aSrobert 
355*404b540aSrobert   /* Free asserted bitmaps and stacks.  */
356*404b540aSrobert   BITMAP_FREE (need_eh_cleanup);
357*404b540aSrobert 
358*404b540aSrobert   VEC_free (tree, heap, avail_exprs_stack);
359*404b540aSrobert   VEC_free (tree, heap, const_and_copies_stack);
360*404b540aSrobert   VEC_free (tree, heap, stmts_to_rescan);
361*404b540aSrobert   return 0;
362*404b540aSrobert }
363*404b540aSrobert 
364*404b540aSrobert static bool
gate_dominator(void)365*404b540aSrobert gate_dominator (void)
366*404b540aSrobert {
367*404b540aSrobert   return flag_tree_dom != 0;
368*404b540aSrobert }
369*404b540aSrobert 
370*404b540aSrobert struct tree_opt_pass pass_dominator =
371*404b540aSrobert {
372*404b540aSrobert   "dom",				/* name */
373*404b540aSrobert   gate_dominator,			/* gate */
374*404b540aSrobert   tree_ssa_dominator_optimize,		/* execute */
375*404b540aSrobert   NULL,					/* sub */
376*404b540aSrobert   NULL,					/* next */
377*404b540aSrobert   0,					/* static_pass_number */
378*404b540aSrobert   TV_TREE_SSA_DOMINATOR_OPTS,		/* tv_id */
379*404b540aSrobert   PROP_cfg | PROP_ssa | PROP_alias,	/* properties_required */
380*404b540aSrobert   0,					/* properties_provided */
381*404b540aSrobert   PROP_smt_usage,			/* properties_destroyed */
382*404b540aSrobert   0,					/* todo_flags_start */
383*404b540aSrobert   TODO_dump_func
384*404b540aSrobert     | TODO_update_ssa
385*404b540aSrobert     | TODO_cleanup_cfg
386*404b540aSrobert     | TODO_verify_ssa
387*404b540aSrobert     | TODO_update_smt_usage,		/* todo_flags_finish */
388*404b540aSrobert   0					/* letter */
389*404b540aSrobert };
390*404b540aSrobert 
391*404b540aSrobert 
392*404b540aSrobert /* Given a stmt CONDSTMT containing a COND_EXPR, canonicalize the
393*404b540aSrobert    COND_EXPR into a canonical form.  */
394*404b540aSrobert 
395*404b540aSrobert static void
canonicalize_comparison(tree condstmt)396*404b540aSrobert canonicalize_comparison (tree condstmt)
397*404b540aSrobert {
398*404b540aSrobert   tree cond = COND_EXPR_COND (condstmt);
399*404b540aSrobert   tree op0;
400*404b540aSrobert   tree op1;
401*404b540aSrobert   enum tree_code code = TREE_CODE (cond);
402*404b540aSrobert 
403*404b540aSrobert   if (!COMPARISON_CLASS_P (cond))
404*404b540aSrobert     return;
405*404b540aSrobert 
406*404b540aSrobert   op0 = TREE_OPERAND (cond, 0);
407*404b540aSrobert   op1 = TREE_OPERAND (cond, 1);
408*404b540aSrobert 
409*404b540aSrobert   /* If it would be profitable to swap the operands, then do so to
410*404b540aSrobert      canonicalize the statement, enabling better optimization.
411*404b540aSrobert 
412*404b540aSrobert      By placing canonicalization of such expressions here we
413*404b540aSrobert      transparently keep statements in canonical form, even
414*404b540aSrobert      when the statement is modified.  */
415*404b540aSrobert   if (tree_swap_operands_p (op0, op1, false))
416*404b540aSrobert     {
417*404b540aSrobert       /* For relationals we need to swap the operands
418*404b540aSrobert 	 and change the code.  */
419*404b540aSrobert       if (code == LT_EXPR
420*404b540aSrobert 	  || code == GT_EXPR
421*404b540aSrobert 	  || code == LE_EXPR
422*404b540aSrobert 	  || code == GE_EXPR)
423*404b540aSrobert 	{
424*404b540aSrobert 	  TREE_SET_CODE (cond, swap_tree_comparison (code));
425*404b540aSrobert 	  swap_tree_operands (condstmt,
426*404b540aSrobert 			      &TREE_OPERAND (cond, 0),
427*404b540aSrobert 			      &TREE_OPERAND (cond, 1));
428*404b540aSrobert 	  /* If one operand was in the operand cache, but the other is
429*404b540aSrobert 	     not, because it is a constant, this is a case that the
430*404b540aSrobert 	     internal updating code of swap_tree_operands can't handle
431*404b540aSrobert 	     properly.  */
432*404b540aSrobert 	  if (TREE_CODE_CLASS (TREE_CODE (op0))
433*404b540aSrobert 	      != TREE_CODE_CLASS (TREE_CODE (op1)))
434*404b540aSrobert 	    update_stmt (condstmt);
435*404b540aSrobert 	}
436*404b540aSrobert     }
437*404b540aSrobert }
438*404b540aSrobert 
439*404b540aSrobert /* Initialize local stacks for this optimizer and record equivalences
440*404b540aSrobert    upon entry to BB.  Equivalences can come from the edge traversed to
441*404b540aSrobert    reach BB or they may come from PHI nodes at the start of BB.  */
442*404b540aSrobert 
443*404b540aSrobert static void
dom_opt_initialize_block(struct dom_walk_data * walk_data ATTRIBUTE_UNUSED,basic_block bb)444*404b540aSrobert dom_opt_initialize_block (struct dom_walk_data *walk_data ATTRIBUTE_UNUSED,
445*404b540aSrobert 			  basic_block bb)
446*404b540aSrobert {
447*404b540aSrobert   if (dump_file && (dump_flags & TDF_DETAILS))
448*404b540aSrobert     fprintf (dump_file, "\n\nOptimizing block #%d\n\n", bb->index);
449*404b540aSrobert 
450*404b540aSrobert   /* Push a marker on the stacks of local information so that we know how
451*404b540aSrobert      far to unwind when we finalize this block.  */
452*404b540aSrobert   VEC_safe_push (tree, heap, avail_exprs_stack, NULL_TREE);
453*404b540aSrobert   VEC_safe_push (tree, heap, const_and_copies_stack, NULL_TREE);
454*404b540aSrobert 
455*404b540aSrobert   record_equivalences_from_incoming_edge (bb);
456*404b540aSrobert 
457*404b540aSrobert   /* PHI nodes can create equivalences too.  */
458*404b540aSrobert   record_equivalences_from_phis (bb);
459*404b540aSrobert }
460*404b540aSrobert 
461*404b540aSrobert /* Given an expression EXPR (a relational expression or a statement),
462*404b540aSrobert    initialize the hash table element pointed to by ELEMENT.  */
463*404b540aSrobert 
464*404b540aSrobert static void
initialize_hash_element(tree expr,tree lhs,struct expr_hash_elt * element)465*404b540aSrobert initialize_hash_element (tree expr, tree lhs, struct expr_hash_elt *element)
466*404b540aSrobert {
467*404b540aSrobert   /* Hash table elements may be based on conditional expressions or statements.
468*404b540aSrobert 
469*404b540aSrobert      For the former case, we have no annotation and we want to hash the
470*404b540aSrobert      conditional expression.  In the latter case we have an annotation and
471*404b540aSrobert      we want to record the expression the statement evaluates.  */
472*404b540aSrobert   if (COMPARISON_CLASS_P (expr) || TREE_CODE (expr) == TRUTH_NOT_EXPR)
473*404b540aSrobert     {
474*404b540aSrobert       element->stmt = NULL;
475*404b540aSrobert       element->rhs = expr;
476*404b540aSrobert     }
477*404b540aSrobert   else if (TREE_CODE (expr) == COND_EXPR)
478*404b540aSrobert     {
479*404b540aSrobert       element->stmt = expr;
480*404b540aSrobert       element->rhs = COND_EXPR_COND (expr);
481*404b540aSrobert     }
482*404b540aSrobert   else if (TREE_CODE (expr) == SWITCH_EXPR)
483*404b540aSrobert     {
484*404b540aSrobert       element->stmt = expr;
485*404b540aSrobert       element->rhs = SWITCH_COND (expr);
486*404b540aSrobert     }
487*404b540aSrobert   else if (TREE_CODE (expr) == RETURN_EXPR && TREE_OPERAND (expr, 0))
488*404b540aSrobert     {
489*404b540aSrobert       element->stmt = expr;
490*404b540aSrobert       element->rhs = TREE_OPERAND (TREE_OPERAND (expr, 0), 1);
491*404b540aSrobert     }
492*404b540aSrobert   else if (TREE_CODE (expr) == GOTO_EXPR)
493*404b540aSrobert     {
494*404b540aSrobert       element->stmt = expr;
495*404b540aSrobert       element->rhs = GOTO_DESTINATION (expr);
496*404b540aSrobert     }
497*404b540aSrobert   else
498*404b540aSrobert     {
499*404b540aSrobert       element->stmt = expr;
500*404b540aSrobert       element->rhs = TREE_OPERAND (expr, 1);
501*404b540aSrobert     }
502*404b540aSrobert 
503*404b540aSrobert   element->lhs = lhs;
504*404b540aSrobert   element->hash = avail_expr_hash (element);
505*404b540aSrobert }
506*404b540aSrobert 
507*404b540aSrobert /* Remove all the expressions in LOCALS from TABLE, stopping when there are
508*404b540aSrobert    LIMIT entries left in LOCALs.  */
509*404b540aSrobert 
510*404b540aSrobert static void
remove_local_expressions_from_table(void)511*404b540aSrobert remove_local_expressions_from_table (void)
512*404b540aSrobert {
513*404b540aSrobert   /* Remove all the expressions made available in this block.  */
514*404b540aSrobert   while (VEC_length (tree, avail_exprs_stack) > 0)
515*404b540aSrobert     {
516*404b540aSrobert       struct expr_hash_elt element;
517*404b540aSrobert       tree expr = VEC_pop (tree, avail_exprs_stack);
518*404b540aSrobert 
519*404b540aSrobert       if (expr == NULL_TREE)
520*404b540aSrobert 	break;
521*404b540aSrobert 
522*404b540aSrobert       initialize_hash_element (expr, NULL, &element);
523*404b540aSrobert       htab_remove_elt_with_hash (avail_exprs, &element, element.hash);
524*404b540aSrobert     }
525*404b540aSrobert }
526*404b540aSrobert 
527*404b540aSrobert /* Use the source/dest pairs in CONST_AND_COPIES_STACK to restore
528*404b540aSrobert    CONST_AND_COPIES to its original state, stopping when we hit a
529*404b540aSrobert    NULL marker.  */
530*404b540aSrobert 
531*404b540aSrobert static void
restore_vars_to_original_value(void)532*404b540aSrobert restore_vars_to_original_value (void)
533*404b540aSrobert {
534*404b540aSrobert   while (VEC_length (tree, const_and_copies_stack) > 0)
535*404b540aSrobert     {
536*404b540aSrobert       tree prev_value, dest;
537*404b540aSrobert 
538*404b540aSrobert       dest = VEC_pop (tree, const_and_copies_stack);
539*404b540aSrobert 
540*404b540aSrobert       if (dest == NULL)
541*404b540aSrobert 	break;
542*404b540aSrobert 
543*404b540aSrobert       prev_value = VEC_pop (tree, const_and_copies_stack);
544*404b540aSrobert       SSA_NAME_VALUE (dest) =  prev_value;
545*404b540aSrobert     }
546*404b540aSrobert }
547*404b540aSrobert 
548*404b540aSrobert /* A trivial wrapper so that we can present the generic jump
549*404b540aSrobert    threading code with a simple API for simplifying statements.  */
550*404b540aSrobert static tree
simplify_stmt_for_jump_threading(tree stmt,tree within_stmt ATTRIBUTE_UNUSED)551*404b540aSrobert simplify_stmt_for_jump_threading (tree stmt, tree within_stmt ATTRIBUTE_UNUSED)
552*404b540aSrobert {
553*404b540aSrobert   return lookup_avail_expr (stmt, false);
554*404b540aSrobert }
555*404b540aSrobert 
556*404b540aSrobert /* Wrapper for common code to attempt to thread an edge.  For example,
557*404b540aSrobert    it handles lazily building the dummy condition and the bookkeeping
558*404b540aSrobert    when jump threading is successful.  */
559*404b540aSrobert 
560*404b540aSrobert static void
dom_thread_across_edge(struct dom_walk_data * walk_data,edge e)561*404b540aSrobert dom_thread_across_edge (struct dom_walk_data *walk_data, edge e)
562*404b540aSrobert {
563*404b540aSrobert   /* If we don't already have a dummy condition, build it now.  */
564*404b540aSrobert   if (! walk_data->global_data)
565*404b540aSrobert     {
566*404b540aSrobert       tree dummy_cond = build2 (NE_EXPR, boolean_type_node,
567*404b540aSrobert 			        integer_zero_node, integer_zero_node);
568*404b540aSrobert       dummy_cond = build3 (COND_EXPR, void_type_node, dummy_cond, NULL, NULL);
569*404b540aSrobert       walk_data->global_data = dummy_cond;
570*404b540aSrobert     }
571*404b540aSrobert 
572*404b540aSrobert   thread_across_edge (walk_data->global_data, e, false,
573*404b540aSrobert 		      &const_and_copies_stack,
574*404b540aSrobert 		      simplify_stmt_for_jump_threading);
575*404b540aSrobert }
576*404b540aSrobert 
577*404b540aSrobert /* We have finished processing the dominator children of BB, perform
578*404b540aSrobert    any finalization actions in preparation for leaving this node in
579*404b540aSrobert    the dominator tree.  */
580*404b540aSrobert 
581*404b540aSrobert static void
dom_opt_finalize_block(struct dom_walk_data * walk_data,basic_block bb)582*404b540aSrobert dom_opt_finalize_block (struct dom_walk_data *walk_data, basic_block bb)
583*404b540aSrobert {
584*404b540aSrobert   tree last;
585*404b540aSrobert 
586*404b540aSrobert 
587*404b540aSrobert   /* If we have an outgoing edge to a block with multiple incoming and
588*404b540aSrobert      outgoing edges, then we may be able to thread the edge.  ie, we
589*404b540aSrobert      may be able to statically determine which of the outgoing edges
590*404b540aSrobert      will be traversed when the incoming edge from BB is traversed.  */
591*404b540aSrobert   if (single_succ_p (bb)
592*404b540aSrobert       && (single_succ_edge (bb)->flags & EDGE_ABNORMAL) == 0
593*404b540aSrobert       && potentially_threadable_block (single_succ (bb)))
594*404b540aSrobert     {
595*404b540aSrobert       dom_thread_across_edge (walk_data, single_succ_edge (bb));
596*404b540aSrobert     }
597*404b540aSrobert   else if ((last = last_stmt (bb))
598*404b540aSrobert 	   && TREE_CODE (last) == COND_EXPR
599*404b540aSrobert 	   && (COMPARISON_CLASS_P (COND_EXPR_COND (last))
600*404b540aSrobert 	       || TREE_CODE (COND_EXPR_COND (last)) == SSA_NAME)
601*404b540aSrobert 	   && EDGE_COUNT (bb->succs) == 2
602*404b540aSrobert 	   && (EDGE_SUCC (bb, 0)->flags & EDGE_ABNORMAL) == 0
603*404b540aSrobert 	   && (EDGE_SUCC (bb, 1)->flags & EDGE_ABNORMAL) == 0)
604*404b540aSrobert     {
605*404b540aSrobert       edge true_edge, false_edge;
606*404b540aSrobert 
607*404b540aSrobert       extract_true_false_edges_from_block (bb, &true_edge, &false_edge);
608*404b540aSrobert 
609*404b540aSrobert       /* Only try to thread the edge if it reaches a target block with
610*404b540aSrobert 	 more than one predecessor and more than one successor.  */
611*404b540aSrobert       if (potentially_threadable_block (true_edge->dest))
612*404b540aSrobert 	{
613*404b540aSrobert 	  struct edge_info *edge_info;
614*404b540aSrobert 	  unsigned int i;
615*404b540aSrobert 
616*404b540aSrobert 	  /* Push a marker onto the available expression stack so that we
617*404b540aSrobert 	     unwind any expressions related to the TRUE arm before processing
618*404b540aSrobert 	     the false arm below.  */
619*404b540aSrobert 	  VEC_safe_push (tree, heap, avail_exprs_stack, NULL_TREE);
620*404b540aSrobert 	  VEC_safe_push (tree, heap, const_and_copies_stack, NULL_TREE);
621*404b540aSrobert 
622*404b540aSrobert 	  edge_info = (struct edge_info *) true_edge->aux;
623*404b540aSrobert 
624*404b540aSrobert 	  /* If we have info associated with this edge, record it into
625*404b540aSrobert 	     our equivalency tables.  */
626*404b540aSrobert 	  if (edge_info)
627*404b540aSrobert 	    {
628*404b540aSrobert 	      tree *cond_equivalences = edge_info->cond_equivalences;
629*404b540aSrobert 	      tree lhs = edge_info->lhs;
630*404b540aSrobert 	      tree rhs = edge_info->rhs;
631*404b540aSrobert 
632*404b540aSrobert 	      /* If we have a simple NAME = VALUE equivalency record it.  */
633*404b540aSrobert 	      if (lhs && TREE_CODE (lhs) == SSA_NAME)
634*404b540aSrobert 		record_const_or_copy (lhs, rhs);
635*404b540aSrobert 
636*404b540aSrobert 	      /* If we have 0 = COND or 1 = COND equivalences, record them
637*404b540aSrobert 		 into our expression hash tables.  */
638*404b540aSrobert 	      if (cond_equivalences)
639*404b540aSrobert 		for (i = 0; i < edge_info->max_cond_equivalences; i += 2)
640*404b540aSrobert 		  {
641*404b540aSrobert 		    tree expr = cond_equivalences[i];
642*404b540aSrobert 		    tree value = cond_equivalences[i + 1];
643*404b540aSrobert 
644*404b540aSrobert 		    record_cond (expr, value);
645*404b540aSrobert 		  }
646*404b540aSrobert 	    }
647*404b540aSrobert 
648*404b540aSrobert 	  dom_thread_across_edge (walk_data, true_edge);
649*404b540aSrobert 
650*404b540aSrobert 	  /* And restore the various tables to their state before
651*404b540aSrobert 	     we threaded this edge.  */
652*404b540aSrobert 	  remove_local_expressions_from_table ();
653*404b540aSrobert 	}
654*404b540aSrobert 
655*404b540aSrobert       /* Similarly for the ELSE arm.  */
656*404b540aSrobert       if (potentially_threadable_block (false_edge->dest))
657*404b540aSrobert 	{
658*404b540aSrobert 	  struct edge_info *edge_info;
659*404b540aSrobert 	  unsigned int i;
660*404b540aSrobert 
661*404b540aSrobert 	  VEC_safe_push (tree, heap, const_and_copies_stack, NULL_TREE);
662*404b540aSrobert 	  edge_info = (struct edge_info *) false_edge->aux;
663*404b540aSrobert 
664*404b540aSrobert 	  /* If we have info associated with this edge, record it into
665*404b540aSrobert 	     our equivalency tables.  */
666*404b540aSrobert 	  if (edge_info)
667*404b540aSrobert 	    {
668*404b540aSrobert 	      tree *cond_equivalences = edge_info->cond_equivalences;
669*404b540aSrobert 	      tree lhs = edge_info->lhs;
670*404b540aSrobert 	      tree rhs = edge_info->rhs;
671*404b540aSrobert 
672*404b540aSrobert 	      /* If we have a simple NAME = VALUE equivalency record it.  */
673*404b540aSrobert 	      if (lhs && TREE_CODE (lhs) == SSA_NAME)
674*404b540aSrobert 		record_const_or_copy (lhs, rhs);
675*404b540aSrobert 
676*404b540aSrobert 	      /* If we have 0 = COND or 1 = COND equivalences, record them
677*404b540aSrobert 		 into our expression hash tables.  */
678*404b540aSrobert 	      if (cond_equivalences)
679*404b540aSrobert 		for (i = 0; i < edge_info->max_cond_equivalences; i += 2)
680*404b540aSrobert 		  {
681*404b540aSrobert 		    tree expr = cond_equivalences[i];
682*404b540aSrobert 		    tree value = cond_equivalences[i + 1];
683*404b540aSrobert 
684*404b540aSrobert 		    record_cond (expr, value);
685*404b540aSrobert 		  }
686*404b540aSrobert 	    }
687*404b540aSrobert 
688*404b540aSrobert 	  /* Now thread the edge.  */
689*404b540aSrobert 	  dom_thread_across_edge (walk_data, false_edge);
690*404b540aSrobert 
691*404b540aSrobert 	  /* No need to remove local expressions from our tables
692*404b540aSrobert 	     or restore vars to their original value as that will
693*404b540aSrobert 	     be done immediately below.  */
694*404b540aSrobert 	}
695*404b540aSrobert     }
696*404b540aSrobert 
697*404b540aSrobert   remove_local_expressions_from_table ();
698*404b540aSrobert   restore_vars_to_original_value ();
699*404b540aSrobert 
700*404b540aSrobert   /* If we queued any statements to rescan in this block, then
701*404b540aSrobert      go ahead and rescan them now.  */
702*404b540aSrobert   while (VEC_length (tree, stmts_to_rescan) > 0)
703*404b540aSrobert     {
704*404b540aSrobert       tree stmt = VEC_last (tree, stmts_to_rescan);
705*404b540aSrobert       basic_block stmt_bb = bb_for_stmt (stmt);
706*404b540aSrobert 
707*404b540aSrobert       if (stmt_bb != bb)
708*404b540aSrobert 	break;
709*404b540aSrobert 
710*404b540aSrobert       VEC_pop (tree, stmts_to_rescan);
711*404b540aSrobert       mark_new_vars_to_rename (stmt);
712*404b540aSrobert     }
713*404b540aSrobert }
714*404b540aSrobert 
715*404b540aSrobert /* PHI nodes can create equivalences too.
716*404b540aSrobert 
717*404b540aSrobert    Ignoring any alternatives which are the same as the result, if
718*404b540aSrobert    all the alternatives are equal, then the PHI node creates an
719*404b540aSrobert    equivalence.  */
720*404b540aSrobert 
721*404b540aSrobert static void
record_equivalences_from_phis(basic_block bb)722*404b540aSrobert record_equivalences_from_phis (basic_block bb)
723*404b540aSrobert {
724*404b540aSrobert   tree phi;
725*404b540aSrobert 
726*404b540aSrobert   for (phi = phi_nodes (bb); phi; phi = PHI_CHAIN (phi))
727*404b540aSrobert     {
728*404b540aSrobert       tree lhs = PHI_RESULT (phi);
729*404b540aSrobert       tree rhs = NULL;
730*404b540aSrobert       int i;
731*404b540aSrobert 
732*404b540aSrobert       for (i = 0; i < PHI_NUM_ARGS (phi); i++)
733*404b540aSrobert 	{
734*404b540aSrobert 	  tree t = PHI_ARG_DEF (phi, i);
735*404b540aSrobert 
736*404b540aSrobert 	  /* Ignore alternatives which are the same as our LHS.  Since
737*404b540aSrobert 	     LHS is a PHI_RESULT, it is known to be a SSA_NAME, so we
738*404b540aSrobert 	     can simply compare pointers.  */
739*404b540aSrobert 	  if (lhs == t)
740*404b540aSrobert 	    continue;
741*404b540aSrobert 
742*404b540aSrobert 	  /* If we have not processed an alternative yet, then set
743*404b540aSrobert 	     RHS to this alternative.  */
744*404b540aSrobert 	  if (rhs == NULL)
745*404b540aSrobert 	    rhs = t;
746*404b540aSrobert 	  /* If we have processed an alternative (stored in RHS), then
747*404b540aSrobert 	     see if it is equal to this one.  If it isn't, then stop
748*404b540aSrobert 	     the search.  */
749*404b540aSrobert 	  else if (! operand_equal_for_phi_arg_p (rhs, t))
750*404b540aSrobert 	    break;
751*404b540aSrobert 	}
752*404b540aSrobert 
753*404b540aSrobert       /* If we had no interesting alternatives, then all the RHS alternatives
754*404b540aSrobert 	 must have been the same as LHS.  */
755*404b540aSrobert       if (!rhs)
756*404b540aSrobert 	rhs = lhs;
757*404b540aSrobert 
758*404b540aSrobert       /* If we managed to iterate through each PHI alternative without
759*404b540aSrobert 	 breaking out of the loop, then we have a PHI which may create
760*404b540aSrobert 	 a useful equivalence.  We do not need to record unwind data for
761*404b540aSrobert 	 this, since this is a true assignment and not an equivalence
762*404b540aSrobert 	 inferred from a comparison.  All uses of this ssa name are dominated
763*404b540aSrobert 	 by this assignment, so unwinding just costs time and space.  */
764*404b540aSrobert       if (i == PHI_NUM_ARGS (phi)
765*404b540aSrobert 	  && may_propagate_copy (lhs, rhs))
766*404b540aSrobert 	SSA_NAME_VALUE (lhs) = rhs;
767*404b540aSrobert     }
768*404b540aSrobert }
769*404b540aSrobert 
770*404b540aSrobert /* Ignoring loop backedges, if BB has precisely one incoming edge then
771*404b540aSrobert    return that edge.  Otherwise return NULL.  */
772*404b540aSrobert static edge
single_incoming_edge_ignoring_loop_edges(basic_block bb)773*404b540aSrobert single_incoming_edge_ignoring_loop_edges (basic_block bb)
774*404b540aSrobert {
775*404b540aSrobert   edge retval = NULL;
776*404b540aSrobert   edge e;
777*404b540aSrobert   edge_iterator ei;
778*404b540aSrobert 
779*404b540aSrobert   FOR_EACH_EDGE (e, ei, bb->preds)
780*404b540aSrobert     {
781*404b540aSrobert       /* A loop back edge can be identified by the destination of
782*404b540aSrobert 	 the edge dominating the source of the edge.  */
783*404b540aSrobert       if (dominated_by_p (CDI_DOMINATORS, e->src, e->dest))
784*404b540aSrobert 	continue;
785*404b540aSrobert 
786*404b540aSrobert       /* If we have already seen a non-loop edge, then we must have
787*404b540aSrobert 	 multiple incoming non-loop edges and thus we return NULL.  */
788*404b540aSrobert       if (retval)
789*404b540aSrobert 	return NULL;
790*404b540aSrobert 
791*404b540aSrobert       /* This is the first non-loop incoming edge we have found.  Record
792*404b540aSrobert 	 it.  */
793*404b540aSrobert       retval = e;
794*404b540aSrobert     }
795*404b540aSrobert 
796*404b540aSrobert   return retval;
797*404b540aSrobert }
798*404b540aSrobert 
799*404b540aSrobert /* Record any equivalences created by the incoming edge to BB.  If BB
800*404b540aSrobert    has more than one incoming edge, then no equivalence is created.  */
801*404b540aSrobert 
802*404b540aSrobert static void
record_equivalences_from_incoming_edge(basic_block bb)803*404b540aSrobert record_equivalences_from_incoming_edge (basic_block bb)
804*404b540aSrobert {
805*404b540aSrobert   edge e;
806*404b540aSrobert   basic_block parent;
807*404b540aSrobert   struct edge_info *edge_info;
808*404b540aSrobert 
809*404b540aSrobert   /* If our parent block ended with a control statement, then we may be
810*404b540aSrobert      able to record some equivalences based on which outgoing edge from
811*404b540aSrobert      the parent was followed.  */
812*404b540aSrobert   parent = get_immediate_dominator (CDI_DOMINATORS, bb);
813*404b540aSrobert 
814*404b540aSrobert   e = single_incoming_edge_ignoring_loop_edges (bb);
815*404b540aSrobert 
816*404b540aSrobert   /* If we had a single incoming edge from our parent block, then enter
817*404b540aSrobert      any data associated with the edge into our tables.  */
818*404b540aSrobert   if (e && e->src == parent)
819*404b540aSrobert     {
820*404b540aSrobert       unsigned int i;
821*404b540aSrobert 
822*404b540aSrobert       edge_info = (struct edge_info *) e->aux;
823*404b540aSrobert 
824*404b540aSrobert       if (edge_info)
825*404b540aSrobert 	{
826*404b540aSrobert 	  tree lhs = edge_info->lhs;
827*404b540aSrobert 	  tree rhs = edge_info->rhs;
828*404b540aSrobert 	  tree *cond_equivalences = edge_info->cond_equivalences;
829*404b540aSrobert 
830*404b540aSrobert 	  if (lhs)
831*404b540aSrobert 	    record_equality (lhs, rhs);
832*404b540aSrobert 
833*404b540aSrobert 	  if (cond_equivalences)
834*404b540aSrobert 	    {
835*404b540aSrobert 	      for (i = 0; i < edge_info->max_cond_equivalences; i += 2)
836*404b540aSrobert 		{
837*404b540aSrobert 		  tree expr = cond_equivalences[i];
838*404b540aSrobert 		  tree value = cond_equivalences[i + 1];
839*404b540aSrobert 
840*404b540aSrobert 		  record_cond (expr, value);
841*404b540aSrobert 		}
842*404b540aSrobert 	    }
843*404b540aSrobert 	}
844*404b540aSrobert     }
845*404b540aSrobert }
846*404b540aSrobert 
847*404b540aSrobert /* Dump SSA statistics on FILE.  */
848*404b540aSrobert 
849*404b540aSrobert void
dump_dominator_optimization_stats(FILE * file)850*404b540aSrobert dump_dominator_optimization_stats (FILE *file)
851*404b540aSrobert {
852*404b540aSrobert   long n_exprs;
853*404b540aSrobert 
854*404b540aSrobert   fprintf (file, "Total number of statements:                   %6ld\n\n",
855*404b540aSrobert 	   opt_stats.num_stmts);
856*404b540aSrobert   fprintf (file, "Exprs considered for dominator optimizations: %6ld\n",
857*404b540aSrobert            opt_stats.num_exprs_considered);
858*404b540aSrobert 
859*404b540aSrobert   n_exprs = opt_stats.num_exprs_considered;
860*404b540aSrobert   if (n_exprs == 0)
861*404b540aSrobert     n_exprs = 1;
862*404b540aSrobert 
863*404b540aSrobert   fprintf (file, "    Redundant expressions eliminated:         %6ld (%.0f%%)\n",
864*404b540aSrobert 	   opt_stats.num_re, PERCENT (opt_stats.num_re,
865*404b540aSrobert 				      n_exprs));
866*404b540aSrobert   fprintf (file, "    Constants propagated:                     %6ld\n",
867*404b540aSrobert 	   opt_stats.num_const_prop);
868*404b540aSrobert   fprintf (file, "    Copies propagated:                        %6ld\n",
869*404b540aSrobert 	   opt_stats.num_copy_prop);
870*404b540aSrobert 
871*404b540aSrobert   fprintf (file, "\nHash table statistics:\n");
872*404b540aSrobert 
873*404b540aSrobert   fprintf (file, "    avail_exprs: ");
874*404b540aSrobert   htab_statistics (file, avail_exprs);
875*404b540aSrobert }
876*404b540aSrobert 
877*404b540aSrobert 
878*404b540aSrobert /* Dump SSA statistics on stderr.  */
879*404b540aSrobert 
880*404b540aSrobert void
debug_dominator_optimization_stats(void)881*404b540aSrobert debug_dominator_optimization_stats (void)
882*404b540aSrobert {
883*404b540aSrobert   dump_dominator_optimization_stats (stderr);
884*404b540aSrobert }
885*404b540aSrobert 
886*404b540aSrobert 
887*404b540aSrobert /* Dump statistics for the hash table HTAB.  */
888*404b540aSrobert 
889*404b540aSrobert static void
htab_statistics(FILE * file,htab_t htab)890*404b540aSrobert htab_statistics (FILE *file, htab_t htab)
891*404b540aSrobert {
892*404b540aSrobert   fprintf (file, "size %ld, %ld elements, %f collision/search ratio\n",
893*404b540aSrobert 	   (long) htab_size (htab),
894*404b540aSrobert 	   (long) htab_elements (htab),
895*404b540aSrobert 	   htab_collisions (htab));
896*404b540aSrobert }
897*404b540aSrobert 
898*404b540aSrobert /* Enter a statement into the true/false expression hash table indicating
899*404b540aSrobert    that the condition COND has the value VALUE.  */
900*404b540aSrobert 
901*404b540aSrobert static void
record_cond(tree cond,tree value)902*404b540aSrobert record_cond (tree cond, tree value)
903*404b540aSrobert {
904*404b540aSrobert   struct expr_hash_elt *element = XCNEW (struct expr_hash_elt);
905*404b540aSrobert   void **slot;
906*404b540aSrobert 
907*404b540aSrobert   initialize_hash_element (cond, value, element);
908*404b540aSrobert 
909*404b540aSrobert   slot = htab_find_slot_with_hash (avail_exprs, (void *)element,
910*404b540aSrobert 				   element->hash, INSERT);
911*404b540aSrobert   if (*slot == NULL)
912*404b540aSrobert     {
913*404b540aSrobert       *slot = (void *) element;
914*404b540aSrobert       VEC_safe_push (tree, heap, avail_exprs_stack, cond);
915*404b540aSrobert     }
916*404b540aSrobert   else
917*404b540aSrobert     free (element);
918*404b540aSrobert }
919*404b540aSrobert 
920*404b540aSrobert /* Build a new conditional using NEW_CODE, OP0 and OP1 and store
921*404b540aSrobert    the new conditional into *p, then store a boolean_true_node
922*404b540aSrobert    into *(p + 1).  */
923*404b540aSrobert 
924*404b540aSrobert static void
build_and_record_new_cond(enum tree_code new_code,tree op0,tree op1,tree * p)925*404b540aSrobert build_and_record_new_cond (enum tree_code new_code, tree op0, tree op1, tree *p)
926*404b540aSrobert {
927*404b540aSrobert   *p = build2 (new_code, boolean_type_node, op0, op1);
928*404b540aSrobert   p++;
929*404b540aSrobert   *p = boolean_true_node;
930*404b540aSrobert }
931*404b540aSrobert 
932*404b540aSrobert /* Record that COND is true and INVERTED is false into the edge information
933*404b540aSrobert    structure.  Also record that any conditions dominated by COND are true
934*404b540aSrobert    as well.
935*404b540aSrobert 
936*404b540aSrobert    For example, if a < b is true, then a <= b must also be true.  */
937*404b540aSrobert 
938*404b540aSrobert static void
record_conditions(struct edge_info * edge_info,tree cond,tree inverted)939*404b540aSrobert record_conditions (struct edge_info *edge_info, tree cond, tree inverted)
940*404b540aSrobert {
941*404b540aSrobert   tree op0, op1;
942*404b540aSrobert 
943*404b540aSrobert   if (!COMPARISON_CLASS_P (cond))
944*404b540aSrobert     return;
945*404b540aSrobert 
946*404b540aSrobert   op0 = TREE_OPERAND (cond, 0);
947*404b540aSrobert   op1 = TREE_OPERAND (cond, 1);
948*404b540aSrobert 
949*404b540aSrobert   switch (TREE_CODE (cond))
950*404b540aSrobert     {
951*404b540aSrobert     case LT_EXPR:
952*404b540aSrobert     case GT_EXPR:
953*404b540aSrobert       if (FLOAT_TYPE_P (TREE_TYPE (op0)))
954*404b540aSrobert 	{
955*404b540aSrobert 	  edge_info->max_cond_equivalences = 12;
956*404b540aSrobert 	  edge_info->cond_equivalences = XNEWVEC (tree, 12);
957*404b540aSrobert 	  build_and_record_new_cond (ORDERED_EXPR, op0, op1,
958*404b540aSrobert 				     &edge_info->cond_equivalences[8]);
959*404b540aSrobert 	  build_and_record_new_cond (LTGT_EXPR, op0, op1,
960*404b540aSrobert 				     &edge_info->cond_equivalences[10]);
961*404b540aSrobert 	}
962*404b540aSrobert       else
963*404b540aSrobert 	{
964*404b540aSrobert 	  edge_info->max_cond_equivalences = 8;
965*404b540aSrobert 	  edge_info->cond_equivalences = XNEWVEC (tree, 8);
966*404b540aSrobert 	}
967*404b540aSrobert 
968*404b540aSrobert       build_and_record_new_cond ((TREE_CODE (cond) == LT_EXPR
969*404b540aSrobert 				  ? LE_EXPR : GE_EXPR),
970*404b540aSrobert 				 op0, op1, &edge_info->cond_equivalences[4]);
971*404b540aSrobert       build_and_record_new_cond (NE_EXPR, op0, op1,
972*404b540aSrobert 				 &edge_info->cond_equivalences[6]);
973*404b540aSrobert       break;
974*404b540aSrobert 
975*404b540aSrobert     case GE_EXPR:
976*404b540aSrobert     case LE_EXPR:
977*404b540aSrobert       if (FLOAT_TYPE_P (TREE_TYPE (op0)))
978*404b540aSrobert 	{
979*404b540aSrobert 	  edge_info->max_cond_equivalences = 6;
980*404b540aSrobert 	  edge_info->cond_equivalences = XNEWVEC (tree, 6);
981*404b540aSrobert 	  build_and_record_new_cond (ORDERED_EXPR, op0, op1,
982*404b540aSrobert 				     &edge_info->cond_equivalences[4]);
983*404b540aSrobert 	}
984*404b540aSrobert       else
985*404b540aSrobert 	{
986*404b540aSrobert 	  edge_info->max_cond_equivalences = 4;
987*404b540aSrobert 	  edge_info->cond_equivalences = XNEWVEC (tree, 4);
988*404b540aSrobert 	}
989*404b540aSrobert       break;
990*404b540aSrobert 
991*404b540aSrobert     case EQ_EXPR:
992*404b540aSrobert       if (FLOAT_TYPE_P (TREE_TYPE (op0)))
993*404b540aSrobert 	{
994*404b540aSrobert 	  edge_info->max_cond_equivalences = 10;
995*404b540aSrobert 	  edge_info->cond_equivalences = XNEWVEC (tree, 10);
996*404b540aSrobert 	  build_and_record_new_cond (ORDERED_EXPR, op0, op1,
997*404b540aSrobert 				     &edge_info->cond_equivalences[8]);
998*404b540aSrobert 	}
999*404b540aSrobert       else
1000*404b540aSrobert 	{
1001*404b540aSrobert 	  edge_info->max_cond_equivalences = 8;
1002*404b540aSrobert 	  edge_info->cond_equivalences = XNEWVEC (tree, 8);
1003*404b540aSrobert 	}
1004*404b540aSrobert       build_and_record_new_cond (LE_EXPR, op0, op1,
1005*404b540aSrobert 				 &edge_info->cond_equivalences[4]);
1006*404b540aSrobert       build_and_record_new_cond (GE_EXPR, op0, op1,
1007*404b540aSrobert 				 &edge_info->cond_equivalences[6]);
1008*404b540aSrobert       break;
1009*404b540aSrobert 
1010*404b540aSrobert     case UNORDERED_EXPR:
1011*404b540aSrobert       edge_info->max_cond_equivalences = 16;
1012*404b540aSrobert       edge_info->cond_equivalences = XNEWVEC (tree, 16);
1013*404b540aSrobert       build_and_record_new_cond (NE_EXPR, op0, op1,
1014*404b540aSrobert 				 &edge_info->cond_equivalences[4]);
1015*404b540aSrobert       build_and_record_new_cond (UNLE_EXPR, op0, op1,
1016*404b540aSrobert 				 &edge_info->cond_equivalences[6]);
1017*404b540aSrobert       build_and_record_new_cond (UNGE_EXPR, op0, op1,
1018*404b540aSrobert 				 &edge_info->cond_equivalences[8]);
1019*404b540aSrobert       build_and_record_new_cond (UNEQ_EXPR, op0, op1,
1020*404b540aSrobert 				 &edge_info->cond_equivalences[10]);
1021*404b540aSrobert       build_and_record_new_cond (UNLT_EXPR, op0, op1,
1022*404b540aSrobert 				 &edge_info->cond_equivalences[12]);
1023*404b540aSrobert       build_and_record_new_cond (UNGT_EXPR, op0, op1,
1024*404b540aSrobert 				 &edge_info->cond_equivalences[14]);
1025*404b540aSrobert       break;
1026*404b540aSrobert 
1027*404b540aSrobert     case UNLT_EXPR:
1028*404b540aSrobert     case UNGT_EXPR:
1029*404b540aSrobert       edge_info->max_cond_equivalences = 8;
1030*404b540aSrobert       edge_info->cond_equivalences = XNEWVEC (tree, 8);
1031*404b540aSrobert       build_and_record_new_cond ((TREE_CODE (cond) == UNLT_EXPR
1032*404b540aSrobert 				  ? UNLE_EXPR : UNGE_EXPR),
1033*404b540aSrobert 				 op0, op1, &edge_info->cond_equivalences[4]);
1034*404b540aSrobert       build_and_record_new_cond (NE_EXPR, op0, op1,
1035*404b540aSrobert 				 &edge_info->cond_equivalences[6]);
1036*404b540aSrobert       break;
1037*404b540aSrobert 
1038*404b540aSrobert     case UNEQ_EXPR:
1039*404b540aSrobert       edge_info->max_cond_equivalences = 8;
1040*404b540aSrobert       edge_info->cond_equivalences = XNEWVEC (tree, 8);
1041*404b540aSrobert       build_and_record_new_cond (UNLE_EXPR, op0, op1,
1042*404b540aSrobert 				 &edge_info->cond_equivalences[4]);
1043*404b540aSrobert       build_and_record_new_cond (UNGE_EXPR, op0, op1,
1044*404b540aSrobert 				 &edge_info->cond_equivalences[6]);
1045*404b540aSrobert       break;
1046*404b540aSrobert 
1047*404b540aSrobert     case LTGT_EXPR:
1048*404b540aSrobert       edge_info->max_cond_equivalences = 8;
1049*404b540aSrobert       edge_info->cond_equivalences = XNEWVEC (tree, 8);
1050*404b540aSrobert       build_and_record_new_cond (NE_EXPR, op0, op1,
1051*404b540aSrobert 				 &edge_info->cond_equivalences[4]);
1052*404b540aSrobert       build_and_record_new_cond (ORDERED_EXPR, op0, op1,
1053*404b540aSrobert 				 &edge_info->cond_equivalences[6]);
1054*404b540aSrobert       break;
1055*404b540aSrobert 
1056*404b540aSrobert     default:
1057*404b540aSrobert       edge_info->max_cond_equivalences = 4;
1058*404b540aSrobert       edge_info->cond_equivalences = XNEWVEC (tree, 4);
1059*404b540aSrobert       break;
1060*404b540aSrobert     }
1061*404b540aSrobert 
1062*404b540aSrobert   /* Now store the original true and false conditions into the first
1063*404b540aSrobert      two slots.  */
1064*404b540aSrobert   edge_info->cond_equivalences[0] = cond;
1065*404b540aSrobert   edge_info->cond_equivalences[1] = boolean_true_node;
1066*404b540aSrobert   edge_info->cond_equivalences[2] = inverted;
1067*404b540aSrobert   edge_info->cond_equivalences[3] = boolean_false_node;
1068*404b540aSrobert }
1069*404b540aSrobert 
1070*404b540aSrobert /* A helper function for record_const_or_copy and record_equality.
1071*404b540aSrobert    Do the work of recording the value and undo info.  */
1072*404b540aSrobert 
1073*404b540aSrobert static void
record_const_or_copy_1(tree x,tree y,tree prev_x)1074*404b540aSrobert record_const_or_copy_1 (tree x, tree y, tree prev_x)
1075*404b540aSrobert {
1076*404b540aSrobert   SSA_NAME_VALUE (x) = y;
1077*404b540aSrobert 
1078*404b540aSrobert   VEC_reserve (tree, heap, const_and_copies_stack, 2);
1079*404b540aSrobert   VEC_quick_push (tree, const_and_copies_stack, prev_x);
1080*404b540aSrobert   VEC_quick_push (tree, const_and_copies_stack, x);
1081*404b540aSrobert }
1082*404b540aSrobert 
1083*404b540aSrobert 
1084*404b540aSrobert /* Return the loop depth of the basic block of the defining statement of X.
1085*404b540aSrobert    This number should not be treated as absolutely correct because the loop
1086*404b540aSrobert    information may not be completely up-to-date when dom runs.  However, it
1087*404b540aSrobert    will be relatively correct, and as more passes are taught to keep loop info
1088*404b540aSrobert    up to date, the result will become more and more accurate.  */
1089*404b540aSrobert 
1090*404b540aSrobert int
loop_depth_of_name(tree x)1091*404b540aSrobert loop_depth_of_name (tree x)
1092*404b540aSrobert {
1093*404b540aSrobert   tree defstmt;
1094*404b540aSrobert   basic_block defbb;
1095*404b540aSrobert 
1096*404b540aSrobert   /* If it's not an SSA_NAME, we have no clue where the definition is.  */
1097*404b540aSrobert   if (TREE_CODE (x) != SSA_NAME)
1098*404b540aSrobert     return 0;
1099*404b540aSrobert 
1100*404b540aSrobert   /* Otherwise return the loop depth of the defining statement's bb.
1101*404b540aSrobert      Note that there may not actually be a bb for this statement, if the
1102*404b540aSrobert      ssa_name is live on entry.  */
1103*404b540aSrobert   defstmt = SSA_NAME_DEF_STMT (x);
1104*404b540aSrobert   defbb = bb_for_stmt (defstmt);
1105*404b540aSrobert   if (!defbb)
1106*404b540aSrobert     return 0;
1107*404b540aSrobert 
1108*404b540aSrobert   return defbb->loop_depth;
1109*404b540aSrobert }
1110*404b540aSrobert 
1111*404b540aSrobert 
1112*404b540aSrobert /* Record that X is equal to Y in const_and_copies.  Record undo
1113*404b540aSrobert    information in the block-local vector.  */
1114*404b540aSrobert 
1115*404b540aSrobert static void
record_const_or_copy(tree x,tree y)1116*404b540aSrobert record_const_or_copy (tree x, tree y)
1117*404b540aSrobert {
1118*404b540aSrobert   tree prev_x = SSA_NAME_VALUE (x);
1119*404b540aSrobert 
1120*404b540aSrobert   if (TREE_CODE (y) == SSA_NAME)
1121*404b540aSrobert     {
1122*404b540aSrobert       tree tmp = SSA_NAME_VALUE (y);
1123*404b540aSrobert       if (tmp)
1124*404b540aSrobert 	y = tmp;
1125*404b540aSrobert     }
1126*404b540aSrobert 
1127*404b540aSrobert   record_const_or_copy_1 (x, y, prev_x);
1128*404b540aSrobert }
1129*404b540aSrobert 
1130*404b540aSrobert /* Similarly, but assume that X and Y are the two operands of an EQ_EXPR.
1131*404b540aSrobert    This constrains the cases in which we may treat this as assignment.  */
1132*404b540aSrobert 
1133*404b540aSrobert static void
record_equality(tree x,tree y)1134*404b540aSrobert record_equality (tree x, tree y)
1135*404b540aSrobert {
1136*404b540aSrobert   tree prev_x = NULL, prev_y = NULL;
1137*404b540aSrobert 
1138*404b540aSrobert   if (TREE_CODE (x) == SSA_NAME)
1139*404b540aSrobert     prev_x = SSA_NAME_VALUE (x);
1140*404b540aSrobert   if (TREE_CODE (y) == SSA_NAME)
1141*404b540aSrobert     prev_y = SSA_NAME_VALUE (y);
1142*404b540aSrobert 
1143*404b540aSrobert   /* If one of the previous values is invariant, or invariant in more loops
1144*404b540aSrobert      (by depth), then use that.
1145*404b540aSrobert      Otherwise it doesn't matter which value we choose, just so
1146*404b540aSrobert      long as we canonicalize on one value.  */
1147*404b540aSrobert   if (TREE_INVARIANT (y))
1148*404b540aSrobert     ;
1149*404b540aSrobert   else if (TREE_INVARIANT (x) || (loop_depth_of_name (x) <= loop_depth_of_name (y)))
1150*404b540aSrobert     prev_x = x, x = y, y = prev_x, prev_x = prev_y;
1151*404b540aSrobert   else if (prev_x && TREE_INVARIANT (prev_x))
1152*404b540aSrobert     x = y, y = prev_x, prev_x = prev_y;
1153*404b540aSrobert   else if (prev_y && TREE_CODE (prev_y) != VALUE_HANDLE)
1154*404b540aSrobert     y = prev_y;
1155*404b540aSrobert 
1156*404b540aSrobert   /* After the swapping, we must have one SSA_NAME.  */
1157*404b540aSrobert   if (TREE_CODE (x) != SSA_NAME)
1158*404b540aSrobert     return;
1159*404b540aSrobert 
1160*404b540aSrobert   /* For IEEE, -0.0 == 0.0, so we don't necessarily know the sign of a
1161*404b540aSrobert      variable compared against zero.  If we're honoring signed zeros,
1162*404b540aSrobert      then we cannot record this value unless we know that the value is
1163*404b540aSrobert      nonzero.  */
1164*404b540aSrobert   if (HONOR_SIGNED_ZEROS (TYPE_MODE (TREE_TYPE (x)))
1165*404b540aSrobert       && (TREE_CODE (y) != REAL_CST
1166*404b540aSrobert 	  || REAL_VALUES_EQUAL (dconst0, TREE_REAL_CST (y))))
1167*404b540aSrobert     return;
1168*404b540aSrobert 
1169*404b540aSrobert   record_const_or_copy_1 (x, y, prev_x);
1170*404b540aSrobert }
1171*404b540aSrobert 
1172*404b540aSrobert /* Returns true when STMT is a simple iv increment.  It detects the
1173*404b540aSrobert    following situation:
1174*404b540aSrobert 
1175*404b540aSrobert    i_1 = phi (..., i_2)
1176*404b540aSrobert    i_2 = i_1 +/- ...  */
1177*404b540aSrobert 
1178*404b540aSrobert static bool
simple_iv_increment_p(tree stmt)1179*404b540aSrobert simple_iv_increment_p (tree stmt)
1180*404b540aSrobert {
1181*404b540aSrobert   tree lhs, rhs, preinc, phi;
1182*404b540aSrobert   unsigned i;
1183*404b540aSrobert 
1184*404b540aSrobert   if (TREE_CODE (stmt) != MODIFY_EXPR)
1185*404b540aSrobert     return false;
1186*404b540aSrobert 
1187*404b540aSrobert   lhs = TREE_OPERAND (stmt, 0);
1188*404b540aSrobert   if (TREE_CODE (lhs) != SSA_NAME)
1189*404b540aSrobert     return false;
1190*404b540aSrobert 
1191*404b540aSrobert   rhs = TREE_OPERAND (stmt, 1);
1192*404b540aSrobert 
1193*404b540aSrobert   if (TREE_CODE (rhs) != PLUS_EXPR
1194*404b540aSrobert       && TREE_CODE (rhs) != MINUS_EXPR)
1195*404b540aSrobert     return false;
1196*404b540aSrobert 
1197*404b540aSrobert   preinc = TREE_OPERAND (rhs, 0);
1198*404b540aSrobert   if (TREE_CODE (preinc) != SSA_NAME)
1199*404b540aSrobert     return false;
1200*404b540aSrobert 
1201*404b540aSrobert   phi = SSA_NAME_DEF_STMT (preinc);
1202*404b540aSrobert   if (TREE_CODE (phi) != PHI_NODE)
1203*404b540aSrobert     return false;
1204*404b540aSrobert 
1205*404b540aSrobert   for (i = 0; i < (unsigned) PHI_NUM_ARGS (phi); i++)
1206*404b540aSrobert     if (PHI_ARG_DEF (phi, i) == lhs)
1207*404b540aSrobert       return true;
1208*404b540aSrobert 
1209*404b540aSrobert   return false;
1210*404b540aSrobert }
1211*404b540aSrobert 
1212*404b540aSrobert /* CONST_AND_COPIES is a table which maps an SSA_NAME to the current
1213*404b540aSrobert    known value for that SSA_NAME (or NULL if no value is known).
1214*404b540aSrobert 
1215*404b540aSrobert    Propagate values from CONST_AND_COPIES into the PHI nodes of the
1216*404b540aSrobert    successors of BB.  */
1217*404b540aSrobert 
1218*404b540aSrobert static void
cprop_into_successor_phis(basic_block bb)1219*404b540aSrobert cprop_into_successor_phis (basic_block bb)
1220*404b540aSrobert {
1221*404b540aSrobert   edge e;
1222*404b540aSrobert   edge_iterator ei;
1223*404b540aSrobert 
1224*404b540aSrobert   FOR_EACH_EDGE (e, ei, bb->succs)
1225*404b540aSrobert     {
1226*404b540aSrobert       tree phi;
1227*404b540aSrobert       int indx;
1228*404b540aSrobert 
1229*404b540aSrobert       /* If this is an abnormal edge, then we do not want to copy propagate
1230*404b540aSrobert 	 into the PHI alternative associated with this edge.  */
1231*404b540aSrobert       if (e->flags & EDGE_ABNORMAL)
1232*404b540aSrobert 	continue;
1233*404b540aSrobert 
1234*404b540aSrobert       phi = phi_nodes (e->dest);
1235*404b540aSrobert       if (! phi)
1236*404b540aSrobert 	continue;
1237*404b540aSrobert 
1238*404b540aSrobert       indx = e->dest_idx;
1239*404b540aSrobert       for ( ; phi; phi = PHI_CHAIN (phi))
1240*404b540aSrobert 	{
1241*404b540aSrobert 	  tree new;
1242*404b540aSrobert 	  use_operand_p orig_p;
1243*404b540aSrobert 	  tree orig;
1244*404b540aSrobert 
1245*404b540aSrobert 	  /* The alternative may be associated with a constant, so verify
1246*404b540aSrobert 	     it is an SSA_NAME before doing anything with it.  */
1247*404b540aSrobert 	  orig_p = PHI_ARG_DEF_PTR (phi, indx);
1248*404b540aSrobert 	  orig = USE_FROM_PTR (orig_p);
1249*404b540aSrobert 	  if (TREE_CODE (orig) != SSA_NAME)
1250*404b540aSrobert 	    continue;
1251*404b540aSrobert 
1252*404b540aSrobert 	  /* If we have *ORIG_P in our constant/copy table, then replace
1253*404b540aSrobert 	     ORIG_P with its value in our constant/copy table.  */
1254*404b540aSrobert 	  new = SSA_NAME_VALUE (orig);
1255*404b540aSrobert 	  if (new
1256*404b540aSrobert 	      && new != orig
1257*404b540aSrobert 	      && (TREE_CODE (new) == SSA_NAME
1258*404b540aSrobert 		  || is_gimple_min_invariant (new))
1259*404b540aSrobert 	      && may_propagate_copy (orig, new))
1260*404b540aSrobert 	    propagate_value (orig_p, new);
1261*404b540aSrobert 	}
1262*404b540aSrobert     }
1263*404b540aSrobert }
1264*404b540aSrobert 
1265*404b540aSrobert /* We have finished optimizing BB, record any information implied by
1266*404b540aSrobert    taking a specific outgoing edge from BB.  */
1267*404b540aSrobert 
1268*404b540aSrobert static void
record_edge_info(basic_block bb)1269*404b540aSrobert record_edge_info (basic_block bb)
1270*404b540aSrobert {
1271*404b540aSrobert   block_stmt_iterator bsi = bsi_last (bb);
1272*404b540aSrobert   struct edge_info *edge_info;
1273*404b540aSrobert 
1274*404b540aSrobert   if (! bsi_end_p (bsi))
1275*404b540aSrobert     {
1276*404b540aSrobert       tree stmt = bsi_stmt (bsi);
1277*404b540aSrobert 
1278*404b540aSrobert       if (stmt && TREE_CODE (stmt) == SWITCH_EXPR)
1279*404b540aSrobert 	{
1280*404b540aSrobert 	  tree cond = SWITCH_COND (stmt);
1281*404b540aSrobert 
1282*404b540aSrobert 	  if (TREE_CODE (cond) == SSA_NAME)
1283*404b540aSrobert 	    {
1284*404b540aSrobert 	      tree labels = SWITCH_LABELS (stmt);
1285*404b540aSrobert 	      int i, n_labels = TREE_VEC_LENGTH (labels);
1286*404b540aSrobert 	      tree *info = XCNEWVEC (tree, last_basic_block);
1287*404b540aSrobert 	      edge e;
1288*404b540aSrobert 	      edge_iterator ei;
1289*404b540aSrobert 
1290*404b540aSrobert 	      for (i = 0; i < n_labels; i++)
1291*404b540aSrobert 		{
1292*404b540aSrobert 		  tree label = TREE_VEC_ELT (labels, i);
1293*404b540aSrobert 		  basic_block target_bb = label_to_block (CASE_LABEL (label));
1294*404b540aSrobert 
1295*404b540aSrobert 		  if (CASE_HIGH (label)
1296*404b540aSrobert 		      || !CASE_LOW (label)
1297*404b540aSrobert 		      || info[target_bb->index])
1298*404b540aSrobert 		    info[target_bb->index] = error_mark_node;
1299*404b540aSrobert 		  else
1300*404b540aSrobert 		    info[target_bb->index] = label;
1301*404b540aSrobert 		}
1302*404b540aSrobert 
1303*404b540aSrobert 	      FOR_EACH_EDGE (e, ei, bb->succs)
1304*404b540aSrobert 		{
1305*404b540aSrobert 		  basic_block target_bb = e->dest;
1306*404b540aSrobert 		  tree node = info[target_bb->index];
1307*404b540aSrobert 
1308*404b540aSrobert 		  if (node != NULL && node != error_mark_node)
1309*404b540aSrobert 		    {
1310*404b540aSrobert 		      tree x = fold_convert (TREE_TYPE (cond), CASE_LOW (node));
1311*404b540aSrobert 		      edge_info = allocate_edge_info (e);
1312*404b540aSrobert 		      edge_info->lhs = cond;
1313*404b540aSrobert 		      edge_info->rhs = x;
1314*404b540aSrobert 		    }
1315*404b540aSrobert 		}
1316*404b540aSrobert 	      free (info);
1317*404b540aSrobert 	    }
1318*404b540aSrobert 	}
1319*404b540aSrobert 
1320*404b540aSrobert       /* A COND_EXPR may create equivalences too.  */
1321*404b540aSrobert       if (stmt && TREE_CODE (stmt) == COND_EXPR)
1322*404b540aSrobert 	{
1323*404b540aSrobert 	  tree cond = COND_EXPR_COND (stmt);
1324*404b540aSrobert 	  edge true_edge;
1325*404b540aSrobert 	  edge false_edge;
1326*404b540aSrobert 
1327*404b540aSrobert 	  extract_true_false_edges_from_block (bb, &true_edge, &false_edge);
1328*404b540aSrobert 
1329*404b540aSrobert 	  /* If the conditional is a single variable 'X', record 'X = 1'
1330*404b540aSrobert 	     for the true edge and 'X = 0' on the false edge.  */
1331*404b540aSrobert 	  if (SSA_VAR_P (cond))
1332*404b540aSrobert 	    {
1333*404b540aSrobert 	      struct edge_info *edge_info;
1334*404b540aSrobert 
1335*404b540aSrobert 	      edge_info = allocate_edge_info (true_edge);
1336*404b540aSrobert 	      edge_info->lhs = cond;
1337*404b540aSrobert 	      edge_info->rhs = constant_boolean_node (1, TREE_TYPE (cond));
1338*404b540aSrobert 
1339*404b540aSrobert 	      edge_info = allocate_edge_info (false_edge);
1340*404b540aSrobert 	      edge_info->lhs = cond;
1341*404b540aSrobert 	      edge_info->rhs = constant_boolean_node (0, TREE_TYPE (cond));
1342*404b540aSrobert 	    }
1343*404b540aSrobert 	  /* Equality tests may create one or two equivalences.  */
1344*404b540aSrobert 	  else if (COMPARISON_CLASS_P (cond))
1345*404b540aSrobert 	    {
1346*404b540aSrobert 	      tree op0 = TREE_OPERAND (cond, 0);
1347*404b540aSrobert 	      tree op1 = TREE_OPERAND (cond, 1);
1348*404b540aSrobert 
1349*404b540aSrobert 	      /* Special case comparing booleans against a constant as we
1350*404b540aSrobert 		 know the value of OP0 on both arms of the branch.  i.e., we
1351*404b540aSrobert 		 can record an equivalence for OP0 rather than COND.  */
1352*404b540aSrobert 	      if ((TREE_CODE (cond) == EQ_EXPR || TREE_CODE (cond) == NE_EXPR)
1353*404b540aSrobert 		  && TREE_CODE (op0) == SSA_NAME
1354*404b540aSrobert 		  && TREE_CODE (TREE_TYPE (op0)) == BOOLEAN_TYPE
1355*404b540aSrobert 		  && is_gimple_min_invariant (op1))
1356*404b540aSrobert 		{
1357*404b540aSrobert 		  if (TREE_CODE (cond) == EQ_EXPR)
1358*404b540aSrobert 		    {
1359*404b540aSrobert 		      edge_info = allocate_edge_info (true_edge);
1360*404b540aSrobert 		      edge_info->lhs = op0;
1361*404b540aSrobert 		      edge_info->rhs = (integer_zerop (op1)
1362*404b540aSrobert 					    ? boolean_false_node
1363*404b540aSrobert 					    : boolean_true_node);
1364*404b540aSrobert 
1365*404b540aSrobert 		      edge_info = allocate_edge_info (false_edge);
1366*404b540aSrobert 		      edge_info->lhs = op0;
1367*404b540aSrobert 		      edge_info->rhs = (integer_zerop (op1)
1368*404b540aSrobert 					    ? boolean_true_node
1369*404b540aSrobert 					    : boolean_false_node);
1370*404b540aSrobert 		    }
1371*404b540aSrobert 		  else
1372*404b540aSrobert 		    {
1373*404b540aSrobert 		      edge_info = allocate_edge_info (true_edge);
1374*404b540aSrobert 		      edge_info->lhs = op0;
1375*404b540aSrobert 		      edge_info->rhs = (integer_zerop (op1)
1376*404b540aSrobert 					    ? boolean_true_node
1377*404b540aSrobert 					    : boolean_false_node);
1378*404b540aSrobert 
1379*404b540aSrobert 		      edge_info = allocate_edge_info (false_edge);
1380*404b540aSrobert 		      edge_info->lhs = op0;
1381*404b540aSrobert 		      edge_info->rhs = (integer_zerop (op1)
1382*404b540aSrobert 					    ? boolean_false_node
1383*404b540aSrobert 					    : boolean_true_node);
1384*404b540aSrobert 		    }
1385*404b540aSrobert 		}
1386*404b540aSrobert 
1387*404b540aSrobert 	      else if (is_gimple_min_invariant (op0)
1388*404b540aSrobert 		       && (TREE_CODE (op1) == SSA_NAME
1389*404b540aSrobert 			   || is_gimple_min_invariant (op1)))
1390*404b540aSrobert 		{
1391*404b540aSrobert 		  tree inverted = invert_truthvalue (cond);
1392*404b540aSrobert 		  struct edge_info *edge_info;
1393*404b540aSrobert 
1394*404b540aSrobert 		  edge_info = allocate_edge_info (true_edge);
1395*404b540aSrobert 		  record_conditions (edge_info, cond, inverted);
1396*404b540aSrobert 
1397*404b540aSrobert 		  if (TREE_CODE (cond) == EQ_EXPR)
1398*404b540aSrobert 		    {
1399*404b540aSrobert 		      edge_info->lhs = op1;
1400*404b540aSrobert 		      edge_info->rhs = op0;
1401*404b540aSrobert 		    }
1402*404b540aSrobert 
1403*404b540aSrobert 		  edge_info = allocate_edge_info (false_edge);
1404*404b540aSrobert 		  record_conditions (edge_info, inverted, cond);
1405*404b540aSrobert 
1406*404b540aSrobert 		  if (TREE_CODE (cond) == NE_EXPR)
1407*404b540aSrobert 		    {
1408*404b540aSrobert 		      edge_info->lhs = op1;
1409*404b540aSrobert 		      edge_info->rhs = op0;
1410*404b540aSrobert 		    }
1411*404b540aSrobert 		}
1412*404b540aSrobert 
1413*404b540aSrobert 	      else if (TREE_CODE (op0) == SSA_NAME
1414*404b540aSrobert 		       && (is_gimple_min_invariant (op1)
1415*404b540aSrobert 			   || TREE_CODE (op1) == SSA_NAME))
1416*404b540aSrobert 		{
1417*404b540aSrobert 		  tree inverted = invert_truthvalue (cond);
1418*404b540aSrobert 		  struct edge_info *edge_info;
1419*404b540aSrobert 
1420*404b540aSrobert 		  edge_info = allocate_edge_info (true_edge);
1421*404b540aSrobert 		  record_conditions (edge_info, cond, inverted);
1422*404b540aSrobert 
1423*404b540aSrobert 		  if (TREE_CODE (cond) == EQ_EXPR)
1424*404b540aSrobert 		    {
1425*404b540aSrobert 		      edge_info->lhs = op0;
1426*404b540aSrobert 		      edge_info->rhs = op1;
1427*404b540aSrobert 		    }
1428*404b540aSrobert 
1429*404b540aSrobert 		  edge_info = allocate_edge_info (false_edge);
1430*404b540aSrobert 		  record_conditions (edge_info, inverted, cond);
1431*404b540aSrobert 
1432*404b540aSrobert 		  if (TREE_CODE (cond) == NE_EXPR)
1433*404b540aSrobert 		    {
1434*404b540aSrobert 		      edge_info->lhs = op0;
1435*404b540aSrobert 		      edge_info->rhs = op1;
1436*404b540aSrobert 		    }
1437*404b540aSrobert 		}
1438*404b540aSrobert 	    }
1439*404b540aSrobert 
1440*404b540aSrobert 	  /* ??? TRUTH_NOT_EXPR can create an equivalence too.  */
1441*404b540aSrobert 	}
1442*404b540aSrobert     }
1443*404b540aSrobert }
1444*404b540aSrobert 
1445*404b540aSrobert /* Propagate information from BB to its outgoing edges.
1446*404b540aSrobert 
1447*404b540aSrobert    This can include equivalency information implied by control statements
1448*404b540aSrobert    at the end of BB and const/copy propagation into PHIs in BB's
1449*404b540aSrobert    successor blocks.  */
1450*404b540aSrobert 
1451*404b540aSrobert static void
propagate_to_outgoing_edges(struct dom_walk_data * walk_data ATTRIBUTE_UNUSED,basic_block bb)1452*404b540aSrobert propagate_to_outgoing_edges (struct dom_walk_data *walk_data ATTRIBUTE_UNUSED,
1453*404b540aSrobert 			     basic_block bb)
1454*404b540aSrobert {
1455*404b540aSrobert   record_edge_info (bb);
1456*404b540aSrobert   cprop_into_successor_phis (bb);
1457*404b540aSrobert }
1458*404b540aSrobert 
1459*404b540aSrobert /* Search for redundant computations in STMT.  If any are found, then
1460*404b540aSrobert    replace them with the variable holding the result of the computation.
1461*404b540aSrobert 
1462*404b540aSrobert    If safe, record this expression into the available expression hash
1463*404b540aSrobert    table.  */
1464*404b540aSrobert 
1465*404b540aSrobert static bool
eliminate_redundant_computations(tree stmt)1466*404b540aSrobert eliminate_redundant_computations (tree stmt)
1467*404b540aSrobert {
1468*404b540aSrobert   tree *expr_p, def = NULL_TREE;
1469*404b540aSrobert   bool insert = true;
1470*404b540aSrobert   tree cached_lhs;
1471*404b540aSrobert   bool retval = false;
1472*404b540aSrobert   bool modify_expr_p = false;
1473*404b540aSrobert 
1474*404b540aSrobert   if (TREE_CODE (stmt) == MODIFY_EXPR)
1475*404b540aSrobert     def = TREE_OPERAND (stmt, 0);
1476*404b540aSrobert 
1477*404b540aSrobert   /* Certain expressions on the RHS can be optimized away, but can not
1478*404b540aSrobert      themselves be entered into the hash tables.  */
1479*404b540aSrobert   if (! def
1480*404b540aSrobert       || TREE_CODE (def) != SSA_NAME
1481*404b540aSrobert       || SSA_NAME_OCCURS_IN_ABNORMAL_PHI (def)
1482*404b540aSrobert       || !ZERO_SSA_OPERANDS (stmt, SSA_OP_VMAYDEF)
1483*404b540aSrobert       /* Do not record equivalences for increments of ivs.  This would create
1484*404b540aSrobert 	 overlapping live ranges for a very questionable gain.  */
1485*404b540aSrobert       || simple_iv_increment_p (stmt))
1486*404b540aSrobert     insert = false;
1487*404b540aSrobert 
1488*404b540aSrobert   /* Check if the expression has been computed before.  */
1489*404b540aSrobert   cached_lhs = lookup_avail_expr (stmt, insert);
1490*404b540aSrobert 
1491*404b540aSrobert   opt_stats.num_exprs_considered++;
1492*404b540aSrobert 
1493*404b540aSrobert   /* Get a pointer to the expression we are trying to optimize.  */
1494*404b540aSrobert   if (TREE_CODE (stmt) == COND_EXPR)
1495*404b540aSrobert     expr_p = &COND_EXPR_COND (stmt);
1496*404b540aSrobert   else if (TREE_CODE (stmt) == SWITCH_EXPR)
1497*404b540aSrobert     expr_p = &SWITCH_COND (stmt);
1498*404b540aSrobert   else if (TREE_CODE (stmt) == RETURN_EXPR && TREE_OPERAND (stmt, 0))
1499*404b540aSrobert     {
1500*404b540aSrobert       expr_p = &TREE_OPERAND (TREE_OPERAND (stmt, 0), 1);
1501*404b540aSrobert       modify_expr_p = true;
1502*404b540aSrobert     }
1503*404b540aSrobert   else
1504*404b540aSrobert     {
1505*404b540aSrobert       expr_p = &TREE_OPERAND (stmt, 1);
1506*404b540aSrobert       modify_expr_p = true;
1507*404b540aSrobert     }
1508*404b540aSrobert 
1509*404b540aSrobert   /* It is safe to ignore types here since we have already done
1510*404b540aSrobert      type checking in the hashing and equality routines.  In fact
1511*404b540aSrobert      type checking here merely gets in the way of constant
1512*404b540aSrobert      propagation.  Also, make sure that it is safe to propagate
1513*404b540aSrobert      CACHED_LHS into *EXPR_P.  */
1514*404b540aSrobert   if (cached_lhs
1515*404b540aSrobert       && ((TREE_CODE (cached_lhs) != SSA_NAME
1516*404b540aSrobert 	   && (modify_expr_p
1517*404b540aSrobert 	       || tree_ssa_useless_type_conversion_1 (TREE_TYPE (*expr_p),
1518*404b540aSrobert 						      TREE_TYPE (cached_lhs))))
1519*404b540aSrobert 	  || may_propagate_copy (*expr_p, cached_lhs)))
1520*404b540aSrobert     {
1521*404b540aSrobert       if (dump_file && (dump_flags & TDF_DETAILS))
1522*404b540aSrobert 	{
1523*404b540aSrobert 	  fprintf (dump_file, "  Replaced redundant expr '");
1524*404b540aSrobert 	  print_generic_expr (dump_file, *expr_p, dump_flags);
1525*404b540aSrobert 	  fprintf (dump_file, "' with '");
1526*404b540aSrobert 	  print_generic_expr (dump_file, cached_lhs, dump_flags);
1527*404b540aSrobert 	   fprintf (dump_file, "'\n");
1528*404b540aSrobert 	}
1529*404b540aSrobert 
1530*404b540aSrobert       opt_stats.num_re++;
1531*404b540aSrobert 
1532*404b540aSrobert #if defined ENABLE_CHECKING
1533*404b540aSrobert       gcc_assert (TREE_CODE (cached_lhs) == SSA_NAME
1534*404b540aSrobert 		  || is_gimple_min_invariant (cached_lhs));
1535*404b540aSrobert #endif
1536*404b540aSrobert 
1537*404b540aSrobert       if (TREE_CODE (cached_lhs) == ADDR_EXPR
1538*404b540aSrobert 	  || (POINTER_TYPE_P (TREE_TYPE (*expr_p))
1539*404b540aSrobert 	      && is_gimple_min_invariant (cached_lhs)))
1540*404b540aSrobert 	retval = true;
1541*404b540aSrobert 
1542*404b540aSrobert       if (modify_expr_p
1543*404b540aSrobert 	  && !tree_ssa_useless_type_conversion_1 (TREE_TYPE (*expr_p),
1544*404b540aSrobert 						  TREE_TYPE (cached_lhs)))
1545*404b540aSrobert 	cached_lhs = fold_convert (TREE_TYPE (*expr_p), cached_lhs);
1546*404b540aSrobert 
1547*404b540aSrobert       propagate_tree_value (expr_p, cached_lhs);
1548*404b540aSrobert       mark_stmt_modified (stmt);
1549*404b540aSrobert     }
1550*404b540aSrobert   return retval;
1551*404b540aSrobert }
1552*404b540aSrobert 
1553*404b540aSrobert /* STMT, a MODIFY_EXPR, may create certain equivalences, in either
1554*404b540aSrobert    the available expressions table or the const_and_copies table.
1555*404b540aSrobert    Detect and record those equivalences.  */
1556*404b540aSrobert 
1557*404b540aSrobert static void
record_equivalences_from_stmt(tree stmt,int may_optimize_p,stmt_ann_t ann)1558*404b540aSrobert record_equivalences_from_stmt (tree stmt,
1559*404b540aSrobert 			       int may_optimize_p,
1560*404b540aSrobert 			       stmt_ann_t ann)
1561*404b540aSrobert {
1562*404b540aSrobert   tree lhs = TREE_OPERAND (stmt, 0);
1563*404b540aSrobert   enum tree_code lhs_code = TREE_CODE (lhs);
1564*404b540aSrobert 
1565*404b540aSrobert   if (lhs_code == SSA_NAME)
1566*404b540aSrobert     {
1567*404b540aSrobert       tree rhs = TREE_OPERAND (stmt, 1);
1568*404b540aSrobert 
1569*404b540aSrobert       /* Strip away any useless type conversions.  */
1570*404b540aSrobert       STRIP_USELESS_TYPE_CONVERSION (rhs);
1571*404b540aSrobert 
1572*404b540aSrobert       /* If the RHS of the assignment is a constant or another variable that
1573*404b540aSrobert 	 may be propagated, register it in the CONST_AND_COPIES table.  We
1574*404b540aSrobert 	 do not need to record unwind data for this, since this is a true
1575*404b540aSrobert 	 assignment and not an equivalence inferred from a comparison.  All
1576*404b540aSrobert 	 uses of this ssa name are dominated by this assignment, so unwinding
1577*404b540aSrobert 	 just costs time and space.  */
1578*404b540aSrobert       if (may_optimize_p
1579*404b540aSrobert 	  && (TREE_CODE (rhs) == SSA_NAME
1580*404b540aSrobert 	      || is_gimple_min_invariant (rhs)))
1581*404b540aSrobert 	SSA_NAME_VALUE (lhs) = rhs;
1582*404b540aSrobert     }
1583*404b540aSrobert 
1584*404b540aSrobert   /* A memory store, even an aliased store, creates a useful
1585*404b540aSrobert      equivalence.  By exchanging the LHS and RHS, creating suitable
1586*404b540aSrobert      vops and recording the result in the available expression table,
1587*404b540aSrobert      we may be able to expose more redundant loads.  */
1588*404b540aSrobert   if (!ann->has_volatile_ops
1589*404b540aSrobert       && (TREE_CODE (TREE_OPERAND (stmt, 1)) == SSA_NAME
1590*404b540aSrobert 	  || is_gimple_min_invariant (TREE_OPERAND (stmt, 1)))
1591*404b540aSrobert       && !is_gimple_reg (lhs))
1592*404b540aSrobert     {
1593*404b540aSrobert       tree rhs = TREE_OPERAND (stmt, 1);
1594*404b540aSrobert       tree new;
1595*404b540aSrobert 
1596*404b540aSrobert       /* FIXME: If the LHS of the assignment is a bitfield and the RHS
1597*404b540aSrobert          is a constant, we need to adjust the constant to fit into the
1598*404b540aSrobert          type of the LHS.  If the LHS is a bitfield and the RHS is not
1599*404b540aSrobert 	 a constant, then we can not record any equivalences for this
1600*404b540aSrobert 	 statement since we would need to represent the widening or
1601*404b540aSrobert 	 narrowing of RHS.  This fixes gcc.c-torture/execute/921016-1.c
1602*404b540aSrobert 	 and should not be necessary if GCC represented bitfields
1603*404b540aSrobert 	 properly.  */
1604*404b540aSrobert       if (lhs_code == COMPONENT_REF
1605*404b540aSrobert 	  && DECL_BIT_FIELD (TREE_OPERAND (lhs, 1)))
1606*404b540aSrobert 	{
1607*404b540aSrobert 	  if (TREE_CONSTANT (rhs))
1608*404b540aSrobert 	    rhs = widen_bitfield (rhs, TREE_OPERAND (lhs, 1), lhs);
1609*404b540aSrobert 	  else
1610*404b540aSrobert 	    rhs = NULL;
1611*404b540aSrobert 
1612*404b540aSrobert 	  /* If the value overflowed, then we can not use this equivalence.  */
1613*404b540aSrobert 	  if (rhs && ! is_gimple_min_invariant (rhs))
1614*404b540aSrobert 	    rhs = NULL;
1615*404b540aSrobert 	}
1616*404b540aSrobert 
1617*404b540aSrobert       if (rhs)
1618*404b540aSrobert 	{
1619*404b540aSrobert 	  /* Build a new statement with the RHS and LHS exchanged.  */
1620*404b540aSrobert 	  new = build2 (MODIFY_EXPR, TREE_TYPE (stmt), rhs, lhs);
1621*404b540aSrobert 
1622*404b540aSrobert 	  create_ssa_artficial_load_stmt (new, stmt);
1623*404b540aSrobert 
1624*404b540aSrobert 	  /* Finally enter the statement into the available expression
1625*404b540aSrobert 	     table.  */
1626*404b540aSrobert 	  lookup_avail_expr (new, true);
1627*404b540aSrobert 	}
1628*404b540aSrobert     }
1629*404b540aSrobert }
1630*404b540aSrobert 
1631*404b540aSrobert /* Replace *OP_P in STMT with any known equivalent value for *OP_P from
1632*404b540aSrobert    CONST_AND_COPIES.  */
1633*404b540aSrobert 
1634*404b540aSrobert static bool
cprop_operand(tree stmt,use_operand_p op_p)1635*404b540aSrobert cprop_operand (tree stmt, use_operand_p op_p)
1636*404b540aSrobert {
1637*404b540aSrobert   bool may_have_exposed_new_symbols = false;
1638*404b540aSrobert   tree val;
1639*404b540aSrobert   tree op = USE_FROM_PTR (op_p);
1640*404b540aSrobert 
1641*404b540aSrobert   /* If the operand has a known constant value or it is known to be a
1642*404b540aSrobert      copy of some other variable, use the value or copy stored in
1643*404b540aSrobert      CONST_AND_COPIES.  */
1644*404b540aSrobert   val = SSA_NAME_VALUE (op);
1645*404b540aSrobert   if (val && val != op && TREE_CODE (val) != VALUE_HANDLE)
1646*404b540aSrobert     {
1647*404b540aSrobert       tree op_type, val_type;
1648*404b540aSrobert 
1649*404b540aSrobert       /* Do not change the base variable in the virtual operand
1650*404b540aSrobert 	 tables.  That would make it impossible to reconstruct
1651*404b540aSrobert 	 the renamed virtual operand if we later modify this
1652*404b540aSrobert 	 statement.  Also only allow the new value to be an SSA_NAME
1653*404b540aSrobert 	 for propagation into virtual operands.  */
1654*404b540aSrobert       if (!is_gimple_reg (op)
1655*404b540aSrobert 	  && (TREE_CODE (val) != SSA_NAME
1656*404b540aSrobert 	      || is_gimple_reg (val)
1657*404b540aSrobert 	      || get_virtual_var (val) != get_virtual_var (op)))
1658*404b540aSrobert 	return false;
1659*404b540aSrobert 
1660*404b540aSrobert       /* Do not replace hard register operands in asm statements.  */
1661*404b540aSrobert       if (TREE_CODE (stmt) == ASM_EXPR
1662*404b540aSrobert 	  && !may_propagate_copy_into_asm (op))
1663*404b540aSrobert 	return false;
1664*404b540aSrobert 
1665*404b540aSrobert       /* Get the toplevel type of each operand.  */
1666*404b540aSrobert       op_type = TREE_TYPE (op);
1667*404b540aSrobert       val_type = TREE_TYPE (val);
1668*404b540aSrobert 
1669*404b540aSrobert       /* While both types are pointers, get the type of the object
1670*404b540aSrobert 	 pointed to.  */
1671*404b540aSrobert       while (POINTER_TYPE_P (op_type) && POINTER_TYPE_P (val_type))
1672*404b540aSrobert 	{
1673*404b540aSrobert 	  op_type = TREE_TYPE (op_type);
1674*404b540aSrobert 	  val_type = TREE_TYPE (val_type);
1675*404b540aSrobert 	}
1676*404b540aSrobert 
1677*404b540aSrobert       /* Make sure underlying types match before propagating a constant by
1678*404b540aSrobert 	 converting the constant to the proper type.  Note that convert may
1679*404b540aSrobert 	 return a non-gimple expression, in which case we ignore this
1680*404b540aSrobert 	 propagation opportunity.  */
1681*404b540aSrobert       if (TREE_CODE (val) != SSA_NAME)
1682*404b540aSrobert 	{
1683*404b540aSrobert 	  if (!lang_hooks.types_compatible_p (op_type, val_type))
1684*404b540aSrobert 	    {
1685*404b540aSrobert 	      val = fold_convert (TREE_TYPE (op), val);
1686*404b540aSrobert 	      if (!is_gimple_min_invariant (val))
1687*404b540aSrobert 		return false;
1688*404b540aSrobert 	    }
1689*404b540aSrobert 	}
1690*404b540aSrobert 
1691*404b540aSrobert       /* Certain operands are not allowed to be copy propagated due
1692*404b540aSrobert 	 to their interaction with exception handling and some GCC
1693*404b540aSrobert 	 extensions.  */
1694*404b540aSrobert       else if (!may_propagate_copy (op, val))
1695*404b540aSrobert 	return false;
1696*404b540aSrobert 
1697*404b540aSrobert       /* Do not propagate copies if the propagated value is at a deeper loop
1698*404b540aSrobert 	 depth than the propagatee.  Otherwise, this may move loop variant
1699*404b540aSrobert 	 variables outside of their loops and prevent coalescing
1700*404b540aSrobert 	 opportunities.  If the value was loop invariant, it will be hoisted
1701*404b540aSrobert 	 by LICM and exposed for copy propagation.  */
1702*404b540aSrobert       if (loop_depth_of_name (val) > loop_depth_of_name (op))
1703*404b540aSrobert 	return false;
1704*404b540aSrobert 
1705*404b540aSrobert       /* Dump details.  */
1706*404b540aSrobert       if (dump_file && (dump_flags & TDF_DETAILS))
1707*404b540aSrobert 	{
1708*404b540aSrobert 	  fprintf (dump_file, "  Replaced '");
1709*404b540aSrobert 	  print_generic_expr (dump_file, op, dump_flags);
1710*404b540aSrobert 	  fprintf (dump_file, "' with %s '",
1711*404b540aSrobert 		   (TREE_CODE (val) != SSA_NAME ? "constant" : "variable"));
1712*404b540aSrobert 	  print_generic_expr (dump_file, val, dump_flags);
1713*404b540aSrobert 	  fprintf (dump_file, "'\n");
1714*404b540aSrobert 	}
1715*404b540aSrobert 
1716*404b540aSrobert       /* If VAL is an ADDR_EXPR or a constant of pointer type, note
1717*404b540aSrobert 	 that we may have exposed a new symbol for SSA renaming.  */
1718*404b540aSrobert       if (TREE_CODE (val) == ADDR_EXPR
1719*404b540aSrobert 	  || (POINTER_TYPE_P (TREE_TYPE (op))
1720*404b540aSrobert 	      && is_gimple_min_invariant (val)))
1721*404b540aSrobert 	may_have_exposed_new_symbols = true;
1722*404b540aSrobert 
1723*404b540aSrobert       if (TREE_CODE (val) != SSA_NAME)
1724*404b540aSrobert 	opt_stats.num_const_prop++;
1725*404b540aSrobert       else
1726*404b540aSrobert 	opt_stats.num_copy_prop++;
1727*404b540aSrobert 
1728*404b540aSrobert       propagate_value (op_p, val);
1729*404b540aSrobert 
1730*404b540aSrobert       /* And note that we modified this statement.  This is now
1731*404b540aSrobert 	 safe, even if we changed virtual operands since we will
1732*404b540aSrobert 	 rescan the statement and rewrite its operands again.  */
1733*404b540aSrobert       mark_stmt_modified (stmt);
1734*404b540aSrobert     }
1735*404b540aSrobert   return may_have_exposed_new_symbols;
1736*404b540aSrobert }
1737*404b540aSrobert 
1738*404b540aSrobert /* CONST_AND_COPIES is a table which maps an SSA_NAME to the current
1739*404b540aSrobert    known value for that SSA_NAME (or NULL if no value is known).
1740*404b540aSrobert 
1741*404b540aSrobert    Propagate values from CONST_AND_COPIES into the uses, vuses and
1742*404b540aSrobert    v_may_def_ops of STMT.  */
1743*404b540aSrobert 
1744*404b540aSrobert static bool
cprop_into_stmt(tree stmt)1745*404b540aSrobert cprop_into_stmt (tree stmt)
1746*404b540aSrobert {
1747*404b540aSrobert   bool may_have_exposed_new_symbols = false;
1748*404b540aSrobert   use_operand_p op_p;
1749*404b540aSrobert   ssa_op_iter iter;
1750*404b540aSrobert 
1751*404b540aSrobert   FOR_EACH_SSA_USE_OPERAND (op_p, stmt, iter, SSA_OP_ALL_USES)
1752*404b540aSrobert     {
1753*404b540aSrobert       if (TREE_CODE (USE_FROM_PTR (op_p)) == SSA_NAME)
1754*404b540aSrobert 	may_have_exposed_new_symbols |= cprop_operand (stmt, op_p);
1755*404b540aSrobert     }
1756*404b540aSrobert 
1757*404b540aSrobert   return may_have_exposed_new_symbols;
1758*404b540aSrobert }
1759*404b540aSrobert 
1760*404b540aSrobert 
1761*404b540aSrobert /* Optimize the statement pointed to by iterator SI.
1762*404b540aSrobert 
1763*404b540aSrobert    We try to perform some simplistic global redundancy elimination and
1764*404b540aSrobert    constant propagation:
1765*404b540aSrobert 
1766*404b540aSrobert    1- To detect global redundancy, we keep track of expressions that have
1767*404b540aSrobert       been computed in this block and its dominators.  If we find that the
1768*404b540aSrobert       same expression is computed more than once, we eliminate repeated
1769*404b540aSrobert       computations by using the target of the first one.
1770*404b540aSrobert 
1771*404b540aSrobert    2- Constant values and copy assignments.  This is used to do very
1772*404b540aSrobert       simplistic constant and copy propagation.  When a constant or copy
1773*404b540aSrobert       assignment is found, we map the value on the RHS of the assignment to
1774*404b540aSrobert       the variable in the LHS in the CONST_AND_COPIES table.  */
1775*404b540aSrobert 
1776*404b540aSrobert static void
optimize_stmt(struct dom_walk_data * walk_data ATTRIBUTE_UNUSED,basic_block bb,block_stmt_iterator si)1777*404b540aSrobert optimize_stmt (struct dom_walk_data *walk_data ATTRIBUTE_UNUSED,
1778*404b540aSrobert 	       basic_block bb, block_stmt_iterator si)
1779*404b540aSrobert {
1780*404b540aSrobert   stmt_ann_t ann;
1781*404b540aSrobert   tree stmt, old_stmt;
1782*404b540aSrobert   bool may_optimize_p;
1783*404b540aSrobert   bool may_have_exposed_new_symbols = false;
1784*404b540aSrobert 
1785*404b540aSrobert   old_stmt = stmt = bsi_stmt (si);
1786*404b540aSrobert 
1787*404b540aSrobert   if (TREE_CODE (stmt) == COND_EXPR)
1788*404b540aSrobert     canonicalize_comparison (stmt);
1789*404b540aSrobert 
1790*404b540aSrobert   update_stmt_if_modified (stmt);
1791*404b540aSrobert   ann = stmt_ann (stmt);
1792*404b540aSrobert   opt_stats.num_stmts++;
1793*404b540aSrobert   may_have_exposed_new_symbols = false;
1794*404b540aSrobert 
1795*404b540aSrobert   if (dump_file && (dump_flags & TDF_DETAILS))
1796*404b540aSrobert     {
1797*404b540aSrobert       fprintf (dump_file, "Optimizing statement ");
1798*404b540aSrobert       print_generic_stmt (dump_file, stmt, TDF_SLIM);
1799*404b540aSrobert     }
1800*404b540aSrobert 
1801*404b540aSrobert   /* Const/copy propagate into USES, VUSES and the RHS of V_MAY_DEFs.  */
1802*404b540aSrobert   may_have_exposed_new_symbols = cprop_into_stmt (stmt);
1803*404b540aSrobert 
1804*404b540aSrobert   /* If the statement has been modified with constant replacements,
1805*404b540aSrobert      fold its RHS before checking for redundant computations.  */
1806*404b540aSrobert   if (ann->modified)
1807*404b540aSrobert     {
1808*404b540aSrobert       tree rhs;
1809*404b540aSrobert 
1810*404b540aSrobert       /* Try to fold the statement making sure that STMT is kept
1811*404b540aSrobert 	 up to date.  */
1812*404b540aSrobert       if (fold_stmt (bsi_stmt_ptr (si)))
1813*404b540aSrobert 	{
1814*404b540aSrobert 	  stmt = bsi_stmt (si);
1815*404b540aSrobert 	  ann = stmt_ann (stmt);
1816*404b540aSrobert 
1817*404b540aSrobert 	  if (dump_file && (dump_flags & TDF_DETAILS))
1818*404b540aSrobert 	    {
1819*404b540aSrobert 	      fprintf (dump_file, "  Folded to: ");
1820*404b540aSrobert 	      print_generic_stmt (dump_file, stmt, TDF_SLIM);
1821*404b540aSrobert 	    }
1822*404b540aSrobert 	}
1823*404b540aSrobert 
1824*404b540aSrobert       rhs = get_rhs (stmt);
1825*404b540aSrobert       if (rhs && TREE_CODE (rhs) == ADDR_EXPR)
1826*404b540aSrobert 	recompute_tree_invariant_for_addr_expr (rhs);
1827*404b540aSrobert 
1828*404b540aSrobert       /* Constant/copy propagation above may change the set of
1829*404b540aSrobert 	 virtual operands associated with this statement.  Folding
1830*404b540aSrobert 	 may remove the need for some virtual operands.
1831*404b540aSrobert 
1832*404b540aSrobert 	 Indicate we will need to rescan and rewrite the statement.  */
1833*404b540aSrobert       may_have_exposed_new_symbols = true;
1834*404b540aSrobert     }
1835*404b540aSrobert 
1836*404b540aSrobert   /* Check for redundant computations.  Do this optimization only
1837*404b540aSrobert      for assignments that have no volatile ops and conditionals.  */
1838*404b540aSrobert   may_optimize_p = (!ann->has_volatile_ops
1839*404b540aSrobert 		    && ((TREE_CODE (stmt) == RETURN_EXPR
1840*404b540aSrobert 			 && TREE_OPERAND (stmt, 0)
1841*404b540aSrobert 			 && TREE_CODE (TREE_OPERAND (stmt, 0)) == MODIFY_EXPR
1842*404b540aSrobert 			 && ! (TREE_SIDE_EFFECTS
1843*404b540aSrobert 			       (TREE_OPERAND (TREE_OPERAND (stmt, 0), 1))))
1844*404b540aSrobert 			|| (TREE_CODE (stmt) == MODIFY_EXPR
1845*404b540aSrobert 			    && ! TREE_SIDE_EFFECTS (TREE_OPERAND (stmt, 1)))
1846*404b540aSrobert 			|| TREE_CODE (stmt) == COND_EXPR
1847*404b540aSrobert 			|| TREE_CODE (stmt) == SWITCH_EXPR));
1848*404b540aSrobert 
1849*404b540aSrobert   if (may_optimize_p)
1850*404b540aSrobert     may_have_exposed_new_symbols |= eliminate_redundant_computations (stmt);
1851*404b540aSrobert 
1852*404b540aSrobert   /* Record any additional equivalences created by this statement.  */
1853*404b540aSrobert   if (TREE_CODE (stmt) == MODIFY_EXPR)
1854*404b540aSrobert     record_equivalences_from_stmt (stmt,
1855*404b540aSrobert 				   may_optimize_p,
1856*404b540aSrobert 				   ann);
1857*404b540aSrobert 
1858*404b540aSrobert   /* If STMT is a COND_EXPR and it was modified, then we may know
1859*404b540aSrobert      where it goes.  If that is the case, then mark the CFG as altered.
1860*404b540aSrobert 
1861*404b540aSrobert      This will cause us to later call remove_unreachable_blocks and
1862*404b540aSrobert      cleanup_tree_cfg when it is safe to do so.  It is not safe to
1863*404b540aSrobert      clean things up here since removal of edges and such can trigger
1864*404b540aSrobert      the removal of PHI nodes, which in turn can release SSA_NAMEs to
1865*404b540aSrobert      the manager.
1866*404b540aSrobert 
1867*404b540aSrobert      That's all fine and good, except that once SSA_NAMEs are released
1868*404b540aSrobert      to the manager, we must not call create_ssa_name until all references
1869*404b540aSrobert      to released SSA_NAMEs have been eliminated.
1870*404b540aSrobert 
1871*404b540aSrobert      All references to the deleted SSA_NAMEs can not be eliminated until
1872*404b540aSrobert      we remove unreachable blocks.
1873*404b540aSrobert 
1874*404b540aSrobert      We can not remove unreachable blocks until after we have completed
1875*404b540aSrobert      any queued jump threading.
1876*404b540aSrobert 
1877*404b540aSrobert      We can not complete any queued jump threads until we have taken
1878*404b540aSrobert      appropriate variables out of SSA form.  Taking variables out of
1879*404b540aSrobert      SSA form can call create_ssa_name and thus we lose.
1880*404b540aSrobert 
1881*404b540aSrobert      Ultimately I suspect we're going to need to change the interface
1882*404b540aSrobert      into the SSA_NAME manager.  */
1883*404b540aSrobert 
1884*404b540aSrobert   if (ann->modified)
1885*404b540aSrobert     {
1886*404b540aSrobert       tree val = NULL;
1887*404b540aSrobert 
1888*404b540aSrobert       if (TREE_CODE (stmt) == COND_EXPR)
1889*404b540aSrobert 	val = COND_EXPR_COND (stmt);
1890*404b540aSrobert       else if (TREE_CODE (stmt) == SWITCH_EXPR)
1891*404b540aSrobert 	val = SWITCH_COND (stmt);
1892*404b540aSrobert 
1893*404b540aSrobert       if (val && TREE_CODE (val) == INTEGER_CST && find_taken_edge (bb, val))
1894*404b540aSrobert 	cfg_altered = true;
1895*404b540aSrobert 
1896*404b540aSrobert       /* If we simplified a statement in such a way as to be shown that it
1897*404b540aSrobert 	 cannot trap, update the eh information and the cfg to match.  */
1898*404b540aSrobert       if (maybe_clean_or_replace_eh_stmt (old_stmt, stmt))
1899*404b540aSrobert 	{
1900*404b540aSrobert 	  bitmap_set_bit (need_eh_cleanup, bb->index);
1901*404b540aSrobert 	  if (dump_file && (dump_flags & TDF_DETAILS))
1902*404b540aSrobert 	    fprintf (dump_file, "  Flagged to clear EH edges.\n");
1903*404b540aSrobert 	}
1904*404b540aSrobert     }
1905*404b540aSrobert 
1906*404b540aSrobert   if (may_have_exposed_new_symbols)
1907*404b540aSrobert     VEC_safe_push (tree, heap, stmts_to_rescan, bsi_stmt (si));
1908*404b540aSrobert }
1909*404b540aSrobert 
1910*404b540aSrobert /* Search for an existing instance of STMT in the AVAIL_EXPRS table.  If
1911*404b540aSrobert    found, return its LHS. Otherwise insert STMT in the table and return
1912*404b540aSrobert    NULL_TREE.
1913*404b540aSrobert 
1914*404b540aSrobert    Also, when an expression is first inserted in the AVAIL_EXPRS table, it
1915*404b540aSrobert    is also added to the stack pointed to by BLOCK_AVAIL_EXPRS_P, so that they
1916*404b540aSrobert    can be removed when we finish processing this block and its children.
1917*404b540aSrobert 
1918*404b540aSrobert    NOTE: This function assumes that STMT is a MODIFY_EXPR node that
1919*404b540aSrobert    contains no CALL_EXPR on its RHS and makes no volatile nor
1920*404b540aSrobert    aliased references.  */
1921*404b540aSrobert 
1922*404b540aSrobert static tree
lookup_avail_expr(tree stmt,bool insert)1923*404b540aSrobert lookup_avail_expr (tree stmt, bool insert)
1924*404b540aSrobert {
1925*404b540aSrobert   void **slot;
1926*404b540aSrobert   tree lhs;
1927*404b540aSrobert   tree temp;
1928*404b540aSrobert   struct expr_hash_elt *element = XNEW (struct expr_hash_elt);
1929*404b540aSrobert 
1930*404b540aSrobert   lhs = TREE_CODE (stmt) == MODIFY_EXPR ? TREE_OPERAND (stmt, 0) : NULL;
1931*404b540aSrobert 
1932*404b540aSrobert   initialize_hash_element (stmt, lhs, element);
1933*404b540aSrobert 
1934*404b540aSrobert   /* Don't bother remembering constant assignments and copy operations.
1935*404b540aSrobert      Constants and copy operations are handled by the constant/copy propagator
1936*404b540aSrobert      in optimize_stmt.  */
1937*404b540aSrobert   if (TREE_CODE (element->rhs) == SSA_NAME
1938*404b540aSrobert       || is_gimple_min_invariant (element->rhs))
1939*404b540aSrobert     {
1940*404b540aSrobert       free (element);
1941*404b540aSrobert       return NULL_TREE;
1942*404b540aSrobert     }
1943*404b540aSrobert 
1944*404b540aSrobert   /* Finally try to find the expression in the main expression hash table.  */
1945*404b540aSrobert   slot = htab_find_slot_with_hash (avail_exprs, element, element->hash,
1946*404b540aSrobert 				   (insert ? INSERT : NO_INSERT));
1947*404b540aSrobert   if (slot == NULL)
1948*404b540aSrobert     {
1949*404b540aSrobert       free (element);
1950*404b540aSrobert       return NULL_TREE;
1951*404b540aSrobert     }
1952*404b540aSrobert 
1953*404b540aSrobert   if (*slot == NULL)
1954*404b540aSrobert     {
1955*404b540aSrobert       *slot = (void *) element;
1956*404b540aSrobert       VEC_safe_push (tree, heap, avail_exprs_stack,
1957*404b540aSrobert 		     stmt ? stmt : element->rhs);
1958*404b540aSrobert       return NULL_TREE;
1959*404b540aSrobert     }
1960*404b540aSrobert 
1961*404b540aSrobert   /* Extract the LHS of the assignment so that it can be used as the current
1962*404b540aSrobert      definition of another variable.  */
1963*404b540aSrobert   lhs = ((struct expr_hash_elt *)*slot)->lhs;
1964*404b540aSrobert 
1965*404b540aSrobert   /* See if the LHS appears in the CONST_AND_COPIES table.  If it does, then
1966*404b540aSrobert      use the value from the const_and_copies table.  */
1967*404b540aSrobert   if (TREE_CODE (lhs) == SSA_NAME)
1968*404b540aSrobert     {
1969*404b540aSrobert       temp = SSA_NAME_VALUE (lhs);
1970*404b540aSrobert       if (temp && TREE_CODE (temp) != VALUE_HANDLE)
1971*404b540aSrobert 	lhs = temp;
1972*404b540aSrobert     }
1973*404b540aSrobert 
1974*404b540aSrobert   free (element);
1975*404b540aSrobert   return lhs;
1976*404b540aSrobert }
1977*404b540aSrobert 
1978*404b540aSrobert /* Hashing and equality functions for AVAIL_EXPRS.  The table stores
1979*404b540aSrobert    MODIFY_EXPR statements.  We compute a value number for expressions using
1980*404b540aSrobert    the code of the expression and the SSA numbers of its operands.  */
1981*404b540aSrobert 
1982*404b540aSrobert static hashval_t
avail_expr_hash(const void * p)1983*404b540aSrobert avail_expr_hash (const void *p)
1984*404b540aSrobert {
1985*404b540aSrobert   tree stmt = ((struct expr_hash_elt *)p)->stmt;
1986*404b540aSrobert   tree rhs = ((struct expr_hash_elt *)p)->rhs;
1987*404b540aSrobert   tree vuse;
1988*404b540aSrobert   ssa_op_iter iter;
1989*404b540aSrobert   hashval_t val = 0;
1990*404b540aSrobert 
1991*404b540aSrobert   /* iterative_hash_expr knows how to deal with any expression and
1992*404b540aSrobert      deals with commutative operators as well, so just use it instead
1993*404b540aSrobert      of duplicating such complexities here.  */
1994*404b540aSrobert   val = iterative_hash_expr (rhs, val);
1995*404b540aSrobert 
1996*404b540aSrobert   /* If the hash table entry is not associated with a statement, then we
1997*404b540aSrobert      can just hash the expression and not worry about virtual operands
1998*404b540aSrobert      and such.  */
1999*404b540aSrobert   if (!stmt || !stmt_ann (stmt))
2000*404b540aSrobert     return val;
2001*404b540aSrobert 
2002*404b540aSrobert   /* Add the SSA version numbers of every vuse operand.  This is important
2003*404b540aSrobert      because compound variables like arrays are not renamed in the
2004*404b540aSrobert      operands.  Rather, the rename is done on the virtual variable
2005*404b540aSrobert      representing all the elements of the array.  */
2006*404b540aSrobert   FOR_EACH_SSA_TREE_OPERAND (vuse, stmt, iter, SSA_OP_VUSE)
2007*404b540aSrobert     val = iterative_hash_expr (vuse, val);
2008*404b540aSrobert 
2009*404b540aSrobert   return val;
2010*404b540aSrobert }
2011*404b540aSrobert 
2012*404b540aSrobert static hashval_t
real_avail_expr_hash(const void * p)2013*404b540aSrobert real_avail_expr_hash (const void *p)
2014*404b540aSrobert {
2015*404b540aSrobert   return ((const struct expr_hash_elt *)p)->hash;
2016*404b540aSrobert }
2017*404b540aSrobert 
2018*404b540aSrobert static int
avail_expr_eq(const void * p1,const void * p2)2019*404b540aSrobert avail_expr_eq (const void *p1, const void *p2)
2020*404b540aSrobert {
2021*404b540aSrobert   tree stmt1 = ((struct expr_hash_elt *)p1)->stmt;
2022*404b540aSrobert   tree rhs1 = ((struct expr_hash_elt *)p1)->rhs;
2023*404b540aSrobert   tree stmt2 = ((struct expr_hash_elt *)p2)->stmt;
2024*404b540aSrobert   tree rhs2 = ((struct expr_hash_elt *)p2)->rhs;
2025*404b540aSrobert 
2026*404b540aSrobert   /* If they are the same physical expression, return true.  */
2027*404b540aSrobert   if (rhs1 == rhs2 && stmt1 == stmt2)
2028*404b540aSrobert     return true;
2029*404b540aSrobert 
2030*404b540aSrobert   /* If their codes are not equal, then quit now.  */
2031*404b540aSrobert   if (TREE_CODE (rhs1) != TREE_CODE (rhs2))
2032*404b540aSrobert     return false;
2033*404b540aSrobert 
2034*404b540aSrobert   /* In case of a collision, both RHS have to be identical and have the
2035*404b540aSrobert      same VUSE operands.  */
2036*404b540aSrobert   if ((TREE_TYPE (rhs1) == TREE_TYPE (rhs2)
2037*404b540aSrobert        || lang_hooks.types_compatible_p (TREE_TYPE (rhs1), TREE_TYPE (rhs2)))
2038*404b540aSrobert       && operand_equal_p (rhs1, rhs2, OEP_PURE_SAME))
2039*404b540aSrobert     {
2040*404b540aSrobert       bool ret = compare_ssa_operands_equal (stmt1, stmt2, SSA_OP_VUSE);
2041*404b540aSrobert       gcc_assert (!ret || ((struct expr_hash_elt *)p1)->hash
2042*404b540aSrobert 		  == ((struct expr_hash_elt *)p2)->hash);
2043*404b540aSrobert       return ret;
2044*404b540aSrobert     }
2045*404b540aSrobert 
2046*404b540aSrobert   return false;
2047*404b540aSrobert }
2048*404b540aSrobert 
2049*404b540aSrobert /* PHI-ONLY copy and constant propagation.  This pass is meant to clean
2050*404b540aSrobert    up degenerate PHIs created by or exposed by jump threading.  */
2051*404b540aSrobert 
2052*404b540aSrobert /* Given PHI, return its RHS if the PHI is a degenerate, otherwise return
2053*404b540aSrobert    NULL.  */
2054*404b540aSrobert 
2055*404b540aSrobert static tree
degenerate_phi_result(tree phi)2056*404b540aSrobert degenerate_phi_result (tree phi)
2057*404b540aSrobert {
2058*404b540aSrobert   tree lhs = PHI_RESULT (phi);
2059*404b540aSrobert   tree val = NULL;
2060*404b540aSrobert   int i;
2061*404b540aSrobert 
2062*404b540aSrobert   /* Ignoring arguments which are the same as LHS, if all the remaining
2063*404b540aSrobert      arguments are the same, then the PHI is a degenerate and has the
2064*404b540aSrobert      value of that common argument.  */
2065*404b540aSrobert   for (i = 0; i < PHI_NUM_ARGS (phi); i++)
2066*404b540aSrobert     {
2067*404b540aSrobert       tree arg = PHI_ARG_DEF (phi, i);
2068*404b540aSrobert 
2069*404b540aSrobert       if (arg == lhs)
2070*404b540aSrobert 	continue;
2071*404b540aSrobert       else if (!val)
2072*404b540aSrobert 	val = arg;
2073*404b540aSrobert       else if (!operand_equal_p (arg, val, 0))
2074*404b540aSrobert 	break;
2075*404b540aSrobert     }
2076*404b540aSrobert   return (i == PHI_NUM_ARGS (phi) ? val : NULL);
2077*404b540aSrobert }
2078*404b540aSrobert 
2079*404b540aSrobert /* Given a tree node T, which is either a PHI_NODE or MODIFY_EXPR,
2080*404b540aSrobert    remove it from the IL.  */
2081*404b540aSrobert 
2082*404b540aSrobert static void
remove_stmt_or_phi(tree t)2083*404b540aSrobert remove_stmt_or_phi (tree t)
2084*404b540aSrobert {
2085*404b540aSrobert   if (TREE_CODE (t) == PHI_NODE)
2086*404b540aSrobert     remove_phi_node (t, NULL);
2087*404b540aSrobert   else
2088*404b540aSrobert     {
2089*404b540aSrobert       block_stmt_iterator bsi = bsi_for_stmt (t);
2090*404b540aSrobert       bsi_remove (&bsi, true);
2091*404b540aSrobert     }
2092*404b540aSrobert }
2093*404b540aSrobert 
2094*404b540aSrobert /* Given a tree node T, which is either a PHI_NODE or MODIFY_EXPR,
2095*404b540aSrobert    return the "rhs" of the node, in the case of a non-degenerate
2096*404b540aSrobert    PHI, NULL is returned.  */
2097*404b540aSrobert 
2098*404b540aSrobert static tree
get_rhs_or_phi_arg(tree t)2099*404b540aSrobert get_rhs_or_phi_arg (tree t)
2100*404b540aSrobert {
2101*404b540aSrobert   if (TREE_CODE (t) == PHI_NODE)
2102*404b540aSrobert     return degenerate_phi_result (t);
2103*404b540aSrobert   else if (TREE_CODE (t) == MODIFY_EXPR)
2104*404b540aSrobert     return TREE_OPERAND (t, 1);
2105*404b540aSrobert   gcc_unreachable ();
2106*404b540aSrobert }
2107*404b540aSrobert 
2108*404b540aSrobert 
2109*404b540aSrobert /* Given a tree node T, which is either a PHI_NODE or a MODIFY_EXPR,
2110*404b540aSrobert    return the "lhs" of the node.  */
2111*404b540aSrobert 
2112*404b540aSrobert static tree
get_lhs_or_phi_result(tree t)2113*404b540aSrobert get_lhs_or_phi_result (tree t)
2114*404b540aSrobert {
2115*404b540aSrobert   if (TREE_CODE (t) == PHI_NODE)
2116*404b540aSrobert     return PHI_RESULT (t);
2117*404b540aSrobert   else if (TREE_CODE (t) == MODIFY_EXPR)
2118*404b540aSrobert     return TREE_OPERAND (t, 0);
2119*404b540aSrobert   gcc_unreachable ();
2120*404b540aSrobert }
2121*404b540aSrobert 
2122*404b540aSrobert /* Propagate RHS into all uses of LHS (when possible).
2123*404b540aSrobert 
2124*404b540aSrobert    RHS and LHS are derived from STMT, which is passed in solely so
2125*404b540aSrobert    that we can remove it if propagation is successful.
2126*404b540aSrobert 
2127*404b540aSrobert    When propagating into a PHI node or into a statement which turns
2128*404b540aSrobert    into a trivial copy or constant initialization, set the
2129*404b540aSrobert    appropriate bit in INTERESTING_NAMEs so that we will visit those
2130*404b540aSrobert    nodes as well in an effort to pick up secondary optimization
2131*404b540aSrobert    opportunities.  */
2132*404b540aSrobert 
2133*404b540aSrobert static void
propagate_rhs_into_lhs(tree stmt,tree lhs,tree rhs,bitmap interesting_names)2134*404b540aSrobert propagate_rhs_into_lhs (tree stmt, tree lhs, tree rhs, bitmap interesting_names)
2135*404b540aSrobert {
2136*404b540aSrobert   /* First verify that propagation is valid and isn't going to move a
2137*404b540aSrobert      loop variant variable outside its loop.  */
2138*404b540aSrobert   if (! SSA_NAME_OCCURS_IN_ABNORMAL_PHI (lhs)
2139*404b540aSrobert       && (TREE_CODE (rhs) != SSA_NAME
2140*404b540aSrobert 	  || ! SSA_NAME_OCCURS_IN_ABNORMAL_PHI (rhs))
2141*404b540aSrobert       && may_propagate_copy (lhs, rhs)
2142*404b540aSrobert       && loop_depth_of_name (lhs) >= loop_depth_of_name (rhs))
2143*404b540aSrobert     {
2144*404b540aSrobert       use_operand_p use_p;
2145*404b540aSrobert       imm_use_iterator iter;
2146*404b540aSrobert       tree use_stmt;
2147*404b540aSrobert       bool all = true;
2148*404b540aSrobert 
2149*404b540aSrobert       /* Dump details.  */
2150*404b540aSrobert       if (dump_file && (dump_flags & TDF_DETAILS))
2151*404b540aSrobert 	{
2152*404b540aSrobert 	  fprintf (dump_file, "  Replacing '");
2153*404b540aSrobert 	  print_generic_expr (dump_file, lhs, dump_flags);
2154*404b540aSrobert 	  fprintf (dump_file, "' with %s '",
2155*404b540aSrobert 	           (TREE_CODE (rhs) != SSA_NAME ? "constant" : "variable"));
2156*404b540aSrobert 		   print_generic_expr (dump_file, rhs, dump_flags);
2157*404b540aSrobert 	  fprintf (dump_file, "'\n");
2158*404b540aSrobert 	}
2159*404b540aSrobert 
2160*404b540aSrobert       /* Walk over every use of LHS and try to replace the use with RHS.
2161*404b540aSrobert 	 At this point the only reason why such a propagation would not
2162*404b540aSrobert 	 be successful would be if the use occurs in an ASM_EXPR.  */
2163*404b540aSrobert       FOR_EACH_IMM_USE_STMT (use_stmt, iter, lhs)
2164*404b540aSrobert 	{
2165*404b540aSrobert 
2166*404b540aSrobert 	  /* It's not always safe to propagate into an ASM_EXPR.  */
2167*404b540aSrobert 	  if (TREE_CODE (use_stmt) == ASM_EXPR
2168*404b540aSrobert 	      && ! may_propagate_copy_into_asm (lhs))
2169*404b540aSrobert 	    {
2170*404b540aSrobert 	      all = false;
2171*404b540aSrobert 	      continue;
2172*404b540aSrobert 	    }
2173*404b540aSrobert 
2174*404b540aSrobert 	  /* Dump details.  */
2175*404b540aSrobert 	  if (dump_file && (dump_flags & TDF_DETAILS))
2176*404b540aSrobert 	    {
2177*404b540aSrobert 	      fprintf (dump_file, "    Original statement:");
2178*404b540aSrobert 	      print_generic_expr (dump_file, use_stmt, dump_flags);
2179*404b540aSrobert 	      fprintf (dump_file, "\n");
2180*404b540aSrobert 	    }
2181*404b540aSrobert 
2182*404b540aSrobert 	  /* Propagate the RHS into this use of the LHS.  */
2183*404b540aSrobert 	  FOR_EACH_IMM_USE_ON_STMT (use_p, iter)
2184*404b540aSrobert 	    propagate_value (use_p, rhs);
2185*404b540aSrobert 
2186*404b540aSrobert 	  /* Special cases to avoid useless calls into the folding
2187*404b540aSrobert 	     routines, operand scanning, etc.
2188*404b540aSrobert 
2189*404b540aSrobert 	     First, propagation into a PHI may cause the PHI to become
2190*404b540aSrobert 	     a degenerate, so mark the PHI as interesting.  No other
2191*404b540aSrobert 	     actions are necessary.
2192*404b540aSrobert 
2193*404b540aSrobert 	     Second, if we're propagating a virtual operand and the
2194*404b540aSrobert 	     propagation does not change the underlying _DECL node for
2195*404b540aSrobert 	     the virtual operand, then no further actions are necessary.  */
2196*404b540aSrobert 	  if (TREE_CODE (use_stmt) == PHI_NODE
2197*404b540aSrobert 	      || (! is_gimple_reg (lhs)
2198*404b540aSrobert 		  && TREE_CODE (rhs) == SSA_NAME
2199*404b540aSrobert 		  && SSA_NAME_VAR (lhs) == SSA_NAME_VAR (rhs)))
2200*404b540aSrobert 	    {
2201*404b540aSrobert 	      /* Dump details.  */
2202*404b540aSrobert 	      if (dump_file && (dump_flags & TDF_DETAILS))
2203*404b540aSrobert 		{
2204*404b540aSrobert 		  fprintf (dump_file, "    Updated statement:");
2205*404b540aSrobert 		  print_generic_expr (dump_file, use_stmt, dump_flags);
2206*404b540aSrobert 		  fprintf (dump_file, "\n");
2207*404b540aSrobert 		}
2208*404b540aSrobert 
2209*404b540aSrobert 	      /* Propagation into a PHI may expose new degenerate PHIs,
2210*404b540aSrobert 		 so mark the result of the PHI as interesting.  */
2211*404b540aSrobert 	      if (TREE_CODE (use_stmt) == PHI_NODE)
2212*404b540aSrobert 		{
2213*404b540aSrobert 		  tree result = get_lhs_or_phi_result (use_stmt);
2214*404b540aSrobert 		  bitmap_set_bit (interesting_names, SSA_NAME_VERSION (result));
2215*404b540aSrobert 		}
2216*404b540aSrobert 	      continue;
2217*404b540aSrobert 	    }
2218*404b540aSrobert 
2219*404b540aSrobert 	  /* From this point onward we are propagating into a
2220*404b540aSrobert 	     real statement.  Folding may (or may not) be possible,
2221*404b540aSrobert 	     we may expose new operands, expose dead EH edges,
2222*404b540aSrobert 	     etc.  */
2223*404b540aSrobert 	  fold_stmt_inplace (use_stmt);
2224*404b540aSrobert 
2225*404b540aSrobert 	  /* Sometimes propagation can expose new operands to the
2226*404b540aSrobert 	     renamer.  Note this will call update_stmt at the
2227*404b540aSrobert 	     appropriate time.  */
2228*404b540aSrobert 	  mark_new_vars_to_rename (use_stmt);
2229*404b540aSrobert 
2230*404b540aSrobert 	  /* Dump details.  */
2231*404b540aSrobert 	  if (dump_file && (dump_flags & TDF_DETAILS))
2232*404b540aSrobert 	    {
2233*404b540aSrobert 	      fprintf (dump_file, "    Updated statement:");
2234*404b540aSrobert 	      print_generic_expr (dump_file, use_stmt, dump_flags);
2235*404b540aSrobert 	      fprintf (dump_file, "\n");
2236*404b540aSrobert 	    }
2237*404b540aSrobert 
2238*404b540aSrobert 	  /* If we replaced a variable index with a constant, then
2239*404b540aSrobert 	     we would need to update the invariant flag for ADDR_EXPRs.  */
2240*404b540aSrobert 	  if (TREE_CODE (use_stmt) == MODIFY_EXPR
2241*404b540aSrobert 	      && TREE_CODE (TREE_OPERAND (use_stmt, 1)) == ADDR_EXPR)
2242*404b540aSrobert 	    recompute_tree_invariant_for_addr_expr (TREE_OPERAND (use_stmt, 1));
2243*404b540aSrobert 
2244*404b540aSrobert 	  /* If we cleaned up EH information from the statement,
2245*404b540aSrobert 	     mark its containing block as needing EH cleanups.  */
2246*404b540aSrobert 	  if (maybe_clean_or_replace_eh_stmt (use_stmt, use_stmt))
2247*404b540aSrobert 	    {
2248*404b540aSrobert 	      bitmap_set_bit (need_eh_cleanup, bb_for_stmt (use_stmt)->index);
2249*404b540aSrobert 	      if (dump_file && (dump_flags & TDF_DETAILS))
2250*404b540aSrobert 		fprintf (dump_file, "  Flagged to clear EH edges.\n");
2251*404b540aSrobert 	    }
2252*404b540aSrobert 
2253*404b540aSrobert 	  /* Propagation may expose new trivial copy/constant propagation
2254*404b540aSrobert 	     opportunities.  */
2255*404b540aSrobert 	  if (TREE_CODE (use_stmt) == MODIFY_EXPR
2256*404b540aSrobert 	      && TREE_CODE (TREE_OPERAND (use_stmt, 0)) == SSA_NAME
2257*404b540aSrobert 	      && (TREE_CODE (TREE_OPERAND (use_stmt, 1)) == SSA_NAME
2258*404b540aSrobert 		  || is_gimple_min_invariant (TREE_OPERAND (use_stmt, 1))))
2259*404b540aSrobert 	    {
2260*404b540aSrobert 	      tree result = get_lhs_or_phi_result (use_stmt);
2261*404b540aSrobert 	      bitmap_set_bit (interesting_names, SSA_NAME_VERSION (result));
2262*404b540aSrobert 	    }
2263*404b540aSrobert 
2264*404b540aSrobert 	  /* Propagation into these nodes may make certain edges in
2265*404b540aSrobert 	     the CFG unexecutable.  We want to identify them as PHI nodes
2266*404b540aSrobert 	     at the destination of those unexecutable edges may become
2267*404b540aSrobert 	     degenerates.  */
2268*404b540aSrobert 	  else if (TREE_CODE (use_stmt) == COND_EXPR
2269*404b540aSrobert 		   || TREE_CODE (use_stmt) == SWITCH_EXPR
2270*404b540aSrobert 		   || TREE_CODE (use_stmt) == GOTO_EXPR)
2271*404b540aSrobert 	    {
2272*404b540aSrobert 	      tree val;
2273*404b540aSrobert 
2274*404b540aSrobert 	      if (TREE_CODE (use_stmt) == COND_EXPR)
2275*404b540aSrobert 		val = COND_EXPR_COND (use_stmt);
2276*404b540aSrobert 	      else if (TREE_CODE (use_stmt) == SWITCH_EXPR)
2277*404b540aSrobert 		val = SWITCH_COND (use_stmt);
2278*404b540aSrobert 	      else
2279*404b540aSrobert 		val = GOTO_DESTINATION  (use_stmt);
2280*404b540aSrobert 
2281*404b540aSrobert 	      if (is_gimple_min_invariant (val))
2282*404b540aSrobert 		{
2283*404b540aSrobert 		  basic_block bb = bb_for_stmt (use_stmt);
2284*404b540aSrobert 		  edge te = find_taken_edge (bb, val);
2285*404b540aSrobert 		  edge_iterator ei;
2286*404b540aSrobert 		  edge e;
2287*404b540aSrobert 		  block_stmt_iterator bsi;
2288*404b540aSrobert 
2289*404b540aSrobert 		  /* Remove all outgoing edges except TE.  */
2290*404b540aSrobert 		  for (ei = ei_start (bb->succs); (e = ei_safe_edge (ei));)
2291*404b540aSrobert 		    {
2292*404b540aSrobert 		      if (e != te)
2293*404b540aSrobert 			{
2294*404b540aSrobert 			  tree phi;
2295*404b540aSrobert 
2296*404b540aSrobert 			  /* Mark all the PHI nodes at the destination of
2297*404b540aSrobert 			     the unexecutable edge as interesting.  */
2298*404b540aSrobert 			  for (phi = phi_nodes (e->dest);
2299*404b540aSrobert 			       phi;
2300*404b540aSrobert 			       phi = PHI_CHAIN (phi))
2301*404b540aSrobert 			    {
2302*404b540aSrobert 			      tree result = PHI_RESULT (phi);
2303*404b540aSrobert 			      int version = SSA_NAME_VERSION (result);
2304*404b540aSrobert 
2305*404b540aSrobert 			      bitmap_set_bit (interesting_names, version);
2306*404b540aSrobert 			    }
2307*404b540aSrobert 
2308*404b540aSrobert 			  te->probability += e->probability;
2309*404b540aSrobert 
2310*404b540aSrobert 			  te->count += e->count;
2311*404b540aSrobert 			  remove_edge (e);
2312*404b540aSrobert 			  cfg_altered = 1;
2313*404b540aSrobert 			}
2314*404b540aSrobert 		      else
2315*404b540aSrobert 			ei_next (&ei);
2316*404b540aSrobert 		    }
2317*404b540aSrobert 
2318*404b540aSrobert 		  bsi = bsi_last (bb_for_stmt (use_stmt));
2319*404b540aSrobert 		  bsi_remove (&bsi, true);
2320*404b540aSrobert 
2321*404b540aSrobert 		  /* And fixup the flags on the single remaining edge.  */
2322*404b540aSrobert 		  te->flags &= ~(EDGE_TRUE_VALUE | EDGE_FALSE_VALUE);
2323*404b540aSrobert 		  te->flags &= ~EDGE_ABNORMAL;
2324*404b540aSrobert 		  te->flags |= EDGE_FALLTHRU;
2325*404b540aSrobert 		  if (te->probability > REG_BR_PROB_BASE)
2326*404b540aSrobert 		    te->probability = REG_BR_PROB_BASE;
2327*404b540aSrobert 	        }
2328*404b540aSrobert 	    }
2329*404b540aSrobert 	}
2330*404b540aSrobert 
2331*404b540aSrobert       /* Ensure there is nothing else to do. */
2332*404b540aSrobert       gcc_assert (!all || has_zero_uses (lhs));
2333*404b540aSrobert 
2334*404b540aSrobert       /* If we were able to propagate away all uses of LHS, then
2335*404b540aSrobert 	 we can remove STMT.  */
2336*404b540aSrobert       if (all)
2337*404b540aSrobert 	remove_stmt_or_phi (stmt);
2338*404b540aSrobert     }
2339*404b540aSrobert }
2340*404b540aSrobert 
2341*404b540aSrobert /* T is either a PHI node (potentially a degenerate PHI node) or
2342*404b540aSrobert    a statement that is a trivial copy or constant initialization.
2343*404b540aSrobert 
2344*404b540aSrobert    Attempt to eliminate T by propagating its RHS into all uses of
2345*404b540aSrobert    its LHS.  This may in turn set new bits in INTERESTING_NAMES
2346*404b540aSrobert    for nodes we want to revisit later.
2347*404b540aSrobert 
2348*404b540aSrobert    All exit paths should clear INTERESTING_NAMES for the result
2349*404b540aSrobert    of T.  */
2350*404b540aSrobert 
2351*404b540aSrobert static void
eliminate_const_or_copy(tree t,bitmap interesting_names)2352*404b540aSrobert eliminate_const_or_copy (tree t, bitmap interesting_names)
2353*404b540aSrobert {
2354*404b540aSrobert   tree lhs = get_lhs_or_phi_result (t);
2355*404b540aSrobert   tree rhs;
2356*404b540aSrobert   int version = SSA_NAME_VERSION (lhs);
2357*404b540aSrobert 
2358*404b540aSrobert   /* If the LHS of this statement or PHI has no uses, then we can
2359*404b540aSrobert      just eliminate it.  This can occur if, for example, the PHI
2360*404b540aSrobert      was created by block duplication due to threading and its only
2361*404b540aSrobert      use was in the conditional at the end of the block which was
2362*404b540aSrobert      deleted.  */
2363*404b540aSrobert   if (has_zero_uses (lhs))
2364*404b540aSrobert     {
2365*404b540aSrobert       bitmap_clear_bit (interesting_names, version);
2366*404b540aSrobert       remove_stmt_or_phi (t);
2367*404b540aSrobert       return;
2368*404b540aSrobert     }
2369*404b540aSrobert 
2370*404b540aSrobert   /* Get the RHS of the assignment or PHI node if the PHI is a
2371*404b540aSrobert      degenerate.  */
2372*404b540aSrobert   rhs = get_rhs_or_phi_arg (t);
2373*404b540aSrobert   if (!rhs)
2374*404b540aSrobert     {
2375*404b540aSrobert       bitmap_clear_bit (interesting_names, version);
2376*404b540aSrobert       return;
2377*404b540aSrobert     }
2378*404b540aSrobert 
2379*404b540aSrobert   propagate_rhs_into_lhs (t, lhs, rhs, interesting_names);
2380*404b540aSrobert 
2381*404b540aSrobert   /* Note that T may well have been deleted by now, so do
2382*404b540aSrobert      not access it, instead use the saved version # to clear
2383*404b540aSrobert      T's entry in the worklist.  */
2384*404b540aSrobert   bitmap_clear_bit (interesting_names, version);
2385*404b540aSrobert }
2386*404b540aSrobert 
2387*404b540aSrobert /* The first phase in degenerate PHI elimination.
2388*404b540aSrobert 
2389*404b540aSrobert    Eliminate the degenerate PHIs in BB, then recurse on the
2390*404b540aSrobert    dominator children of BB.  */
2391*404b540aSrobert 
2392*404b540aSrobert static void
eliminate_degenerate_phis_1(basic_block bb,bitmap interesting_names)2393*404b540aSrobert eliminate_degenerate_phis_1 (basic_block bb, bitmap interesting_names)
2394*404b540aSrobert {
2395*404b540aSrobert   tree phi, next;
2396*404b540aSrobert   basic_block son;
2397*404b540aSrobert 
2398*404b540aSrobert   for (phi = phi_nodes (bb); phi; phi = next)
2399*404b540aSrobert     {
2400*404b540aSrobert       next = PHI_CHAIN (phi);
2401*404b540aSrobert       eliminate_const_or_copy (phi, interesting_names);
2402*404b540aSrobert     }
2403*404b540aSrobert 
2404*404b540aSrobert   /* Recurse into the dominator children of BB.  */
2405*404b540aSrobert   for (son = first_dom_son (CDI_DOMINATORS, bb);
2406*404b540aSrobert        son;
2407*404b540aSrobert        son = next_dom_son (CDI_DOMINATORS, son))
2408*404b540aSrobert     eliminate_degenerate_phis_1 (son, interesting_names);
2409*404b540aSrobert }
2410*404b540aSrobert 
2411*404b540aSrobert 
2412*404b540aSrobert /* A very simple pass to eliminate degenerate PHI nodes from the
2413*404b540aSrobert    IL.  This is meant to be fast enough to be able to be run several
2414*404b540aSrobert    times in the optimization pipeline.
2415*404b540aSrobert 
2416*404b540aSrobert    Certain optimizations, particularly those which duplicate blocks
2417*404b540aSrobert    or remove edges from the CFG can create or expose PHIs which are
2418*404b540aSrobert    trivial copies or constant initializations.
2419*404b540aSrobert 
2420*404b540aSrobert    While we could pick up these optimizations in DOM or with the
2421*404b540aSrobert    combination of copy-prop and CCP, those solutions are far too
2422*404b540aSrobert    heavy-weight for our needs.
2423*404b540aSrobert 
2424*404b540aSrobert    This implementation has two phases so that we can efficiently
2425*404b540aSrobert    eliminate the first order degenerate PHIs and second order
2426*404b540aSrobert    degenerate PHIs.
2427*404b540aSrobert 
2428*404b540aSrobert    The first phase performs a dominator walk to identify and eliminate
2429*404b540aSrobert    the vast majority of the degenerate PHIs.  When a degenerate PHI
2430*404b540aSrobert    is identified and eliminated any affected statements or PHIs
2431*404b540aSrobert    are put on a worklist.
2432*404b540aSrobert 
2433*404b540aSrobert    The second phase eliminates degenerate PHIs and trivial copies
2434*404b540aSrobert    or constant initializations using the worklist.  This is how we
2435*404b540aSrobert    pick up the secondary optimization opportunities with minimal
2436*404b540aSrobert    cost.  */
2437*404b540aSrobert 
2438*404b540aSrobert static unsigned int
eliminate_degenerate_phis(void)2439*404b540aSrobert eliminate_degenerate_phis (void)
2440*404b540aSrobert {
2441*404b540aSrobert   bitmap interesting_names;
2442*404b540aSrobert   bitmap interesting_names1;
2443*404b540aSrobert 
2444*404b540aSrobert   /* Bitmap of blocks which need EH information updated.  We can not
2445*404b540aSrobert      update it on-the-fly as doing so invalidates the dominator tree.  */
2446*404b540aSrobert   need_eh_cleanup = BITMAP_ALLOC (NULL);
2447*404b540aSrobert 
2448*404b540aSrobert   /* INTERESTING_NAMES is effectively our worklist, indexed by
2449*404b540aSrobert      SSA_NAME_VERSION.
2450*404b540aSrobert 
2451*404b540aSrobert      A set bit indicates that the statement or PHI node which
2452*404b540aSrobert      defines the SSA_NAME should be (re)examined to determine if
2453*404b540aSrobert      it has become a degenerate PHI or trivial const/copy propagation
2454*404b540aSrobert      opportunity.
2455*404b540aSrobert 
2456*404b540aSrobert      Experiments have show we generally get better compilation
2457*404b540aSrobert      time behavior with bitmaps rather than sbitmaps.  */
2458*404b540aSrobert   interesting_names = BITMAP_ALLOC (NULL);
2459*404b540aSrobert   interesting_names1 = BITMAP_ALLOC (NULL);
2460*404b540aSrobert 
2461*404b540aSrobert   /* First phase.  Eliminate degenerate PHIs via a dominator
2462*404b540aSrobert      walk of the CFG.
2463*404b540aSrobert 
2464*404b540aSrobert      Experiments have indicated that we generally get better
2465*404b540aSrobert      compile-time behavior by visiting blocks in the first
2466*404b540aSrobert      phase in dominator order.  Presumably this is because walking
2467*404b540aSrobert      in dominator order leaves fewer PHIs for later examination
2468*404b540aSrobert      by the worklist phase.  */
2469*404b540aSrobert   calculate_dominance_info (CDI_DOMINATORS);
2470*404b540aSrobert   eliminate_degenerate_phis_1 (ENTRY_BLOCK_PTR, interesting_names);
2471*404b540aSrobert 
2472*404b540aSrobert   /* Second phase.  Eliminate second order degenerate PHIs as well
2473*404b540aSrobert      as trivial copies or constant initializations identified by
2474*404b540aSrobert      the first phase or this phase.  Basically we keep iterating
2475*404b540aSrobert      until our set of INTERESTING_NAMEs is empty.   */
2476*404b540aSrobert   while (!bitmap_empty_p (interesting_names))
2477*404b540aSrobert     {
2478*404b540aSrobert       unsigned int i;
2479*404b540aSrobert       bitmap_iterator bi;
2480*404b540aSrobert 
2481*404b540aSrobert       /* EXECUTE_IF_SET_IN_BITMAP does not like its bitmap
2482*404b540aSrobert 	 changed during the loop.  Copy it to another bitmap and
2483*404b540aSrobert 	 use that.  */
2484*404b540aSrobert       bitmap_copy (interesting_names1, interesting_names);
2485*404b540aSrobert 
2486*404b540aSrobert       EXECUTE_IF_SET_IN_BITMAP (interesting_names1, 0, i, bi)
2487*404b540aSrobert 	{
2488*404b540aSrobert 	  tree name = ssa_name (i);
2489*404b540aSrobert 
2490*404b540aSrobert 	  /* Ignore SSA_NAMEs that have been released because
2491*404b540aSrobert 	     their defining statement was deleted (unreachable).  */
2492*404b540aSrobert 	  if (name)
2493*404b540aSrobert 	    eliminate_const_or_copy (SSA_NAME_DEF_STMT (ssa_name (i)),
2494*404b540aSrobert 				     interesting_names);
2495*404b540aSrobert 	}
2496*404b540aSrobert     }
2497*404b540aSrobert 
2498*404b540aSrobert   /* Propagation of const and copies may make some EH edges dead.  Purge
2499*404b540aSrobert      such edges from the CFG as needed.  */
2500*404b540aSrobert   if (!bitmap_empty_p (need_eh_cleanup))
2501*404b540aSrobert     {
2502*404b540aSrobert       cfg_altered |= tree_purge_all_dead_eh_edges (need_eh_cleanup);
2503*404b540aSrobert       BITMAP_FREE (need_eh_cleanup);
2504*404b540aSrobert     }
2505*404b540aSrobert 
2506*404b540aSrobert   BITMAP_FREE (interesting_names);
2507*404b540aSrobert   BITMAP_FREE (interesting_names1);
2508*404b540aSrobert   if (cfg_altered)
2509*404b540aSrobert     free_dominance_info (CDI_DOMINATORS);
2510*404b540aSrobert   return 0;
2511*404b540aSrobert }
2512*404b540aSrobert 
2513*404b540aSrobert struct tree_opt_pass pass_phi_only_cprop =
2514*404b540aSrobert {
2515*404b540aSrobert   "phicprop",                           /* name */
2516*404b540aSrobert   gate_dominator,                       /* gate */
2517*404b540aSrobert   eliminate_degenerate_phis,            /* execute */
2518*404b540aSrobert   NULL,                                 /* sub */
2519*404b540aSrobert   NULL,                                 /* next */
2520*404b540aSrobert   0,                                    /* static_pass_number */
2521*404b540aSrobert   TV_TREE_PHI_CPROP,                    /* tv_id */
2522*404b540aSrobert   PROP_cfg | PROP_ssa | PROP_alias,     /* properties_required */
2523*404b540aSrobert   0,                                    /* properties_provided */
2524*404b540aSrobert   PROP_smt_usage,                       /* properties_destroyed */
2525*404b540aSrobert   0,                                    /* todo_flags_start */
2526*404b540aSrobert   TODO_cleanup_cfg | TODO_dump_func
2527*404b540aSrobert     | TODO_ggc_collect | TODO_verify_ssa
2528*404b540aSrobert     | TODO_verify_stmts | TODO_update_smt_usage
2529*404b540aSrobert     | TODO_update_ssa, /* todo_flags_finish */
2530*404b540aSrobert   0                                     /* letter */
2531*404b540aSrobert };
2532