* tree-cfg.c (tree_find_edge_insert_loc): Handle naked RETURN_EXPR.
[official-gcc.git] / gcc / tree-ssa-loop-ivopts.c
blob8bfbf7f8424b0637c61a0bf8839b93c5814ea7b5
1 /* Induction variable optimizations.
2 Copyright (C) 2003, 2004, 2005 Free Software Foundation, Inc.
4 This file is part of GCC.
6 GCC is free software; you can redistribute it and/or modify it
7 under the terms of the GNU General Public License as published by the
8 Free Software Foundation; either version 2, or (at your option) any
9 later version.
11 GCC is distributed in the hope that it will be useful, but WITHOUT
12 ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
13 FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
14 for more details.
16 You should have received a copy of the GNU General Public License
17 along with GCC; see the file COPYING. If not, write to the Free
18 Software Foundation, 51 Franklin Street, Fifth Floor, Boston, MA
19 02110-1301, USA. */
21 /* This pass tries to find the optimal set of induction variables for the loop.
22 It optimizes just the basic linear induction variables (although adding
23 support for other types should not be too hard). It includes the
24 optimizations commonly known as strength reduction, induction variable
25 coalescing and induction variable elimination. It does it in the
26 following steps:
28 1) The interesting uses of induction variables are found. This includes
30 -- uses of induction variables in non-linear expressions
31 -- addresses of arrays
32 -- comparisons of induction variables
34 2) Candidates for the induction variables are found. This includes
36 -- old induction variables
37 -- the variables defined by expressions derived from the "interesting
38 uses" above
40 3) The optimal (w.r. to a cost function) set of variables is chosen. The
41 cost function assigns a cost to sets of induction variables and consists
42 of three parts:
44 -- The use costs. Each of the interesting uses chooses the best induction
45 variable in the set and adds its cost to the sum. The cost reflects
46 the time spent on modifying the induction variables value to be usable
47 for the given purpose (adding base and offset for arrays, etc.).
48 -- The variable costs. Each of the variables has a cost assigned that
49 reflects the costs associated with incrementing the value of the
50 variable. The original variables are somewhat preferred.
51 -- The set cost. Depending on the size of the set, extra cost may be
52 added to reflect register pressure.
54 All the costs are defined in a machine-specific way, using the target
55 hooks and machine descriptions to determine them.
57 4) The trees are transformed to use the new variables, the dead code is
58 removed.
60 All of this is done loop by loop. Doing it globally is theoretically
61 possible, it might give a better performance and it might enable us
62 to decide costs more precisely, but getting all the interactions right
63 would be complicated. */
65 #include "config.h"
66 #include "system.h"
67 #include "coretypes.h"
68 #include "tm.h"
69 #include "tree.h"
70 #include "rtl.h"
71 #include "tm_p.h"
72 #include "hard-reg-set.h"
73 #include "basic-block.h"
74 #include "output.h"
75 #include "diagnostic.h"
76 #include "tree-flow.h"
77 #include "tree-dump.h"
78 #include "timevar.h"
79 #include "cfgloop.h"
80 #include "varray.h"
81 #include "expr.h"
82 #include "tree-pass.h"
83 #include "ggc.h"
84 #include "insn-config.h"
85 #include "recog.h"
86 #include "hashtab.h"
87 #include "tree-chrec.h"
88 #include "tree-scalar-evolution.h"
89 #include "cfgloop.h"
90 #include "params.h"
91 #include "langhooks.h"
93 /* The infinite cost. */
94 #define INFTY 10000000
96 /* The expected number of loop iterations. TODO -- use profiling instead of
97 this. */
98 #define AVG_LOOP_NITER(LOOP) 5
101 /* Representation of the induction variable. */
102 struct iv
104 tree base; /* Initial value of the iv. */
105 tree base_object; /* A memory object to that the induction variable points. */
106 tree step; /* Step of the iv (constant only). */
107 tree ssa_name; /* The ssa name with the value. */
108 bool biv_p; /* Is it a biv? */
109 bool have_use_for; /* Do we already have a use for it? */
110 unsigned use_id; /* The identifier in the use if it is the case. */
113 /* Per-ssa version information (induction variable descriptions, etc.). */
114 struct version_info
116 tree name; /* The ssa name. */
117 struct iv *iv; /* Induction variable description. */
118 bool has_nonlin_use; /* For a loop-level invariant, whether it is used in
119 an expression that is not an induction variable. */
120 unsigned inv_id; /* Id of an invariant. */
121 bool preserve_biv; /* For the original biv, whether to preserve it. */
124 /* Information attached to loop. */
125 struct loop_data
127 unsigned regs_used; /* Number of registers used. */
130 /* Types of uses. */
131 enum use_type
133 USE_NONLINEAR_EXPR, /* Use in a nonlinear expression. */
134 USE_OUTER, /* The induction variable is used outside the loop. */
135 USE_ADDRESS, /* Use in an address. */
136 USE_COMPARE /* Use is a compare. */
139 /* The candidate - cost pair. */
140 struct cost_pair
142 struct iv_cand *cand; /* The candidate. */
143 unsigned cost; /* The cost. */
144 bitmap depends_on; /* The list of invariants that have to be
145 preserved. */
146 tree value; /* For final value elimination, the expression for
147 the final value of the iv. For iv elimination,
148 the new bound to compare with. */
151 /* Use. */
152 struct iv_use
154 unsigned id; /* The id of the use. */
155 enum use_type type; /* Type of the use. */
156 struct iv *iv; /* The induction variable it is based on. */
157 tree stmt; /* Statement in that it occurs. */
158 tree *op_p; /* The place where it occurs. */
159 bitmap related_cands; /* The set of "related" iv candidates, plus the common
160 important ones. */
162 unsigned n_map_members; /* Number of candidates in the cost_map list. */
163 struct cost_pair *cost_map;
164 /* The costs wrto the iv candidates. */
166 struct iv_cand *selected;
167 /* The selected candidate. */
170 /* The position where the iv is computed. */
171 enum iv_position
173 IP_NORMAL, /* At the end, just before the exit condition. */
174 IP_END, /* At the end of the latch block. */
175 IP_ORIGINAL /* The original biv. */
178 /* The induction variable candidate. */
179 struct iv_cand
181 unsigned id; /* The number of the candidate. */
182 bool important; /* Whether this is an "important" candidate, i.e. such
183 that it should be considered by all uses. */
184 enum iv_position pos; /* Where it is computed. */
185 tree incremented_at; /* For original biv, the statement where it is
186 incremented. */
187 tree var_before; /* The variable used for it before increment. */
188 tree var_after; /* The variable used for it after increment. */
189 struct iv *iv; /* The value of the candidate. NULL for
190 "pseudocandidate" used to indicate the possibility
191 to replace the final value of an iv by direct
192 computation of the value. */
193 unsigned cost; /* Cost of the candidate. */
194 bitmap depends_on; /* The list of invariants that are used in step of the
195 biv. */
198 /* The data used by the induction variable optimizations. */
200 typedef struct iv_use *iv_use_p;
201 DEF_VEC_P(iv_use_p);
202 DEF_VEC_ALLOC_P(iv_use_p,heap);
204 typedef struct iv_cand *iv_cand_p;
205 DEF_VEC_P(iv_cand_p);
206 DEF_VEC_ALLOC_P(iv_cand_p,heap);
208 struct ivopts_data
210 /* The currently optimized loop. */
211 struct loop *current_loop;
213 /* Numbers of iterations for all exits of the current loop. */
214 htab_t niters;
216 /* The size of version_info array allocated. */
217 unsigned version_info_size;
219 /* The array of information for the ssa names. */
220 struct version_info *version_info;
222 /* The bitmap of indices in version_info whose value was changed. */
223 bitmap relevant;
225 /* The maximum invariant id. */
226 unsigned max_inv_id;
228 /* The uses of induction variables. */
229 VEC(iv_use_p,heap) *iv_uses;
231 /* The candidates. */
232 VEC(iv_cand_p,heap) *iv_candidates;
234 /* A bitmap of important candidates. */
235 bitmap important_candidates;
237 /* Whether to consider just related and important candidates when replacing a
238 use. */
239 bool consider_all_candidates;
242 /* An assignment of iv candidates to uses. */
244 struct iv_ca
246 /* The number of uses covered by the assignment. */
247 unsigned upto;
249 /* Number of uses that cannot be expressed by the candidates in the set. */
250 unsigned bad_uses;
252 /* Candidate assigned to a use, together with the related costs. */
253 struct cost_pair **cand_for_use;
255 /* Number of times each candidate is used. */
256 unsigned *n_cand_uses;
258 /* The candidates used. */
259 bitmap cands;
261 /* The number of candidates in the set. */
262 unsigned n_cands;
264 /* Total number of registers needed. */
265 unsigned n_regs;
267 /* Total cost of expressing uses. */
268 unsigned cand_use_cost;
270 /* Total cost of candidates. */
271 unsigned cand_cost;
273 /* Number of times each invariant is used. */
274 unsigned *n_invariant_uses;
276 /* Total cost of the assignment. */
277 unsigned cost;
280 /* Difference of two iv candidate assignments. */
282 struct iv_ca_delta
284 /* Changed use. */
285 struct iv_use *use;
287 /* An old assignment (for rollback purposes). */
288 struct cost_pair *old_cp;
290 /* A new assignment. */
291 struct cost_pair *new_cp;
293 /* Next change in the list. */
294 struct iv_ca_delta *next_change;
297 /* Bound on number of candidates below that all candidates are considered. */
299 #define CONSIDER_ALL_CANDIDATES_BOUND \
300 ((unsigned) PARAM_VALUE (PARAM_IV_CONSIDER_ALL_CANDIDATES_BOUND))
302 /* If there are more iv occurrences, we just give up (it is quite unlikely that
303 optimizing such a loop would help, and it would take ages). */
305 #define MAX_CONSIDERED_USES \
306 ((unsigned) PARAM_VALUE (PARAM_IV_MAX_CONSIDERED_USES))
308 /* If there are at most this number of ivs in the set, try removing unnecessary
309 ivs from the set always. */
311 #define ALWAYS_PRUNE_CAND_SET_BOUND \
312 ((unsigned) PARAM_VALUE (PARAM_IV_ALWAYS_PRUNE_CAND_SET_BOUND))
314 /* The list of trees for that the decl_rtl field must be reset is stored
315 here. */
317 static VEC(tree,heap) *decl_rtl_to_reset;
319 /* Number of uses recorded in DATA. */
321 static inline unsigned
322 n_iv_uses (struct ivopts_data *data)
324 return VEC_length (iv_use_p, data->iv_uses);
327 /* Ith use recorded in DATA. */
329 static inline struct iv_use *
330 iv_use (struct ivopts_data *data, unsigned i)
332 return VEC_index (iv_use_p, data->iv_uses, i);
335 /* Number of candidates recorded in DATA. */
337 static inline unsigned
338 n_iv_cands (struct ivopts_data *data)
340 return VEC_length (iv_cand_p, data->iv_candidates);
343 /* Ith candidate recorded in DATA. */
345 static inline struct iv_cand *
346 iv_cand (struct ivopts_data *data, unsigned i)
348 return VEC_index (iv_cand_p, data->iv_candidates, i);
351 /* The data for LOOP. */
353 static inline struct loop_data *
354 loop_data (struct loop *loop)
356 return loop->aux;
359 /* The single loop exit if it dominates the latch, NULL otherwise. */
361 edge
362 single_dom_exit (struct loop *loop)
364 edge exit = loop->single_exit;
366 if (!exit)
367 return NULL;
369 if (!just_once_each_iteration_p (loop, exit->src))
370 return NULL;
372 return exit;
375 /* Dumps information about the induction variable IV to FILE. */
377 extern void dump_iv (FILE *, struct iv *);
378 void
379 dump_iv (FILE *file, struct iv *iv)
381 if (iv->ssa_name)
383 fprintf (file, "ssa name ");
384 print_generic_expr (file, iv->ssa_name, TDF_SLIM);
385 fprintf (file, "\n");
388 fprintf (file, " type ");
389 print_generic_expr (file, TREE_TYPE (iv->base), TDF_SLIM);
390 fprintf (file, "\n");
392 if (iv->step)
394 fprintf (file, " base ");
395 print_generic_expr (file, iv->base, TDF_SLIM);
396 fprintf (file, "\n");
398 fprintf (file, " step ");
399 print_generic_expr (file, iv->step, TDF_SLIM);
400 fprintf (file, "\n");
402 else
404 fprintf (file, " invariant ");
405 print_generic_expr (file, iv->base, TDF_SLIM);
406 fprintf (file, "\n");
409 if (iv->base_object)
411 fprintf (file, " base object ");
412 print_generic_expr (file, iv->base_object, TDF_SLIM);
413 fprintf (file, "\n");
416 if (iv->biv_p)
417 fprintf (file, " is a biv\n");
420 /* Dumps information about the USE to FILE. */
422 extern void dump_use (FILE *, struct iv_use *);
423 void
424 dump_use (FILE *file, struct iv_use *use)
426 fprintf (file, "use %d\n", use->id);
428 switch (use->type)
430 case USE_NONLINEAR_EXPR:
431 fprintf (file, " generic\n");
432 break;
434 case USE_OUTER:
435 fprintf (file, " outside\n");
436 break;
438 case USE_ADDRESS:
439 fprintf (file, " address\n");
440 break;
442 case USE_COMPARE:
443 fprintf (file, " compare\n");
444 break;
446 default:
447 gcc_unreachable ();
450 fprintf (file, " in statement ");
451 print_generic_expr (file, use->stmt, TDF_SLIM);
452 fprintf (file, "\n");
454 fprintf (file, " at position ");
455 if (use->op_p)
456 print_generic_expr (file, *use->op_p, TDF_SLIM);
457 fprintf (file, "\n");
459 dump_iv (file, use->iv);
461 if (use->related_cands)
463 fprintf (file, " related candidates ");
464 dump_bitmap (file, use->related_cands);
468 /* Dumps information about the uses to FILE. */
470 extern void dump_uses (FILE *, struct ivopts_data *);
471 void
472 dump_uses (FILE *file, struct ivopts_data *data)
474 unsigned i;
475 struct iv_use *use;
477 for (i = 0; i < n_iv_uses (data); i++)
479 use = iv_use (data, i);
481 dump_use (file, use);
482 fprintf (file, "\n");
486 /* Dumps information about induction variable candidate CAND to FILE. */
488 extern void dump_cand (FILE *, struct iv_cand *);
489 void
490 dump_cand (FILE *file, struct iv_cand *cand)
492 struct iv *iv = cand->iv;
494 fprintf (file, "candidate %d%s\n",
495 cand->id, cand->important ? " (important)" : "");
497 if (cand->depends_on)
499 fprintf (file, " depends on ");
500 dump_bitmap (file, cand->depends_on);
503 if (!iv)
505 fprintf (file, " final value replacement\n");
506 return;
509 switch (cand->pos)
511 case IP_NORMAL:
512 fprintf (file, " incremented before exit test\n");
513 break;
515 case IP_END:
516 fprintf (file, " incremented at end\n");
517 break;
519 case IP_ORIGINAL:
520 fprintf (file, " original biv\n");
521 break;
524 dump_iv (file, iv);
527 /* Returns the info for ssa version VER. */
529 static inline struct version_info *
530 ver_info (struct ivopts_data *data, unsigned ver)
532 return data->version_info + ver;
535 /* Returns the info for ssa name NAME. */
537 static inline struct version_info *
538 name_info (struct ivopts_data *data, tree name)
540 return ver_info (data, SSA_NAME_VERSION (name));
543 /* Checks whether there exists number X such that X * B = A, counting modulo
544 2^BITS. */
546 static bool
547 divide (unsigned bits, unsigned HOST_WIDE_INT a, unsigned HOST_WIDE_INT b,
548 HOST_WIDE_INT *x)
550 unsigned HOST_WIDE_INT mask = ~(~(unsigned HOST_WIDE_INT) 0 << (bits - 1) << 1);
551 unsigned HOST_WIDE_INT inv, ex, val;
552 unsigned i;
554 a &= mask;
555 b &= mask;
557 /* First divide the whole equation by 2 as long as possible. */
558 while (!(a & 1) && !(b & 1))
560 a >>= 1;
561 b >>= 1;
562 bits--;
563 mask >>= 1;
566 if (!(b & 1))
568 /* If b is still even, a is odd and there is no such x. */
569 return false;
572 /* Find the inverse of b. We compute it as
573 b^(2^(bits - 1) - 1) (mod 2^bits). */
574 inv = 1;
575 ex = b;
576 for (i = 0; i < bits - 1; i++)
578 inv = (inv * ex) & mask;
579 ex = (ex * ex) & mask;
582 val = (a * inv) & mask;
584 gcc_assert (((val * b) & mask) == a);
586 if ((val >> (bits - 1)) & 1)
587 val |= ~mask;
589 *x = val;
591 return true;
594 /* Returns true if STMT is after the place where the IP_NORMAL ivs will be
595 emitted in LOOP. */
597 static bool
598 stmt_after_ip_normal_pos (struct loop *loop, tree stmt)
600 basic_block bb = ip_normal_pos (loop), sbb = bb_for_stmt (stmt);
602 gcc_assert (bb);
604 if (sbb == loop->latch)
605 return true;
607 if (sbb != bb)
608 return false;
610 return stmt == last_stmt (bb);
613 /* Returns true if STMT if after the place where the original induction
614 variable CAND is incremented. */
616 static bool
617 stmt_after_ip_original_pos (struct iv_cand *cand, tree stmt)
619 basic_block cand_bb = bb_for_stmt (cand->incremented_at);
620 basic_block stmt_bb = bb_for_stmt (stmt);
621 block_stmt_iterator bsi;
623 if (!dominated_by_p (CDI_DOMINATORS, stmt_bb, cand_bb))
624 return false;
626 if (stmt_bb != cand_bb)
627 return true;
629 /* Scan the block from the end, since the original ivs are usually
630 incremented at the end of the loop body. */
631 for (bsi = bsi_last (stmt_bb); ; bsi_prev (&bsi))
633 if (bsi_stmt (bsi) == cand->incremented_at)
634 return false;
635 if (bsi_stmt (bsi) == stmt)
636 return true;
640 /* Returns true if STMT if after the place where the induction variable
641 CAND is incremented in LOOP. */
643 static bool
644 stmt_after_increment (struct loop *loop, struct iv_cand *cand, tree stmt)
646 switch (cand->pos)
648 case IP_END:
649 return false;
651 case IP_NORMAL:
652 return stmt_after_ip_normal_pos (loop, stmt);
654 case IP_ORIGINAL:
655 return stmt_after_ip_original_pos (cand, stmt);
657 default:
658 gcc_unreachable ();
662 /* Element of the table in that we cache the numbers of iterations obtained
663 from exits of the loop. */
665 struct nfe_cache_elt
667 /* The edge for that the number of iterations is cached. */
668 edge exit;
670 /* True if the # of iterations was successfully determined. */
671 bool valid_p;
673 /* Description of # of iterations. */
674 struct tree_niter_desc niter;
677 /* Hash function for nfe_cache_elt E. */
679 static hashval_t
680 nfe_hash (const void *e)
682 const struct nfe_cache_elt *elt = e;
684 return htab_hash_pointer (elt->exit);
687 /* Equality function for nfe_cache_elt E1 and edge E2. */
689 static int
690 nfe_eq (const void *e1, const void *e2)
692 const struct nfe_cache_elt *elt1 = e1;
694 return elt1->exit == e2;
697 /* Returns structure describing number of iterations determined from
698 EXIT of DATA->current_loop, or NULL if something goes wrong. */
700 static struct tree_niter_desc *
701 niter_for_exit (struct ivopts_data *data, edge exit)
703 struct nfe_cache_elt *nfe_desc;
704 PTR *slot;
706 slot = htab_find_slot_with_hash (data->niters, exit,
707 htab_hash_pointer (exit),
708 INSERT);
710 if (!*slot)
712 nfe_desc = xmalloc (sizeof (struct nfe_cache_elt));
713 nfe_desc->exit = exit;
714 nfe_desc->valid_p = number_of_iterations_exit (data->current_loop,
715 exit, &nfe_desc->niter,
716 true);
717 *slot = nfe_desc;
719 else
720 nfe_desc = *slot;
722 if (!nfe_desc->valid_p)
723 return NULL;
725 return &nfe_desc->niter;
728 /* Returns structure describing number of iterations determined from
729 single dominating exit of DATA->current_loop, or NULL if something
730 goes wrong. */
732 static struct tree_niter_desc *
733 niter_for_single_dom_exit (struct ivopts_data *data)
735 edge exit = single_dom_exit (data->current_loop);
737 if (!exit)
738 return NULL;
740 return niter_for_exit (data, exit);
743 /* Initializes data structures used by the iv optimization pass, stored
744 in DATA. LOOPS is the loop tree. */
746 static void
747 tree_ssa_iv_optimize_init (struct loops *loops, struct ivopts_data *data)
749 unsigned i;
751 data->version_info_size = 2 * num_ssa_names;
752 data->version_info = xcalloc (data->version_info_size,
753 sizeof (struct version_info));
754 data->relevant = BITMAP_ALLOC (NULL);
755 data->important_candidates = BITMAP_ALLOC (NULL);
756 data->max_inv_id = 0;
757 data->niters = htab_create (10, nfe_hash, nfe_eq, free);
759 for (i = 1; i < loops->num; i++)
760 if (loops->parray[i])
761 loops->parray[i]->aux = xcalloc (1, sizeof (struct loop_data));
763 data->iv_uses = VEC_alloc (iv_use_p, heap, 20);
764 data->iv_candidates = VEC_alloc (iv_cand_p, heap, 20);
765 decl_rtl_to_reset = VEC_alloc (tree, heap, 20);
768 /* Returns a memory object to that EXPR points. In case we are able to
769 determine that it does not point to any such object, NULL is returned. */
771 static tree
772 determine_base_object (tree expr)
774 enum tree_code code = TREE_CODE (expr);
775 tree base, obj, op0, op1;
777 if (!POINTER_TYPE_P (TREE_TYPE (expr)))
778 return NULL_TREE;
780 switch (code)
782 case INTEGER_CST:
783 return NULL_TREE;
785 case ADDR_EXPR:
786 obj = TREE_OPERAND (expr, 0);
787 base = get_base_address (obj);
789 if (!base)
790 return expr;
792 if (TREE_CODE (base) == INDIRECT_REF)
793 return determine_base_object (TREE_OPERAND (base, 0));
795 return fold_convert (ptr_type_node,
796 build_fold_addr_expr (base));
798 case PLUS_EXPR:
799 case MINUS_EXPR:
800 op0 = determine_base_object (TREE_OPERAND (expr, 0));
801 op1 = determine_base_object (TREE_OPERAND (expr, 1));
803 if (!op1)
804 return op0;
806 if (!op0)
807 return (code == PLUS_EXPR
808 ? op1
809 : fold_build1 (NEGATE_EXPR, ptr_type_node, op1));
811 return fold_build2 (code, ptr_type_node, op0, op1);
813 case NOP_EXPR:
814 case CONVERT_EXPR:
815 return determine_base_object (TREE_OPERAND (expr, 0));
817 default:
818 return fold_convert (ptr_type_node, expr);
822 /* Allocates an induction variable with given initial value BASE and step STEP
823 for loop LOOP. */
825 static struct iv *
826 alloc_iv (tree base, tree step)
828 struct iv *iv = xcalloc (1, sizeof (struct iv));
830 if (step && integer_zerop (step))
831 step = NULL_TREE;
833 iv->base = base;
834 iv->base_object = determine_base_object (base);
835 iv->step = step;
836 iv->biv_p = false;
837 iv->have_use_for = false;
838 iv->use_id = 0;
839 iv->ssa_name = NULL_TREE;
841 return iv;
844 /* Sets STEP and BASE for induction variable IV. */
846 static void
847 set_iv (struct ivopts_data *data, tree iv, tree base, tree step)
849 struct version_info *info = name_info (data, iv);
851 gcc_assert (!info->iv);
853 bitmap_set_bit (data->relevant, SSA_NAME_VERSION (iv));
854 info->iv = alloc_iv (base, step);
855 info->iv->ssa_name = iv;
858 /* Finds induction variable declaration for VAR. */
860 static struct iv *
861 get_iv (struct ivopts_data *data, tree var)
863 basic_block bb;
865 if (!name_info (data, var)->iv)
867 bb = bb_for_stmt (SSA_NAME_DEF_STMT (var));
869 if (!bb
870 || !flow_bb_inside_loop_p (data->current_loop, bb))
871 set_iv (data, var, var, NULL_TREE);
874 return name_info (data, var)->iv;
877 /* Determines the step of a biv defined in PHI. Returns NULL if PHI does
878 not define a simple affine biv with nonzero step. */
880 static tree
881 determine_biv_step (tree phi)
883 struct loop *loop = bb_for_stmt (phi)->loop_father;
884 tree name = PHI_RESULT (phi), base, step;
886 if (!is_gimple_reg (name))
887 return NULL_TREE;
889 if (!simple_iv (loop, phi, name, &base, &step, true))
890 return NULL_TREE;
892 if (zero_p (step))
893 return NULL_TREE;
895 return step;
898 /* Returns true if EXP is a ssa name that occurs in an abnormal phi node. */
900 static bool
901 abnormal_ssa_name_p (tree exp)
903 if (!exp)
904 return false;
906 if (TREE_CODE (exp) != SSA_NAME)
907 return false;
909 return SSA_NAME_OCCURS_IN_ABNORMAL_PHI (exp) != 0;
912 /* Returns false if BASE or INDEX contains a ssa name that occurs in an
913 abnormal phi node. Callback for for_each_index. */
915 static bool
916 idx_contains_abnormal_ssa_name_p (tree base, tree *index,
917 void *data ATTRIBUTE_UNUSED)
919 if (TREE_CODE (base) == ARRAY_REF)
921 if (abnormal_ssa_name_p (TREE_OPERAND (base, 2)))
922 return false;
923 if (abnormal_ssa_name_p (TREE_OPERAND (base, 3)))
924 return false;
927 return !abnormal_ssa_name_p (*index);
930 /* Returns true if EXPR contains a ssa name that occurs in an
931 abnormal phi node. */
933 static bool
934 contains_abnormal_ssa_name_p (tree expr)
936 enum tree_code code;
937 enum tree_code_class class;
939 if (!expr)
940 return false;
942 code = TREE_CODE (expr);
943 class = TREE_CODE_CLASS (code);
945 if (code == SSA_NAME)
946 return SSA_NAME_OCCURS_IN_ABNORMAL_PHI (expr) != 0;
948 if (code == INTEGER_CST
949 || is_gimple_min_invariant (expr))
950 return false;
952 if (code == ADDR_EXPR)
953 return !for_each_index (&TREE_OPERAND (expr, 0),
954 idx_contains_abnormal_ssa_name_p,
955 NULL);
957 switch (class)
959 case tcc_binary:
960 case tcc_comparison:
961 if (contains_abnormal_ssa_name_p (TREE_OPERAND (expr, 1)))
962 return true;
964 /* Fallthru. */
965 case tcc_unary:
966 if (contains_abnormal_ssa_name_p (TREE_OPERAND (expr, 0)))
967 return true;
969 break;
971 default:
972 gcc_unreachable ();
975 return false;
978 /* Finds basic ivs. */
980 static bool
981 find_bivs (struct ivopts_data *data)
983 tree phi, step, type, base;
984 bool found = false;
985 struct loop *loop = data->current_loop;
987 for (phi = phi_nodes (loop->header); phi; phi = PHI_CHAIN (phi))
989 if (SSA_NAME_OCCURS_IN_ABNORMAL_PHI (PHI_RESULT (phi)))
990 continue;
992 step = determine_biv_step (phi);
993 if (!step)
994 continue;
996 base = PHI_ARG_DEF_FROM_EDGE (phi, loop_preheader_edge (loop));
997 base = expand_simple_operations (base);
998 if (contains_abnormal_ssa_name_p (base)
999 || contains_abnormal_ssa_name_p (step))
1000 continue;
1002 type = TREE_TYPE (PHI_RESULT (phi));
1003 base = fold_convert (type, base);
1004 if (step)
1005 step = fold_convert (type, step);
1007 set_iv (data, PHI_RESULT (phi), base, step);
1008 found = true;
1011 return found;
1014 /* Marks basic ivs. */
1016 static void
1017 mark_bivs (struct ivopts_data *data)
1019 tree phi, var;
1020 struct iv *iv, *incr_iv;
1021 struct loop *loop = data->current_loop;
1022 basic_block incr_bb;
1024 for (phi = phi_nodes (loop->header); phi; phi = PHI_CHAIN (phi))
1026 iv = get_iv (data, PHI_RESULT (phi));
1027 if (!iv)
1028 continue;
1030 var = PHI_ARG_DEF_FROM_EDGE (phi, loop_latch_edge (loop));
1031 incr_iv = get_iv (data, var);
1032 if (!incr_iv)
1033 continue;
1035 /* If the increment is in the subloop, ignore it. */
1036 incr_bb = bb_for_stmt (SSA_NAME_DEF_STMT (var));
1037 if (incr_bb->loop_father != data->current_loop
1038 || (incr_bb->flags & BB_IRREDUCIBLE_LOOP))
1039 continue;
1041 iv->biv_p = true;
1042 incr_iv->biv_p = true;
1046 /* Checks whether STMT defines a linear induction variable and stores its
1047 parameters to BASE and STEP. */
1049 static bool
1050 find_givs_in_stmt_scev (struct ivopts_data *data, tree stmt,
1051 tree *base, tree *step)
1053 tree lhs;
1054 struct loop *loop = data->current_loop;
1056 *base = NULL_TREE;
1057 *step = NULL_TREE;
1059 if (TREE_CODE (stmt) != MODIFY_EXPR)
1060 return false;
1062 lhs = TREE_OPERAND (stmt, 0);
1063 if (TREE_CODE (lhs) != SSA_NAME)
1064 return false;
1066 if (!simple_iv (loop, stmt, TREE_OPERAND (stmt, 1), base, step, true))
1067 return false;
1068 *base = expand_simple_operations (*base);
1070 if (contains_abnormal_ssa_name_p (*base)
1071 || contains_abnormal_ssa_name_p (*step))
1072 return false;
1074 return true;
1077 /* Finds general ivs in statement STMT. */
1079 static void
1080 find_givs_in_stmt (struct ivopts_data *data, tree stmt)
1082 tree base, step;
1084 if (!find_givs_in_stmt_scev (data, stmt, &base, &step))
1085 return;
1087 set_iv (data, TREE_OPERAND (stmt, 0), base, step);
1090 /* Finds general ivs in basic block BB. */
1092 static void
1093 find_givs_in_bb (struct ivopts_data *data, basic_block bb)
1095 block_stmt_iterator bsi;
1097 for (bsi = bsi_start (bb); !bsi_end_p (bsi); bsi_next (&bsi))
1098 find_givs_in_stmt (data, bsi_stmt (bsi));
1101 /* Finds general ivs. */
1103 static void
1104 find_givs (struct ivopts_data *data)
1106 struct loop *loop = data->current_loop;
1107 basic_block *body = get_loop_body_in_dom_order (loop);
1108 unsigned i;
1110 for (i = 0; i < loop->num_nodes; i++)
1111 find_givs_in_bb (data, body[i]);
1112 free (body);
1115 /* For each ssa name defined in LOOP determines whether it is an induction
1116 variable and if so, its initial value and step. */
1118 static bool
1119 find_induction_variables (struct ivopts_data *data)
1121 unsigned i;
1122 bitmap_iterator bi;
1124 if (!find_bivs (data))
1125 return false;
1127 find_givs (data);
1128 mark_bivs (data);
1130 if (dump_file && (dump_flags & TDF_DETAILS))
1132 struct tree_niter_desc *niter;
1134 niter = niter_for_single_dom_exit (data);
1136 if (niter)
1138 fprintf (dump_file, " number of iterations ");
1139 print_generic_expr (dump_file, niter->niter, TDF_SLIM);
1140 fprintf (dump_file, "\n");
1142 fprintf (dump_file, " may be zero if ");
1143 print_generic_expr (dump_file, niter->may_be_zero, TDF_SLIM);
1144 fprintf (dump_file, "\n");
1145 fprintf (dump_file, "\n");
1148 fprintf (dump_file, "Induction variables:\n\n");
1150 EXECUTE_IF_SET_IN_BITMAP (data->relevant, 0, i, bi)
1152 if (ver_info (data, i)->iv)
1153 dump_iv (dump_file, ver_info (data, i)->iv);
1157 return true;
1160 /* Records a use of type USE_TYPE at *USE_P in STMT whose value is IV. */
1162 static struct iv_use *
1163 record_use (struct ivopts_data *data, tree *use_p, struct iv *iv,
1164 tree stmt, enum use_type use_type)
1166 struct iv_use *use = xcalloc (1, sizeof (struct iv_use));
1168 use->id = n_iv_uses (data);
1169 use->type = use_type;
1170 use->iv = iv;
1171 use->stmt = stmt;
1172 use->op_p = use_p;
1173 use->related_cands = BITMAP_ALLOC (NULL);
1175 /* To avoid showing ssa name in the dumps, if it was not reset by the
1176 caller. */
1177 iv->ssa_name = NULL_TREE;
1179 if (dump_file && (dump_flags & TDF_DETAILS))
1180 dump_use (dump_file, use);
1182 VEC_safe_push (iv_use_p, heap, data->iv_uses, use);
1184 return use;
1187 /* Checks whether OP is a loop-level invariant and if so, records it.
1188 NONLINEAR_USE is true if the invariant is used in a way we do not
1189 handle specially. */
1191 static void
1192 record_invariant (struct ivopts_data *data, tree op, bool nonlinear_use)
1194 basic_block bb;
1195 struct version_info *info;
1197 if (TREE_CODE (op) != SSA_NAME
1198 || !is_gimple_reg (op))
1199 return;
1201 bb = bb_for_stmt (SSA_NAME_DEF_STMT (op));
1202 if (bb
1203 && flow_bb_inside_loop_p (data->current_loop, bb))
1204 return;
1206 info = name_info (data, op);
1207 info->name = op;
1208 info->has_nonlin_use |= nonlinear_use;
1209 if (!info->inv_id)
1210 info->inv_id = ++data->max_inv_id;
1211 bitmap_set_bit (data->relevant, SSA_NAME_VERSION (op));
1214 /* Checks whether the use OP is interesting and if so, records it
1215 as TYPE. */
1217 static struct iv_use *
1218 find_interesting_uses_outer_or_nonlin (struct ivopts_data *data, tree op,
1219 enum use_type type)
1221 struct iv *iv;
1222 struct iv *civ;
1223 tree stmt;
1224 struct iv_use *use;
1226 if (TREE_CODE (op) != SSA_NAME)
1227 return NULL;
1229 iv = get_iv (data, op);
1230 if (!iv)
1231 return NULL;
1233 if (iv->have_use_for)
1235 use = iv_use (data, iv->use_id);
1237 gcc_assert (use->type == USE_NONLINEAR_EXPR
1238 || use->type == USE_OUTER);
1240 if (type == USE_NONLINEAR_EXPR)
1241 use->type = USE_NONLINEAR_EXPR;
1242 return use;
1245 if (zero_p (iv->step))
1247 record_invariant (data, op, true);
1248 return NULL;
1250 iv->have_use_for = true;
1252 civ = xmalloc (sizeof (struct iv));
1253 *civ = *iv;
1255 stmt = SSA_NAME_DEF_STMT (op);
1256 gcc_assert (TREE_CODE (stmt) == PHI_NODE
1257 || TREE_CODE (stmt) == MODIFY_EXPR);
1259 use = record_use (data, NULL, civ, stmt, type);
1260 iv->use_id = use->id;
1262 return use;
1265 /* Checks whether the use OP is interesting and if so, records it. */
1267 static struct iv_use *
1268 find_interesting_uses_op (struct ivopts_data *data, tree op)
1270 return find_interesting_uses_outer_or_nonlin (data, op, USE_NONLINEAR_EXPR);
1273 /* Records a definition of induction variable OP that is used outside of the
1274 loop. */
1276 static struct iv_use *
1277 find_interesting_uses_outer (struct ivopts_data *data, tree op)
1279 return find_interesting_uses_outer_or_nonlin (data, op, USE_OUTER);
1282 /* Checks whether the condition *COND_P in STMT is interesting
1283 and if so, records it. */
1285 static void
1286 find_interesting_uses_cond (struct ivopts_data *data, tree stmt, tree *cond_p)
1288 tree *op0_p;
1289 tree *op1_p;
1290 struct iv *iv0 = NULL, *iv1 = NULL, *civ;
1291 struct iv const_iv;
1292 tree zero = integer_zero_node;
1294 const_iv.step = NULL_TREE;
1296 if (TREE_CODE (*cond_p) != SSA_NAME
1297 && !COMPARISON_CLASS_P (*cond_p))
1298 return;
1300 if (TREE_CODE (*cond_p) == SSA_NAME)
1302 op0_p = cond_p;
1303 op1_p = &zero;
1305 else
1307 op0_p = &TREE_OPERAND (*cond_p, 0);
1308 op1_p = &TREE_OPERAND (*cond_p, 1);
1311 if (TREE_CODE (*op0_p) == SSA_NAME)
1312 iv0 = get_iv (data, *op0_p);
1313 else
1314 iv0 = &const_iv;
1316 if (TREE_CODE (*op1_p) == SSA_NAME)
1317 iv1 = get_iv (data, *op1_p);
1318 else
1319 iv1 = &const_iv;
1321 if (/* When comparing with non-invariant value, we may not do any senseful
1322 induction variable elimination. */
1323 (!iv0 || !iv1)
1324 /* Eliminating condition based on two ivs would be nontrivial.
1325 ??? TODO -- it is not really important to handle this case. */
1326 || (!zero_p (iv0->step) && !zero_p (iv1->step)))
1328 find_interesting_uses_op (data, *op0_p);
1329 find_interesting_uses_op (data, *op1_p);
1330 return;
1333 if (zero_p (iv0->step) && zero_p (iv1->step))
1335 /* If both are invariants, this is a work for unswitching. */
1336 return;
1339 civ = xmalloc (sizeof (struct iv));
1340 *civ = zero_p (iv0->step) ? *iv1: *iv0;
1341 record_use (data, cond_p, civ, stmt, USE_COMPARE);
1344 /* Returns true if expression EXPR is obviously invariant in LOOP,
1345 i.e. if all its operands are defined outside of the LOOP. */
1347 bool
1348 expr_invariant_in_loop_p (struct loop *loop, tree expr)
1350 basic_block def_bb;
1351 unsigned i, len;
1353 if (is_gimple_min_invariant (expr))
1354 return true;
1356 if (TREE_CODE (expr) == SSA_NAME)
1358 def_bb = bb_for_stmt (SSA_NAME_DEF_STMT (expr));
1359 if (def_bb
1360 && flow_bb_inside_loop_p (loop, def_bb))
1361 return false;
1363 return true;
1366 if (!EXPR_P (expr))
1367 return false;
1369 len = TREE_CODE_LENGTH (TREE_CODE (expr));
1370 for (i = 0; i < len; i++)
1371 if (!expr_invariant_in_loop_p (loop, TREE_OPERAND (expr, i)))
1372 return false;
1374 return true;
1377 /* Cumulates the steps of indices into DATA and replaces their values with the
1378 initial ones. Returns false when the value of the index cannot be determined.
1379 Callback for for_each_index. */
1381 struct ifs_ivopts_data
1383 struct ivopts_data *ivopts_data;
1384 tree stmt;
1385 tree *step_p;
1388 static bool
1389 idx_find_step (tree base, tree *idx, void *data)
1391 struct ifs_ivopts_data *dta = data;
1392 struct iv *iv;
1393 tree step, iv_step, lbound, off;
1394 struct loop *loop = dta->ivopts_data->current_loop;
1396 if (TREE_CODE (base) == MISALIGNED_INDIRECT_REF
1397 || TREE_CODE (base) == ALIGN_INDIRECT_REF)
1398 return false;
1400 /* If base is a component ref, require that the offset of the reference
1401 be invariant. */
1402 if (TREE_CODE (base) == COMPONENT_REF)
1404 off = component_ref_field_offset (base);
1405 return expr_invariant_in_loop_p (loop, off);
1408 /* If base is array, first check whether we will be able to move the
1409 reference out of the loop (in order to take its address in strength
1410 reduction). In order for this to work we need both lower bound
1411 and step to be loop invariants. */
1412 if (TREE_CODE (base) == ARRAY_REF)
1414 step = array_ref_element_size (base);
1415 lbound = array_ref_low_bound (base);
1417 if (!expr_invariant_in_loop_p (loop, step)
1418 || !expr_invariant_in_loop_p (loop, lbound))
1419 return false;
1422 if (TREE_CODE (*idx) != SSA_NAME)
1423 return true;
1425 iv = get_iv (dta->ivopts_data, *idx);
1426 if (!iv)
1427 return false;
1429 *idx = iv->base;
1431 if (!iv->step)
1432 return true;
1434 if (TREE_CODE (base) == ARRAY_REF)
1436 step = array_ref_element_size (base);
1438 /* We only handle addresses whose step is an integer constant. */
1439 if (TREE_CODE (step) != INTEGER_CST)
1440 return false;
1442 else
1443 /* The step for pointer arithmetics already is 1 byte. */
1444 step = build_int_cst (sizetype, 1);
1446 /* FIXME: convert_step should not be used outside chrec_convert: fix
1447 this by calling chrec_convert. */
1448 iv_step = convert_step (dta->ivopts_data->current_loop,
1449 sizetype, iv->base, iv->step, dta->stmt);
1451 if (!iv_step)
1453 /* The index might wrap. */
1454 return false;
1457 step = fold_build2 (MULT_EXPR, sizetype, step, iv_step);
1459 if (!*dta->step_p)
1460 *dta->step_p = step;
1461 else
1462 *dta->step_p = fold_build2 (PLUS_EXPR, sizetype, *dta->step_p, step);
1464 return true;
1467 /* Records use in index IDX. Callback for for_each_index. Ivopts data
1468 object is passed to it in DATA. */
1470 static bool
1471 idx_record_use (tree base, tree *idx,
1472 void *data)
1474 find_interesting_uses_op (data, *idx);
1475 if (TREE_CODE (base) == ARRAY_REF)
1477 find_interesting_uses_op (data, array_ref_element_size (base));
1478 find_interesting_uses_op (data, array_ref_low_bound (base));
1480 return true;
1483 /* Returns true if memory reference REF may be unaligned. */
1485 static bool
1486 may_be_unaligned_p (tree ref)
1488 tree base;
1489 tree base_type;
1490 HOST_WIDE_INT bitsize;
1491 HOST_WIDE_INT bitpos;
1492 tree toffset;
1493 enum machine_mode mode;
1494 int unsignedp, volatilep;
1495 unsigned base_align;
1497 /* TARGET_MEM_REFs are translated directly to valid MEMs on the target,
1498 thus they are not misaligned. */
1499 if (TREE_CODE (ref) == TARGET_MEM_REF)
1500 return false;
1502 /* The test below is basically copy of what expr.c:normal_inner_ref
1503 does to check whether the object must be loaded by parts when
1504 STRICT_ALIGNMENT is true. */
1505 base = get_inner_reference (ref, &bitsize, &bitpos, &toffset, &mode,
1506 &unsignedp, &volatilep, true);
1507 base_type = TREE_TYPE (base);
1508 base_align = TYPE_ALIGN (base_type);
1510 if (mode != BLKmode
1511 && (base_align < GET_MODE_ALIGNMENT (mode)
1512 || bitpos % GET_MODE_ALIGNMENT (mode) != 0
1513 || bitpos % BITS_PER_UNIT != 0))
1514 return true;
1516 return false;
1519 /* Finds addresses in *OP_P inside STMT. */
1521 static void
1522 find_interesting_uses_address (struct ivopts_data *data, tree stmt, tree *op_p)
1524 tree base = *op_p, step = NULL;
1525 struct iv *civ;
1526 struct ifs_ivopts_data ifs_ivopts_data;
1528 /* Do not play with volatile memory references. A bit too conservative,
1529 perhaps, but safe. */
1530 if (stmt_ann (stmt)->has_volatile_ops)
1531 goto fail;
1533 /* Ignore bitfields for now. Not really something terribly complicated
1534 to handle. TODO. */
1535 if (TREE_CODE (base) == COMPONENT_REF
1536 && DECL_NONADDRESSABLE_P (TREE_OPERAND (base, 1)))
1537 goto fail;
1539 if (STRICT_ALIGNMENT
1540 && may_be_unaligned_p (base))
1541 goto fail;
1543 base = unshare_expr (base);
1545 if (TREE_CODE (base) == TARGET_MEM_REF)
1547 tree type = build_pointer_type (TREE_TYPE (base));
1548 tree astep;
1550 if (TMR_BASE (base)
1551 && TREE_CODE (TMR_BASE (base)) == SSA_NAME)
1553 civ = get_iv (data, TMR_BASE (base));
1554 if (!civ)
1555 goto fail;
1557 TMR_BASE (base) = civ->base;
1558 step = civ->step;
1560 if (TMR_INDEX (base)
1561 && TREE_CODE (TMR_INDEX (base)) == SSA_NAME)
1563 civ = get_iv (data, TMR_INDEX (base));
1564 if (!civ)
1565 goto fail;
1567 TMR_INDEX (base) = civ->base;
1568 astep = civ->step;
1570 if (astep)
1572 if (TMR_STEP (base))
1573 astep = fold_build2 (MULT_EXPR, type, TMR_STEP (base), astep);
1575 if (step)
1576 step = fold_build2 (PLUS_EXPR, type, step, astep);
1577 else
1578 step = astep;
1582 if (zero_p (step))
1583 goto fail;
1584 base = tree_mem_ref_addr (type, base);
1586 else
1588 ifs_ivopts_data.ivopts_data = data;
1589 ifs_ivopts_data.stmt = stmt;
1590 ifs_ivopts_data.step_p = &step;
1591 if (!for_each_index (&base, idx_find_step, &ifs_ivopts_data)
1592 || zero_p (step))
1593 goto fail;
1595 gcc_assert (TREE_CODE (base) != ALIGN_INDIRECT_REF);
1596 gcc_assert (TREE_CODE (base) != MISALIGNED_INDIRECT_REF);
1598 base = build_fold_addr_expr (base);
1601 civ = alloc_iv (base, step);
1602 record_use (data, op_p, civ, stmt, USE_ADDRESS);
1603 return;
1605 fail:
1606 for_each_index (op_p, idx_record_use, data);
1609 /* Finds and records invariants used in STMT. */
1611 static void
1612 find_invariants_stmt (struct ivopts_data *data, tree stmt)
1614 ssa_op_iter iter;
1615 use_operand_p use_p;
1616 tree op;
1618 FOR_EACH_PHI_OR_STMT_USE (use_p, stmt, iter, SSA_OP_USE)
1620 op = USE_FROM_PTR (use_p);
1621 record_invariant (data, op, false);
1625 /* Finds interesting uses of induction variables in the statement STMT. */
1627 static void
1628 find_interesting_uses_stmt (struct ivopts_data *data, tree stmt)
1630 struct iv *iv;
1631 tree op, lhs, rhs;
1632 ssa_op_iter iter;
1633 use_operand_p use_p;
1635 find_invariants_stmt (data, stmt);
1637 if (TREE_CODE (stmt) == COND_EXPR)
1639 find_interesting_uses_cond (data, stmt, &COND_EXPR_COND (stmt));
1640 return;
1643 if (TREE_CODE (stmt) == MODIFY_EXPR)
1645 lhs = TREE_OPERAND (stmt, 0);
1646 rhs = TREE_OPERAND (stmt, 1);
1648 if (TREE_CODE (lhs) == SSA_NAME)
1650 /* If the statement defines an induction variable, the uses are not
1651 interesting by themselves. */
1653 iv = get_iv (data, lhs);
1655 if (iv && !zero_p (iv->step))
1656 return;
1659 switch (TREE_CODE_CLASS (TREE_CODE (rhs)))
1661 case tcc_comparison:
1662 find_interesting_uses_cond (data, stmt, &TREE_OPERAND (stmt, 1));
1663 return;
1665 case tcc_reference:
1666 find_interesting_uses_address (data, stmt, &TREE_OPERAND (stmt, 1));
1667 if (REFERENCE_CLASS_P (lhs))
1668 find_interesting_uses_address (data, stmt, &TREE_OPERAND (stmt, 0));
1669 return;
1671 default: ;
1674 if (REFERENCE_CLASS_P (lhs)
1675 && is_gimple_val (rhs))
1677 find_interesting_uses_address (data, stmt, &TREE_OPERAND (stmt, 0));
1678 find_interesting_uses_op (data, rhs);
1679 return;
1682 /* TODO -- we should also handle address uses of type
1684 memory = call (whatever);
1688 call (memory). */
1691 if (TREE_CODE (stmt) == PHI_NODE
1692 && bb_for_stmt (stmt) == data->current_loop->header)
1694 lhs = PHI_RESULT (stmt);
1695 iv = get_iv (data, lhs);
1697 if (iv && !zero_p (iv->step))
1698 return;
1701 FOR_EACH_PHI_OR_STMT_USE (use_p, stmt, iter, SSA_OP_USE)
1703 op = USE_FROM_PTR (use_p);
1705 if (TREE_CODE (op) != SSA_NAME)
1706 continue;
1708 iv = get_iv (data, op);
1709 if (!iv)
1710 continue;
1712 find_interesting_uses_op (data, op);
1716 /* Finds interesting uses of induction variables outside of loops
1717 on loop exit edge EXIT. */
1719 static void
1720 find_interesting_uses_outside (struct ivopts_data *data, edge exit)
1722 tree phi, def;
1724 for (phi = phi_nodes (exit->dest); phi; phi = PHI_CHAIN (phi))
1726 def = PHI_ARG_DEF_FROM_EDGE (phi, exit);
1727 find_interesting_uses_outer (data, def);
1731 /* Finds uses of the induction variables that are interesting. */
1733 static void
1734 find_interesting_uses (struct ivopts_data *data)
1736 basic_block bb;
1737 block_stmt_iterator bsi;
1738 tree phi;
1739 basic_block *body = get_loop_body (data->current_loop);
1740 unsigned i;
1741 struct version_info *info;
1742 edge e;
1744 if (dump_file && (dump_flags & TDF_DETAILS))
1745 fprintf (dump_file, "Uses:\n\n");
1747 for (i = 0; i < data->current_loop->num_nodes; i++)
1749 edge_iterator ei;
1750 bb = body[i];
1752 FOR_EACH_EDGE (e, ei, bb->succs)
1753 if (e->dest != EXIT_BLOCK_PTR
1754 && !flow_bb_inside_loop_p (data->current_loop, e->dest))
1755 find_interesting_uses_outside (data, e);
1757 for (phi = phi_nodes (bb); phi; phi = PHI_CHAIN (phi))
1758 find_interesting_uses_stmt (data, phi);
1759 for (bsi = bsi_start (bb); !bsi_end_p (bsi); bsi_next (&bsi))
1760 find_interesting_uses_stmt (data, bsi_stmt (bsi));
1763 if (dump_file && (dump_flags & TDF_DETAILS))
1765 bitmap_iterator bi;
1767 fprintf (dump_file, "\n");
1769 EXECUTE_IF_SET_IN_BITMAP (data->relevant, 0, i, bi)
1771 info = ver_info (data, i);
1772 if (info->inv_id)
1774 fprintf (dump_file, " ");
1775 print_generic_expr (dump_file, info->name, TDF_SLIM);
1776 fprintf (dump_file, " is invariant (%d)%s\n",
1777 info->inv_id, info->has_nonlin_use ? "" : ", eliminable");
1781 fprintf (dump_file, "\n");
1784 free (body);
1787 /* Strips constant offsets from EXPR and stores them to OFFSET. If INSIDE_ADDR
1788 is true, assume we are inside an address. If TOP_COMPREF is true, assume
1789 we are at the top-level of the processed address. */
1791 static tree
1792 strip_offset_1 (tree expr, bool inside_addr, bool top_compref,
1793 unsigned HOST_WIDE_INT *offset)
1795 tree op0 = NULL_TREE, op1 = NULL_TREE, tmp, step;
1796 enum tree_code code;
1797 tree type, orig_type = TREE_TYPE (expr);
1798 unsigned HOST_WIDE_INT off0, off1, st;
1799 tree orig_expr = expr;
1801 STRIP_NOPS (expr);
1803 type = TREE_TYPE (expr);
1804 code = TREE_CODE (expr);
1805 *offset = 0;
1807 switch (code)
1809 case INTEGER_CST:
1810 if (!cst_and_fits_in_hwi (expr)
1811 || zero_p (expr))
1812 return orig_expr;
1814 *offset = int_cst_value (expr);
1815 return build_int_cst_type (orig_type, 0);
1817 case PLUS_EXPR:
1818 case MINUS_EXPR:
1819 op0 = TREE_OPERAND (expr, 0);
1820 op1 = TREE_OPERAND (expr, 1);
1822 op0 = strip_offset_1 (op0, false, false, &off0);
1823 op1 = strip_offset_1 (op1, false, false, &off1);
1825 *offset = (code == PLUS_EXPR ? off0 + off1 : off0 - off1);
1826 if (op0 == TREE_OPERAND (expr, 0)
1827 && op1 == TREE_OPERAND (expr, 1))
1828 return orig_expr;
1830 if (zero_p (op1))
1831 expr = op0;
1832 else if (zero_p (op0))
1834 if (code == PLUS_EXPR)
1835 expr = op1;
1836 else
1837 expr = fold_build1 (NEGATE_EXPR, type, op1);
1839 else
1840 expr = fold_build2 (code, type, op0, op1);
1842 return fold_convert (orig_type, expr);
1844 case ARRAY_REF:
1845 if (!inside_addr)
1846 return orig_expr;
1848 step = array_ref_element_size (expr);
1849 if (!cst_and_fits_in_hwi (step))
1850 break;
1852 st = int_cst_value (step);
1853 op1 = TREE_OPERAND (expr, 1);
1854 op1 = strip_offset_1 (op1, false, false, &off1);
1855 *offset = off1 * st;
1857 if (top_compref
1858 && zero_p (op1))
1860 /* Strip the component reference completely. */
1861 op0 = TREE_OPERAND (expr, 0);
1862 op0 = strip_offset_1 (op0, inside_addr, top_compref, &off0);
1863 *offset += off0;
1864 return op0;
1866 break;
1868 case COMPONENT_REF:
1869 if (!inside_addr)
1870 return orig_expr;
1872 tmp = component_ref_field_offset (expr);
1873 if (top_compref
1874 && cst_and_fits_in_hwi (tmp))
1876 /* Strip the component reference completely. */
1877 op0 = TREE_OPERAND (expr, 0);
1878 op0 = strip_offset_1 (op0, inside_addr, top_compref, &off0);
1879 *offset = off0 + int_cst_value (tmp);
1880 return op0;
1882 break;
1884 case ADDR_EXPR:
1885 op0 = TREE_OPERAND (expr, 0);
1886 op0 = strip_offset_1 (op0, true, true, &off0);
1887 *offset += off0;
1889 if (op0 == TREE_OPERAND (expr, 0))
1890 return orig_expr;
1892 expr = build_fold_addr_expr (op0);
1893 return fold_convert (orig_type, expr);
1895 case INDIRECT_REF:
1896 inside_addr = false;
1897 break;
1899 default:
1900 return orig_expr;
1903 /* Default handling of expressions for that we want to recurse into
1904 the first operand. */
1905 op0 = TREE_OPERAND (expr, 0);
1906 op0 = strip_offset_1 (op0, inside_addr, false, &off0);
1907 *offset += off0;
1909 if (op0 == TREE_OPERAND (expr, 0)
1910 && (!op1 || op1 == TREE_OPERAND (expr, 1)))
1911 return orig_expr;
1913 expr = copy_node (expr);
1914 TREE_OPERAND (expr, 0) = op0;
1915 if (op1)
1916 TREE_OPERAND (expr, 1) = op1;
1918 /* Inside address, we might strip the top level component references,
1919 thus changing type of the expression. Handling of ADDR_EXPR
1920 will fix that. */
1921 expr = fold_convert (orig_type, expr);
1923 return expr;
1926 /* Strips constant offsets from EXPR and stores them to OFFSET. */
1928 static tree
1929 strip_offset (tree expr, unsigned HOST_WIDE_INT *offset)
1931 return strip_offset_1 (expr, false, false, offset);
1934 /* Returns variant of TYPE that can be used as base for different uses.
1935 For integer types, we return unsigned variant of the type, which
1936 avoids problems with overflows. For pointer types, we return void *. */
1938 static tree
1939 generic_type_for (tree type)
1941 if (POINTER_TYPE_P (type))
1942 return ptr_type_node;
1944 if (TYPE_UNSIGNED (type))
1945 return type;
1947 return unsigned_type_for (type);
1950 /* Records invariants in *EXPR_P. Callback for walk_tree. DATA contains
1951 the bitmap to that we should store it. */
1953 static struct ivopts_data *fd_ivopts_data;
1954 static tree
1955 find_depends (tree *expr_p, int *ws ATTRIBUTE_UNUSED, void *data)
1957 bitmap *depends_on = data;
1958 struct version_info *info;
1960 if (TREE_CODE (*expr_p) != SSA_NAME)
1961 return NULL_TREE;
1962 info = name_info (fd_ivopts_data, *expr_p);
1964 if (!info->inv_id || info->has_nonlin_use)
1965 return NULL_TREE;
1967 if (!*depends_on)
1968 *depends_on = BITMAP_ALLOC (NULL);
1969 bitmap_set_bit (*depends_on, info->inv_id);
1971 return NULL_TREE;
1974 /* Adds a candidate BASE + STEP * i. Important field is set to IMPORTANT and
1975 position to POS. If USE is not NULL, the candidate is set as related to
1976 it. If both BASE and STEP are NULL, we add a pseudocandidate for the
1977 replacement of the final value of the iv by a direct computation. */
1979 static struct iv_cand *
1980 add_candidate_1 (struct ivopts_data *data,
1981 tree base, tree step, bool important, enum iv_position pos,
1982 struct iv_use *use, tree incremented_at)
1984 unsigned i;
1985 struct iv_cand *cand = NULL;
1986 tree type, orig_type;
1988 if (base)
1990 orig_type = TREE_TYPE (base);
1991 type = generic_type_for (orig_type);
1992 if (type != orig_type)
1994 base = fold_convert (type, base);
1995 if (step)
1996 step = fold_convert (type, step);
2000 for (i = 0; i < n_iv_cands (data); i++)
2002 cand = iv_cand (data, i);
2004 if (cand->pos != pos)
2005 continue;
2007 if (cand->incremented_at != incremented_at)
2008 continue;
2010 if (!cand->iv)
2012 if (!base && !step)
2013 break;
2015 continue;
2018 if (!base && !step)
2019 continue;
2021 if (!operand_equal_p (base, cand->iv->base, 0))
2022 continue;
2024 if (zero_p (cand->iv->step))
2026 if (zero_p (step))
2027 break;
2029 else
2031 if (step && operand_equal_p (step, cand->iv->step, 0))
2032 break;
2036 if (i == n_iv_cands (data))
2038 cand = xcalloc (1, sizeof (struct iv_cand));
2039 cand->id = i;
2041 if (!base && !step)
2042 cand->iv = NULL;
2043 else
2044 cand->iv = alloc_iv (base, step);
2046 cand->pos = pos;
2047 if (pos != IP_ORIGINAL && cand->iv)
2049 cand->var_before = create_tmp_var_raw (TREE_TYPE (base), "ivtmp");
2050 cand->var_after = cand->var_before;
2052 cand->important = important;
2053 cand->incremented_at = incremented_at;
2054 VEC_safe_push (iv_cand_p, heap, data->iv_candidates, cand);
2056 if (step
2057 && TREE_CODE (step) != INTEGER_CST)
2059 fd_ivopts_data = data;
2060 walk_tree (&step, find_depends, &cand->depends_on, NULL);
2063 if (dump_file && (dump_flags & TDF_DETAILS))
2064 dump_cand (dump_file, cand);
2067 if (important && !cand->important)
2069 cand->important = true;
2070 if (dump_file && (dump_flags & TDF_DETAILS))
2071 fprintf (dump_file, "Candidate %d is important\n", cand->id);
2074 if (use)
2076 bitmap_set_bit (use->related_cands, i);
2077 if (dump_file && (dump_flags & TDF_DETAILS))
2078 fprintf (dump_file, "Candidate %d is related to use %d\n",
2079 cand->id, use->id);
2082 return cand;
2085 /* Returns true if incrementing the induction variable at the end of the LOOP
2086 is allowed.
2088 The purpose is to avoid splitting latch edge with a biv increment, thus
2089 creating a jump, possibly confusing other optimization passes and leaving
2090 less freedom to scheduler. So we allow IP_END_POS only if IP_NORMAL_POS
2091 is not available (so we do not have a better alternative), or if the latch
2092 edge is already nonempty. */
2094 static bool
2095 allow_ip_end_pos_p (struct loop *loop)
2097 if (!ip_normal_pos (loop))
2098 return true;
2100 if (!empty_block_p (ip_end_pos (loop)))
2101 return true;
2103 return false;
2106 /* Adds a candidate BASE + STEP * i. Important field is set to IMPORTANT and
2107 position to POS. If USE is not NULL, the candidate is set as related to
2108 it. The candidate computation is scheduled on all available positions. */
2110 static void
2111 add_candidate (struct ivopts_data *data,
2112 tree base, tree step, bool important, struct iv_use *use)
2114 if (ip_normal_pos (data->current_loop))
2115 add_candidate_1 (data, base, step, important, IP_NORMAL, use, NULL_TREE);
2116 if (ip_end_pos (data->current_loop)
2117 && allow_ip_end_pos_p (data->current_loop))
2118 add_candidate_1 (data, base, step, important, IP_END, use, NULL_TREE);
2121 /* Add a standard "0 + 1 * iteration" iv candidate for a
2122 type with SIZE bits. */
2124 static void
2125 add_standard_iv_candidates_for_size (struct ivopts_data *data,
2126 unsigned int size)
2128 tree type = lang_hooks.types.type_for_size (size, true);
2129 add_candidate (data, build_int_cst (type, 0), build_int_cst (type, 1),
2130 true, NULL);
2133 /* Adds standard iv candidates. */
2135 static void
2136 add_standard_iv_candidates (struct ivopts_data *data)
2138 add_standard_iv_candidates_for_size (data, INT_TYPE_SIZE);
2140 /* The same for a double-integer type if it is still fast enough. */
2141 if (BITS_PER_WORD >= INT_TYPE_SIZE * 2)
2142 add_standard_iv_candidates_for_size (data, INT_TYPE_SIZE * 2);
2146 /* Adds candidates bases on the old induction variable IV. */
2148 static void
2149 add_old_iv_candidates (struct ivopts_data *data, struct iv *iv)
2151 tree phi, def;
2152 struct iv_cand *cand;
2154 add_candidate (data, iv->base, iv->step, true, NULL);
2156 /* The same, but with initial value zero. */
2157 add_candidate (data,
2158 build_int_cst (TREE_TYPE (iv->base), 0),
2159 iv->step, true, NULL);
2161 phi = SSA_NAME_DEF_STMT (iv->ssa_name);
2162 if (TREE_CODE (phi) == PHI_NODE)
2164 /* Additionally record the possibility of leaving the original iv
2165 untouched. */
2166 def = PHI_ARG_DEF_FROM_EDGE (phi, loop_latch_edge (data->current_loop));
2167 cand = add_candidate_1 (data,
2168 iv->base, iv->step, true, IP_ORIGINAL, NULL,
2169 SSA_NAME_DEF_STMT (def));
2170 cand->var_before = iv->ssa_name;
2171 cand->var_after = def;
2175 /* Adds candidates based on the old induction variables. */
2177 static void
2178 add_old_ivs_candidates (struct ivopts_data *data)
2180 unsigned i;
2181 struct iv *iv;
2182 bitmap_iterator bi;
2184 EXECUTE_IF_SET_IN_BITMAP (data->relevant, 0, i, bi)
2186 iv = ver_info (data, i)->iv;
2187 if (iv && iv->biv_p && !zero_p (iv->step))
2188 add_old_iv_candidates (data, iv);
2192 /* Adds candidates based on the value of the induction variable IV and USE. */
2194 static void
2195 add_iv_value_candidates (struct ivopts_data *data,
2196 struct iv *iv, struct iv_use *use)
2198 unsigned HOST_WIDE_INT offset;
2199 tree base;
2201 add_candidate (data, iv->base, iv->step, false, use);
2203 /* The same, but with initial value zero. Make such variable important,
2204 since it is generic enough so that possibly many uses may be based
2205 on it. */
2206 add_candidate (data, build_int_cst (TREE_TYPE (iv->base), 0),
2207 iv->step, true, use);
2209 /* Third, try removing the constant offset. */
2210 base = strip_offset (iv->base, &offset);
2211 if (offset)
2212 add_candidate (data, base, iv->step, false, use);
2215 /* Possibly adds pseudocandidate for replacing the final value of USE by
2216 a direct computation. */
2218 static void
2219 add_iv_outer_candidates (struct ivopts_data *data, struct iv_use *use)
2221 struct tree_niter_desc *niter;
2223 /* We must know where we exit the loop and how many times does it roll. */
2224 niter = niter_for_single_dom_exit (data);
2225 if (!niter
2226 || !zero_p (niter->may_be_zero))
2227 return;
2229 add_candidate_1 (data, NULL, NULL, false, IP_NORMAL, use, NULL_TREE);
2232 /* Adds candidates based on the uses. */
2234 static void
2235 add_derived_ivs_candidates (struct ivopts_data *data)
2237 unsigned i;
2239 for (i = 0; i < n_iv_uses (data); i++)
2241 struct iv_use *use = iv_use (data, i);
2243 if (!use)
2244 continue;
2246 switch (use->type)
2248 case USE_NONLINEAR_EXPR:
2249 case USE_COMPARE:
2250 case USE_ADDRESS:
2251 /* Just add the ivs based on the value of the iv used here. */
2252 add_iv_value_candidates (data, use->iv, use);
2253 break;
2255 case USE_OUTER:
2256 add_iv_value_candidates (data, use->iv, use);
2258 /* Additionally, add the pseudocandidate for the possibility to
2259 replace the final value by a direct computation. */
2260 add_iv_outer_candidates (data, use);
2261 break;
2263 default:
2264 gcc_unreachable ();
2269 /* Record important candidates and add them to related_cands bitmaps
2270 if needed. */
2272 static void
2273 record_important_candidates (struct ivopts_data *data)
2275 unsigned i;
2276 struct iv_use *use;
2278 for (i = 0; i < n_iv_cands (data); i++)
2280 struct iv_cand *cand = iv_cand (data, i);
2282 if (cand->important)
2283 bitmap_set_bit (data->important_candidates, i);
2286 data->consider_all_candidates = (n_iv_cands (data)
2287 <= CONSIDER_ALL_CANDIDATES_BOUND);
2289 if (data->consider_all_candidates)
2291 /* We will not need "related_cands" bitmaps in this case,
2292 so release them to decrease peak memory consumption. */
2293 for (i = 0; i < n_iv_uses (data); i++)
2295 use = iv_use (data, i);
2296 BITMAP_FREE (use->related_cands);
2299 else
2301 /* Add important candidates to the related_cands bitmaps. */
2302 for (i = 0; i < n_iv_uses (data); i++)
2303 bitmap_ior_into (iv_use (data, i)->related_cands,
2304 data->important_candidates);
2308 /* Finds the candidates for the induction variables. */
2310 static void
2311 find_iv_candidates (struct ivopts_data *data)
2313 /* Add commonly used ivs. */
2314 add_standard_iv_candidates (data);
2316 /* Add old induction variables. */
2317 add_old_ivs_candidates (data);
2319 /* Add induction variables derived from uses. */
2320 add_derived_ivs_candidates (data);
2322 /* Record the important candidates. */
2323 record_important_candidates (data);
2326 /* Allocates the data structure mapping the (use, candidate) pairs to costs.
2327 If consider_all_candidates is true, we use a two-dimensional array, otherwise
2328 we allocate a simple list to every use. */
2330 static void
2331 alloc_use_cost_map (struct ivopts_data *data)
2333 unsigned i, size, s, j;
2335 for (i = 0; i < n_iv_uses (data); i++)
2337 struct iv_use *use = iv_use (data, i);
2338 bitmap_iterator bi;
2340 if (data->consider_all_candidates)
2341 size = n_iv_cands (data);
2342 else
2344 s = 0;
2345 EXECUTE_IF_SET_IN_BITMAP (use->related_cands, 0, j, bi)
2347 s++;
2350 /* Round up to the power of two, so that moduling by it is fast. */
2351 for (size = 1; size < s; size <<= 1)
2352 continue;
2355 use->n_map_members = size;
2356 use->cost_map = xcalloc (size, sizeof (struct cost_pair));
2360 /* Sets cost of (USE, CANDIDATE) pair to COST and record that it depends
2361 on invariants DEPENDS_ON and that the value used in expressing it
2362 is VALUE.*/
2364 static void
2365 set_use_iv_cost (struct ivopts_data *data,
2366 struct iv_use *use, struct iv_cand *cand, unsigned cost,
2367 bitmap depends_on, tree value)
2369 unsigned i, s;
2371 if (cost == INFTY)
2373 BITMAP_FREE (depends_on);
2374 return;
2377 if (data->consider_all_candidates)
2379 use->cost_map[cand->id].cand = cand;
2380 use->cost_map[cand->id].cost = cost;
2381 use->cost_map[cand->id].depends_on = depends_on;
2382 use->cost_map[cand->id].value = value;
2383 return;
2386 /* n_map_members is a power of two, so this computes modulo. */
2387 s = cand->id & (use->n_map_members - 1);
2388 for (i = s; i < use->n_map_members; i++)
2389 if (!use->cost_map[i].cand)
2390 goto found;
2391 for (i = 0; i < s; i++)
2392 if (!use->cost_map[i].cand)
2393 goto found;
2395 gcc_unreachable ();
2397 found:
2398 use->cost_map[i].cand = cand;
2399 use->cost_map[i].cost = cost;
2400 use->cost_map[i].depends_on = depends_on;
2401 use->cost_map[i].value = value;
2404 /* Gets cost of (USE, CANDIDATE) pair. */
2406 static struct cost_pair *
2407 get_use_iv_cost (struct ivopts_data *data, struct iv_use *use,
2408 struct iv_cand *cand)
2410 unsigned i, s;
2411 struct cost_pair *ret;
2413 if (!cand)
2414 return NULL;
2416 if (data->consider_all_candidates)
2418 ret = use->cost_map + cand->id;
2419 if (!ret->cand)
2420 return NULL;
2422 return ret;
2425 /* n_map_members is a power of two, so this computes modulo. */
2426 s = cand->id & (use->n_map_members - 1);
2427 for (i = s; i < use->n_map_members; i++)
2428 if (use->cost_map[i].cand == cand)
2429 return use->cost_map + i;
2431 for (i = 0; i < s; i++)
2432 if (use->cost_map[i].cand == cand)
2433 return use->cost_map + i;
2435 return NULL;
2438 /* Returns estimate on cost of computing SEQ. */
2440 static unsigned
2441 seq_cost (rtx seq)
2443 unsigned cost = 0;
2444 rtx set;
2446 for (; seq; seq = NEXT_INSN (seq))
2448 set = single_set (seq);
2449 if (set)
2450 cost += rtx_cost (set, SET);
2451 else
2452 cost++;
2455 return cost;
2458 /* Produce DECL_RTL for object obj so it looks like it is stored in memory. */
2459 static rtx
2460 produce_memory_decl_rtl (tree obj, int *regno)
2462 rtx x;
2464 gcc_assert (obj);
2465 if (TREE_STATIC (obj) || DECL_EXTERNAL (obj))
2467 const char *name = IDENTIFIER_POINTER (DECL_ASSEMBLER_NAME (obj));
2468 x = gen_rtx_SYMBOL_REF (Pmode, name);
2470 else
2471 x = gen_raw_REG (Pmode, (*regno)++);
2473 return gen_rtx_MEM (DECL_MODE (obj), x);
2476 /* Prepares decl_rtl for variables referred in *EXPR_P. Callback for
2477 walk_tree. DATA contains the actual fake register number. */
2479 static tree
2480 prepare_decl_rtl (tree *expr_p, int *ws, void *data)
2482 tree obj = NULL_TREE;
2483 rtx x = NULL_RTX;
2484 int *regno = data;
2486 switch (TREE_CODE (*expr_p))
2488 case ADDR_EXPR:
2489 for (expr_p = &TREE_OPERAND (*expr_p, 0);
2490 handled_component_p (*expr_p);
2491 expr_p = &TREE_OPERAND (*expr_p, 0))
2492 continue;
2493 obj = *expr_p;
2494 if (DECL_P (obj))
2495 x = produce_memory_decl_rtl (obj, regno);
2496 break;
2498 case SSA_NAME:
2499 *ws = 0;
2500 obj = SSA_NAME_VAR (*expr_p);
2501 if (!DECL_RTL_SET_P (obj))
2502 x = gen_raw_REG (DECL_MODE (obj), (*regno)++);
2503 break;
2505 case VAR_DECL:
2506 case PARM_DECL:
2507 case RESULT_DECL:
2508 *ws = 0;
2509 obj = *expr_p;
2511 if (DECL_RTL_SET_P (obj))
2512 break;
2514 if (DECL_MODE (obj) == BLKmode)
2515 x = produce_memory_decl_rtl (obj, regno);
2516 else
2517 x = gen_raw_REG (DECL_MODE (obj), (*regno)++);
2519 break;
2521 default:
2522 break;
2525 if (x)
2527 VEC_safe_push (tree, heap, decl_rtl_to_reset, obj);
2528 SET_DECL_RTL (obj, x);
2531 return NULL_TREE;
2534 /* Determines cost of the computation of EXPR. */
2536 static unsigned
2537 computation_cost (tree expr)
2539 rtx seq, rslt;
2540 tree type = TREE_TYPE (expr);
2541 unsigned cost;
2542 /* Avoid using hard regs in ways which may be unsupported. */
2543 int regno = LAST_VIRTUAL_REGISTER + 1;
2545 walk_tree (&expr, prepare_decl_rtl, &regno, NULL);
2546 start_sequence ();
2547 rslt = expand_expr (expr, NULL_RTX, TYPE_MODE (type), EXPAND_NORMAL);
2548 seq = get_insns ();
2549 end_sequence ();
2551 cost = seq_cost (seq);
2552 if (MEM_P (rslt))
2553 cost += address_cost (XEXP (rslt, 0), TYPE_MODE (type));
2555 return cost;
2558 /* Returns variable containing the value of candidate CAND at statement AT. */
2560 static tree
2561 var_at_stmt (struct loop *loop, struct iv_cand *cand, tree stmt)
2563 if (stmt_after_increment (loop, cand, stmt))
2564 return cand->var_after;
2565 else
2566 return cand->var_before;
2569 /* Return the most significant (sign) bit of T. Similar to tree_int_cst_msb,
2570 but the bit is determined from TYPE_PRECISION, not MODE_BITSIZE. */
2573 tree_int_cst_sign_bit (tree t)
2575 unsigned bitno = TYPE_PRECISION (TREE_TYPE (t)) - 1;
2576 unsigned HOST_WIDE_INT w;
2578 if (bitno < HOST_BITS_PER_WIDE_INT)
2579 w = TREE_INT_CST_LOW (t);
2580 else
2582 w = TREE_INT_CST_HIGH (t);
2583 bitno -= HOST_BITS_PER_WIDE_INT;
2586 return (w >> bitno) & 1;
2589 /* If we can prove that TOP = cst * BOT for some constant cst in TYPE,
2590 return cst. Otherwise return NULL_TREE. */
2592 static tree
2593 constant_multiple_of (tree type, tree top, tree bot)
2595 tree res, mby, p0, p1;
2596 enum tree_code code;
2597 bool negate;
2599 STRIP_NOPS (top);
2600 STRIP_NOPS (bot);
2602 if (operand_equal_p (top, bot, 0))
2603 return build_int_cst (type, 1);
2605 code = TREE_CODE (top);
2606 switch (code)
2608 case MULT_EXPR:
2609 mby = TREE_OPERAND (top, 1);
2610 if (TREE_CODE (mby) != INTEGER_CST)
2611 return NULL_TREE;
2613 res = constant_multiple_of (type, TREE_OPERAND (top, 0), bot);
2614 if (!res)
2615 return NULL_TREE;
2617 return fold_binary_to_constant (MULT_EXPR, type, res,
2618 fold_convert (type, mby));
2620 case PLUS_EXPR:
2621 case MINUS_EXPR:
2622 p0 = constant_multiple_of (type, TREE_OPERAND (top, 0), bot);
2623 if (!p0)
2624 return NULL_TREE;
2625 p1 = constant_multiple_of (type, TREE_OPERAND (top, 1), bot);
2626 if (!p1)
2627 return NULL_TREE;
2629 return fold_binary_to_constant (code, type, p0, p1);
2631 case INTEGER_CST:
2632 if (TREE_CODE (bot) != INTEGER_CST)
2633 return NULL_TREE;
2635 bot = fold_convert (type, bot);
2636 top = fold_convert (type, top);
2638 /* If BOT seems to be negative, try dividing by -BOT instead, and negate
2639 the result afterwards. */
2640 if (tree_int_cst_sign_bit (bot))
2642 negate = true;
2643 bot = fold_unary_to_constant (NEGATE_EXPR, type, bot);
2645 else
2646 negate = false;
2648 /* Ditto for TOP. */
2649 if (tree_int_cst_sign_bit (top))
2651 negate = !negate;
2652 top = fold_unary_to_constant (NEGATE_EXPR, type, top);
2655 if (!zero_p (fold_binary_to_constant (TRUNC_MOD_EXPR, type, top, bot)))
2656 return NULL_TREE;
2658 res = fold_binary_to_constant (EXACT_DIV_EXPR, type, top, bot);
2659 if (negate)
2660 res = fold_unary_to_constant (NEGATE_EXPR, type, res);
2661 return res;
2663 default:
2664 return NULL_TREE;
2668 /* Sets COMB to CST. */
2670 static void
2671 aff_combination_const (struct affine_tree_combination *comb, tree type,
2672 unsigned HOST_WIDE_INT cst)
2674 unsigned prec = TYPE_PRECISION (type);
2676 comb->type = type;
2677 comb->mask = (((unsigned HOST_WIDE_INT) 2 << (prec - 1)) - 1);
2679 comb->n = 0;
2680 comb->rest = NULL_TREE;
2681 comb->offset = cst & comb->mask;
2684 /* Sets COMB to single element ELT. */
2686 static void
2687 aff_combination_elt (struct affine_tree_combination *comb, tree type, tree elt)
2689 unsigned prec = TYPE_PRECISION (type);
2691 comb->type = type;
2692 comb->mask = (((unsigned HOST_WIDE_INT) 2 << (prec - 1)) - 1);
2694 comb->n = 1;
2695 comb->elts[0] = elt;
2696 comb->coefs[0] = 1;
2697 comb->rest = NULL_TREE;
2698 comb->offset = 0;
2701 /* Scales COMB by SCALE. */
2703 static void
2704 aff_combination_scale (struct affine_tree_combination *comb,
2705 unsigned HOST_WIDE_INT scale)
2707 unsigned i, j;
2709 if (scale == 1)
2710 return;
2712 if (scale == 0)
2714 aff_combination_const (comb, comb->type, 0);
2715 return;
2718 comb->offset = (scale * comb->offset) & comb->mask;
2719 for (i = 0, j = 0; i < comb->n; i++)
2721 comb->coefs[j] = (scale * comb->coefs[i]) & comb->mask;
2722 comb->elts[j] = comb->elts[i];
2723 if (comb->coefs[j] != 0)
2724 j++;
2726 comb->n = j;
2728 if (comb->rest)
2730 if (comb->n < MAX_AFF_ELTS)
2732 comb->coefs[comb->n] = scale;
2733 comb->elts[comb->n] = comb->rest;
2734 comb->rest = NULL_TREE;
2735 comb->n++;
2737 else
2738 comb->rest = fold_build2 (MULT_EXPR, comb->type, comb->rest,
2739 build_int_cst_type (comb->type, scale));
2743 /* Adds ELT * SCALE to COMB. */
2745 static void
2746 aff_combination_add_elt (struct affine_tree_combination *comb, tree elt,
2747 unsigned HOST_WIDE_INT scale)
2749 unsigned i;
2751 if (scale == 0)
2752 return;
2754 for (i = 0; i < comb->n; i++)
2755 if (operand_equal_p (comb->elts[i], elt, 0))
2757 comb->coefs[i] = (comb->coefs[i] + scale) & comb->mask;
2758 if (comb->coefs[i])
2759 return;
2761 comb->n--;
2762 comb->coefs[i] = comb->coefs[comb->n];
2763 comb->elts[i] = comb->elts[comb->n];
2764 return;
2766 if (comb->n < MAX_AFF_ELTS)
2768 comb->coefs[comb->n] = scale;
2769 comb->elts[comb->n] = elt;
2770 comb->n++;
2771 return;
2774 if (scale == 1)
2775 elt = fold_convert (comb->type, elt);
2776 else
2777 elt = fold_build2 (MULT_EXPR, comb->type,
2778 fold_convert (comb->type, elt),
2779 build_int_cst_type (comb->type, scale));
2781 if (comb->rest)
2782 comb->rest = fold_build2 (PLUS_EXPR, comb->type, comb->rest, elt);
2783 else
2784 comb->rest = elt;
2787 /* Adds COMB2 to COMB1. */
2789 static void
2790 aff_combination_add (struct affine_tree_combination *comb1,
2791 struct affine_tree_combination *comb2)
2793 unsigned i;
2795 comb1->offset = (comb1->offset + comb2->offset) & comb1->mask;
2796 for (i = 0; i < comb2-> n; i++)
2797 aff_combination_add_elt (comb1, comb2->elts[i], comb2->coefs[i]);
2798 if (comb2->rest)
2799 aff_combination_add_elt (comb1, comb2->rest, 1);
2802 /* Splits EXPR into an affine combination of parts. */
2804 static void
2805 tree_to_aff_combination (tree expr, tree type,
2806 struct affine_tree_combination *comb)
2808 struct affine_tree_combination tmp;
2809 enum tree_code code;
2810 tree cst, core, toffset;
2811 HOST_WIDE_INT bitpos, bitsize;
2812 enum machine_mode mode;
2813 int unsignedp, volatilep;
2815 STRIP_NOPS (expr);
2817 code = TREE_CODE (expr);
2818 switch (code)
2820 case INTEGER_CST:
2821 aff_combination_const (comb, type, int_cst_value (expr));
2822 return;
2824 case PLUS_EXPR:
2825 case MINUS_EXPR:
2826 tree_to_aff_combination (TREE_OPERAND (expr, 0), type, comb);
2827 tree_to_aff_combination (TREE_OPERAND (expr, 1), type, &tmp);
2828 if (code == MINUS_EXPR)
2829 aff_combination_scale (&tmp, -1);
2830 aff_combination_add (comb, &tmp);
2831 return;
2833 case MULT_EXPR:
2834 cst = TREE_OPERAND (expr, 1);
2835 if (TREE_CODE (cst) != INTEGER_CST)
2836 break;
2837 tree_to_aff_combination (TREE_OPERAND (expr, 0), type, comb);
2838 aff_combination_scale (comb, int_cst_value (cst));
2839 return;
2841 case NEGATE_EXPR:
2842 tree_to_aff_combination (TREE_OPERAND (expr, 0), type, comb);
2843 aff_combination_scale (comb, -1);
2844 return;
2846 case ADDR_EXPR:
2847 core = get_inner_reference (TREE_OPERAND (expr, 0), &bitsize, &bitpos,
2848 &toffset, &mode, &unsignedp, &volatilep,
2849 false);
2850 if (bitpos % BITS_PER_UNIT != 0)
2851 break;
2852 aff_combination_const (comb, type, bitpos / BITS_PER_UNIT);
2853 core = build_fold_addr_expr (core);
2854 if (TREE_CODE (core) == ADDR_EXPR)
2855 aff_combination_add_elt (comb, core, 1);
2856 else
2858 tree_to_aff_combination (core, type, &tmp);
2859 aff_combination_add (comb, &tmp);
2861 if (toffset)
2863 tree_to_aff_combination (toffset, type, &tmp);
2864 aff_combination_add (comb, &tmp);
2866 return;
2868 default:
2869 break;
2872 aff_combination_elt (comb, type, expr);
2875 /* Creates EXPR + ELT * SCALE in TYPE. MASK is the mask for width of TYPE. */
2877 static tree
2878 add_elt_to_tree (tree expr, tree type, tree elt, unsigned HOST_WIDE_INT scale,
2879 unsigned HOST_WIDE_INT mask)
2881 enum tree_code code;
2883 scale &= mask;
2884 elt = fold_convert (type, elt);
2886 if (scale == 1)
2888 if (!expr)
2889 return elt;
2891 return fold_build2 (PLUS_EXPR, type, expr, elt);
2894 if (scale == mask)
2896 if (!expr)
2897 return fold_build1 (NEGATE_EXPR, type, elt);
2899 return fold_build2 (MINUS_EXPR, type, expr, elt);
2902 if (!expr)
2903 return fold_build2 (MULT_EXPR, type, elt,
2904 build_int_cst_type (type, scale));
2906 if ((scale | (mask >> 1)) == mask)
2908 /* Scale is negative. */
2909 code = MINUS_EXPR;
2910 scale = (-scale) & mask;
2912 else
2913 code = PLUS_EXPR;
2915 elt = fold_build2 (MULT_EXPR, type, elt,
2916 build_int_cst_type (type, scale));
2917 return fold_build2 (code, type, expr, elt);
2920 /* Copies the tree elements of COMB to ensure that they are not shared. */
2922 static void
2923 unshare_aff_combination (struct affine_tree_combination *comb)
2925 unsigned i;
2927 for (i = 0; i < comb->n; i++)
2928 comb->elts[i] = unshare_expr (comb->elts[i]);
2929 if (comb->rest)
2930 comb->rest = unshare_expr (comb->rest);
2933 /* Makes tree from the affine combination COMB. */
2935 static tree
2936 aff_combination_to_tree (struct affine_tree_combination *comb)
2938 tree type = comb->type;
2939 tree expr = comb->rest;
2940 unsigned i;
2941 unsigned HOST_WIDE_INT off, sgn;
2943 /* Handle the special case produced by get_computation_aff when
2944 the type does not fit in HOST_WIDE_INT. */
2945 if (comb->n == 0 && comb->offset == 0)
2946 return fold_convert (type, expr);
2948 gcc_assert (comb->n == MAX_AFF_ELTS || comb->rest == NULL_TREE);
2950 for (i = 0; i < comb->n; i++)
2951 expr = add_elt_to_tree (expr, type, comb->elts[i], comb->coefs[i],
2952 comb->mask);
2954 if ((comb->offset | (comb->mask >> 1)) == comb->mask)
2956 /* Offset is negative. */
2957 off = (-comb->offset) & comb->mask;
2958 sgn = comb->mask;
2960 else
2962 off = comb->offset;
2963 sgn = 1;
2965 return add_elt_to_tree (expr, type, build_int_cst_type (type, off), sgn,
2966 comb->mask);
2969 /* Determines the expression by that USE is expressed from induction variable
2970 CAND at statement AT in LOOP. The expression is stored in a decomposed
2971 form into AFF. Returns false if USE cannot be expressed using CAND. */
2973 static bool
2974 get_computation_aff (struct loop *loop,
2975 struct iv_use *use, struct iv_cand *cand, tree at,
2976 struct affine_tree_combination *aff)
2978 tree ubase = use->iv->base;
2979 tree ustep = use->iv->step;
2980 tree cbase = cand->iv->base;
2981 tree cstep = cand->iv->step;
2982 tree utype = TREE_TYPE (ubase), ctype = TREE_TYPE (cbase);
2983 tree uutype;
2984 tree expr, delta;
2985 tree ratio;
2986 unsigned HOST_WIDE_INT ustepi, cstepi;
2987 HOST_WIDE_INT ratioi;
2988 struct affine_tree_combination cbase_aff, expr_aff;
2989 tree cstep_orig = cstep, ustep_orig = ustep;
2991 if (TYPE_PRECISION (utype) > TYPE_PRECISION (ctype))
2993 /* We do not have a precision to express the values of use. */
2994 return false;
2997 expr = var_at_stmt (loop, cand, at);
2999 if (TREE_TYPE (expr) != ctype)
3001 /* This may happen with the original ivs. */
3002 expr = fold_convert (ctype, expr);
3005 if (TYPE_UNSIGNED (utype))
3006 uutype = utype;
3007 else
3009 uutype = unsigned_type_for (utype);
3010 ubase = fold_convert (uutype, ubase);
3011 ustep = fold_convert (uutype, ustep);
3014 if (uutype != ctype)
3016 expr = fold_convert (uutype, expr);
3017 cbase = fold_convert (uutype, cbase);
3018 cstep = fold_convert (uutype, cstep);
3020 /* If the conversion is not noop, we must take it into account when
3021 considering the value of the step. */
3022 if (TYPE_PRECISION (utype) < TYPE_PRECISION (ctype))
3023 cstep_orig = cstep;
3026 if (cst_and_fits_in_hwi (cstep_orig)
3027 && cst_and_fits_in_hwi (ustep_orig))
3029 ustepi = int_cst_value (ustep_orig);
3030 cstepi = int_cst_value (cstep_orig);
3032 if (!divide (TYPE_PRECISION (uutype), ustepi, cstepi, &ratioi))
3034 /* TODO maybe consider case when ustep divides cstep and the ratio is
3035 a power of 2 (so that the division is fast to execute)? We would
3036 need to be much more careful with overflows etc. then. */
3037 return false;
3040 ratio = build_int_cst_type (uutype, ratioi);
3042 else
3044 ratio = constant_multiple_of (uutype, ustep_orig, cstep_orig);
3045 if (!ratio)
3046 return false;
3048 /* Ratioi is only used to detect special cases when the multiplicative
3049 factor is 1 or -1, so if we cannot convert ratio to HOST_WIDE_INT,
3050 we may set it to 0. We prefer cst_and_fits_in_hwi/int_cst_value
3051 to integer_onep/integer_all_onesp, since the former ignores
3052 TREE_OVERFLOW. */
3053 if (cst_and_fits_in_hwi (ratio))
3054 ratioi = int_cst_value (ratio);
3055 else if (integer_onep (ratio))
3056 ratioi = 1;
3057 else if (integer_all_onesp (ratio))
3058 ratioi = -1;
3059 else
3060 ratioi = 0;
3063 /* We may need to shift the value if we are after the increment. */
3064 if (stmt_after_increment (loop, cand, at))
3065 cbase = fold_build2 (PLUS_EXPR, uutype, cbase, cstep);
3067 /* use = ubase - ratio * cbase + ratio * var.
3069 In general case ubase + ratio * (var - cbase) could be better (one less
3070 multiplication), but often it is possible to eliminate redundant parts
3071 of computations from (ubase - ratio * cbase) term, and if it does not
3072 happen, fold is able to apply the distributive law to obtain this form
3073 anyway. */
3075 if (TYPE_PRECISION (uutype) > HOST_BITS_PER_WIDE_INT)
3077 /* Let's compute in trees and just return the result in AFF. This case
3078 should not be very common, and fold itself is not that bad either,
3079 so making the aff. functions more complicated to handle this case
3080 is not that urgent. */
3081 if (ratioi == 1)
3083 delta = fold_build2 (MINUS_EXPR, uutype, ubase, cbase);
3084 expr = fold_build2 (PLUS_EXPR, uutype, expr, delta);
3086 else if (ratioi == -1)
3088 delta = fold_build2 (PLUS_EXPR, uutype, ubase, cbase);
3089 expr = fold_build2 (MINUS_EXPR, uutype, delta, expr);
3091 else
3093 delta = fold_build2 (MULT_EXPR, uutype, cbase, ratio);
3094 delta = fold_build2 (MINUS_EXPR, uutype, ubase, delta);
3095 expr = fold_build2 (MULT_EXPR, uutype, ratio, expr);
3096 expr = fold_build2 (PLUS_EXPR, uutype, delta, expr);
3099 aff->type = uutype;
3100 aff->n = 0;
3101 aff->offset = 0;
3102 aff->mask = 0;
3103 aff->rest = expr;
3104 return true;
3107 /* If we got here, the types fits in HOST_WIDE_INT, thus it must be
3108 possible to compute ratioi. */
3109 gcc_assert (ratioi);
3111 tree_to_aff_combination (ubase, uutype, aff);
3112 tree_to_aff_combination (cbase, uutype, &cbase_aff);
3113 tree_to_aff_combination (expr, uutype, &expr_aff);
3114 aff_combination_scale (&cbase_aff, -ratioi);
3115 aff_combination_scale (&expr_aff, ratioi);
3116 aff_combination_add (aff, &cbase_aff);
3117 aff_combination_add (aff, &expr_aff);
3119 return true;
3122 /* Determines the expression by that USE is expressed from induction variable
3123 CAND at statement AT in LOOP. The computation is unshared. */
3125 static tree
3126 get_computation_at (struct loop *loop,
3127 struct iv_use *use, struct iv_cand *cand, tree at)
3129 struct affine_tree_combination aff;
3130 tree type = TREE_TYPE (use->iv->base);
3132 if (!get_computation_aff (loop, use, cand, at, &aff))
3133 return NULL_TREE;
3134 unshare_aff_combination (&aff);
3135 return fold_convert (type, aff_combination_to_tree (&aff));
3138 /* Determines the expression by that USE is expressed from induction variable
3139 CAND in LOOP. The computation is unshared. */
3141 static tree
3142 get_computation (struct loop *loop, struct iv_use *use, struct iv_cand *cand)
3144 return get_computation_at (loop, use, cand, use->stmt);
3147 /* Returns cost of addition in MODE. */
3149 static unsigned
3150 add_cost (enum machine_mode mode)
3152 static unsigned costs[NUM_MACHINE_MODES];
3153 rtx seq;
3154 unsigned cost;
3156 if (costs[mode])
3157 return costs[mode];
3159 start_sequence ();
3160 force_operand (gen_rtx_fmt_ee (PLUS, mode,
3161 gen_raw_REG (mode, LAST_VIRTUAL_REGISTER + 1),
3162 gen_raw_REG (mode, LAST_VIRTUAL_REGISTER + 2)),
3163 NULL_RTX);
3164 seq = get_insns ();
3165 end_sequence ();
3167 cost = seq_cost (seq);
3168 if (!cost)
3169 cost = 1;
3171 costs[mode] = cost;
3173 if (dump_file && (dump_flags & TDF_DETAILS))
3174 fprintf (dump_file, "Addition in %s costs %d\n",
3175 GET_MODE_NAME (mode), cost);
3176 return cost;
3179 /* Entry in a hashtable of already known costs for multiplication. */
3180 struct mbc_entry
3182 HOST_WIDE_INT cst; /* The constant to multiply by. */
3183 enum machine_mode mode; /* In mode. */
3184 unsigned cost; /* The cost. */
3187 /* Counts hash value for the ENTRY. */
3189 static hashval_t
3190 mbc_entry_hash (const void *entry)
3192 const struct mbc_entry *e = entry;
3194 return 57 * (hashval_t) e->mode + (hashval_t) (e->cst % 877);
3197 /* Compares the hash table entries ENTRY1 and ENTRY2. */
3199 static int
3200 mbc_entry_eq (const void *entry1, const void *entry2)
3202 const struct mbc_entry *e1 = entry1;
3203 const struct mbc_entry *e2 = entry2;
3205 return (e1->mode == e2->mode
3206 && e1->cst == e2->cst);
3209 /* Returns cost of multiplication by constant CST in MODE. */
3211 unsigned
3212 multiply_by_cost (HOST_WIDE_INT cst, enum machine_mode mode)
3214 static htab_t costs;
3215 struct mbc_entry **cached, act;
3216 rtx seq;
3217 unsigned cost;
3219 if (!costs)
3220 costs = htab_create (100, mbc_entry_hash, mbc_entry_eq, free);
3222 act.mode = mode;
3223 act.cst = cst;
3224 cached = (struct mbc_entry **) htab_find_slot (costs, &act, INSERT);
3225 if (*cached)
3226 return (*cached)->cost;
3228 *cached = xmalloc (sizeof (struct mbc_entry));
3229 (*cached)->mode = mode;
3230 (*cached)->cst = cst;
3232 start_sequence ();
3233 expand_mult (mode, gen_raw_REG (mode, LAST_VIRTUAL_REGISTER + 1),
3234 gen_int_mode (cst, mode), NULL_RTX, 0);
3235 seq = get_insns ();
3236 end_sequence ();
3238 cost = seq_cost (seq);
3240 if (dump_file && (dump_flags & TDF_DETAILS))
3241 fprintf (dump_file, "Multiplication by %d in %s costs %d\n",
3242 (int) cst, GET_MODE_NAME (mode), cost);
3244 (*cached)->cost = cost;
3246 return cost;
3249 /* Returns true if multiplying by RATIO is allowed in address. */
3251 bool
3252 multiplier_allowed_in_address_p (HOST_WIDE_INT ratio)
3254 #define MAX_RATIO 128
3255 static sbitmap valid_mult;
3257 if (!valid_mult)
3259 rtx reg1 = gen_raw_REG (Pmode, LAST_VIRTUAL_REGISTER + 1);
3260 rtx addr;
3261 HOST_WIDE_INT i;
3263 valid_mult = sbitmap_alloc (2 * MAX_RATIO + 1);
3264 sbitmap_zero (valid_mult);
3265 addr = gen_rtx_fmt_ee (MULT, Pmode, reg1, NULL_RTX);
3266 for (i = -MAX_RATIO; i <= MAX_RATIO; i++)
3268 XEXP (addr, 1) = gen_int_mode (i, Pmode);
3269 if (memory_address_p (Pmode, addr))
3270 SET_BIT (valid_mult, i + MAX_RATIO);
3273 if (dump_file && (dump_flags & TDF_DETAILS))
3275 fprintf (dump_file, " allowed multipliers:");
3276 for (i = -MAX_RATIO; i <= MAX_RATIO; i++)
3277 if (TEST_BIT (valid_mult, i + MAX_RATIO))
3278 fprintf (dump_file, " %d", (int) i);
3279 fprintf (dump_file, "\n");
3280 fprintf (dump_file, "\n");
3284 if (ratio > MAX_RATIO || ratio < -MAX_RATIO)
3285 return false;
3287 return TEST_BIT (valid_mult, ratio + MAX_RATIO);
3290 /* Returns cost of address in shape symbol + var + OFFSET + RATIO * index.
3291 If SYMBOL_PRESENT is false, symbol is omitted. If VAR_PRESENT is false,
3292 variable is omitted. The created memory accesses MODE.
3294 TODO -- there must be some better way. This all is quite crude. */
3296 static unsigned
3297 get_address_cost (bool symbol_present, bool var_present,
3298 unsigned HOST_WIDE_INT offset, HOST_WIDE_INT ratio)
3300 static bool initialized = false;
3301 static HOST_WIDE_INT rat, off;
3302 static HOST_WIDE_INT min_offset, max_offset;
3303 static unsigned costs[2][2][2][2];
3304 unsigned cost, acost;
3305 rtx seq, addr, base;
3306 bool offset_p, ratio_p;
3307 rtx reg1;
3308 HOST_WIDE_INT s_offset;
3309 unsigned HOST_WIDE_INT mask;
3310 unsigned bits;
3312 if (!initialized)
3314 HOST_WIDE_INT i;
3315 initialized = true;
3317 reg1 = gen_raw_REG (Pmode, LAST_VIRTUAL_REGISTER + 1);
3319 addr = gen_rtx_fmt_ee (PLUS, Pmode, reg1, NULL_RTX);
3320 for (i = 1; i <= 1 << 20; i <<= 1)
3322 XEXP (addr, 1) = gen_int_mode (i, Pmode);
3323 if (!memory_address_p (Pmode, addr))
3324 break;
3326 max_offset = i >> 1;
3327 off = max_offset;
3329 for (i = 1; i <= 1 << 20; i <<= 1)
3331 XEXP (addr, 1) = gen_int_mode (-i, Pmode);
3332 if (!memory_address_p (Pmode, addr))
3333 break;
3335 min_offset = -(i >> 1);
3337 if (dump_file && (dump_flags & TDF_DETAILS))
3339 fprintf (dump_file, "get_address_cost:\n");
3340 fprintf (dump_file, " min offset %d\n", (int) min_offset);
3341 fprintf (dump_file, " max offset %d\n", (int) max_offset);
3344 rat = 1;
3345 for (i = 2; i <= MAX_RATIO; i++)
3346 if (multiplier_allowed_in_address_p (i))
3348 rat = i;
3349 break;
3353 bits = GET_MODE_BITSIZE (Pmode);
3354 mask = ~(~(unsigned HOST_WIDE_INT) 0 << (bits - 1) << 1);
3355 offset &= mask;
3356 if ((offset >> (bits - 1) & 1))
3357 offset |= ~mask;
3358 s_offset = offset;
3360 cost = 0;
3361 offset_p = (s_offset != 0
3362 && min_offset <= s_offset && s_offset <= max_offset);
3363 ratio_p = (ratio != 1
3364 && multiplier_allowed_in_address_p (ratio));
3366 if (ratio != 1 && !ratio_p)
3367 cost += multiply_by_cost (ratio, Pmode);
3369 if (s_offset && !offset_p && !symbol_present)
3371 cost += add_cost (Pmode);
3372 var_present = true;
3375 acost = costs[symbol_present][var_present][offset_p][ratio_p];
3376 if (!acost)
3378 acost = 0;
3380 addr = gen_raw_REG (Pmode, LAST_VIRTUAL_REGISTER + 1);
3381 reg1 = gen_raw_REG (Pmode, LAST_VIRTUAL_REGISTER + 2);
3382 if (ratio_p)
3383 addr = gen_rtx_fmt_ee (MULT, Pmode, addr, gen_int_mode (rat, Pmode));
3385 if (var_present)
3386 addr = gen_rtx_fmt_ee (PLUS, Pmode, addr, reg1);
3388 if (symbol_present)
3390 base = gen_rtx_SYMBOL_REF (Pmode, ggc_strdup (""));
3391 if (offset_p)
3392 base = gen_rtx_fmt_e (CONST, Pmode,
3393 gen_rtx_fmt_ee (PLUS, Pmode,
3394 base,
3395 gen_int_mode (off, Pmode)));
3397 else if (offset_p)
3398 base = gen_int_mode (off, Pmode);
3399 else
3400 base = NULL_RTX;
3402 if (base)
3403 addr = gen_rtx_fmt_ee (PLUS, Pmode, addr, base);
3405 start_sequence ();
3406 addr = memory_address (Pmode, addr);
3407 seq = get_insns ();
3408 end_sequence ();
3410 acost = seq_cost (seq);
3411 acost += address_cost (addr, Pmode);
3413 if (!acost)
3414 acost = 1;
3415 costs[symbol_present][var_present][offset_p][ratio_p] = acost;
3418 return cost + acost;
3421 /* Estimates cost of forcing expression EXPR into a variable. */
3423 unsigned
3424 force_expr_to_var_cost (tree expr)
3426 static bool costs_initialized = false;
3427 static unsigned integer_cost;
3428 static unsigned symbol_cost;
3429 static unsigned address_cost;
3430 tree op0, op1;
3431 unsigned cost0, cost1, cost;
3432 enum machine_mode mode;
3434 if (!costs_initialized)
3436 tree var = create_tmp_var_raw (integer_type_node, "test_var");
3437 rtx x = gen_rtx_MEM (DECL_MODE (var),
3438 gen_rtx_SYMBOL_REF (Pmode, "test_var"));
3439 tree addr;
3440 tree type = build_pointer_type (integer_type_node);
3442 integer_cost = computation_cost (build_int_cst_type (integer_type_node,
3443 2000));
3445 SET_DECL_RTL (var, x);
3446 TREE_STATIC (var) = 1;
3447 addr = build1 (ADDR_EXPR, type, var);
3448 symbol_cost = computation_cost (addr) + 1;
3450 address_cost
3451 = computation_cost (build2 (PLUS_EXPR, type,
3452 addr,
3453 build_int_cst_type (type, 2000))) + 1;
3454 if (dump_file && (dump_flags & TDF_DETAILS))
3456 fprintf (dump_file, "force_expr_to_var_cost:\n");
3457 fprintf (dump_file, " integer %d\n", (int) integer_cost);
3458 fprintf (dump_file, " symbol %d\n", (int) symbol_cost);
3459 fprintf (dump_file, " address %d\n", (int) address_cost);
3460 fprintf (dump_file, " other %d\n", (int) target_spill_cost);
3461 fprintf (dump_file, "\n");
3464 costs_initialized = true;
3467 STRIP_NOPS (expr);
3469 if (SSA_VAR_P (expr))
3470 return 0;
3472 if (TREE_INVARIANT (expr))
3474 if (TREE_CODE (expr) == INTEGER_CST)
3475 return integer_cost;
3477 if (TREE_CODE (expr) == ADDR_EXPR)
3479 tree obj = TREE_OPERAND (expr, 0);
3481 if (TREE_CODE (obj) == VAR_DECL
3482 || TREE_CODE (obj) == PARM_DECL
3483 || TREE_CODE (obj) == RESULT_DECL)
3484 return symbol_cost;
3487 return address_cost;
3490 switch (TREE_CODE (expr))
3492 case PLUS_EXPR:
3493 case MINUS_EXPR:
3494 case MULT_EXPR:
3495 op0 = TREE_OPERAND (expr, 0);
3496 op1 = TREE_OPERAND (expr, 1);
3497 STRIP_NOPS (op0);
3498 STRIP_NOPS (op1);
3500 if (is_gimple_val (op0))
3501 cost0 = 0;
3502 else
3503 cost0 = force_expr_to_var_cost (op0);
3505 if (is_gimple_val (op1))
3506 cost1 = 0;
3507 else
3508 cost1 = force_expr_to_var_cost (op1);
3510 break;
3512 default:
3513 /* Just an arbitrary value, FIXME. */
3514 return target_spill_cost;
3517 mode = TYPE_MODE (TREE_TYPE (expr));
3518 switch (TREE_CODE (expr))
3520 case PLUS_EXPR:
3521 case MINUS_EXPR:
3522 cost = add_cost (mode);
3523 break;
3525 case MULT_EXPR:
3526 if (cst_and_fits_in_hwi (op0))
3527 cost = multiply_by_cost (int_cst_value (op0), mode);
3528 else if (cst_and_fits_in_hwi (op1))
3529 cost = multiply_by_cost (int_cst_value (op1), mode);
3530 else
3531 return target_spill_cost;
3532 break;
3534 default:
3535 gcc_unreachable ();
3538 cost += cost0;
3539 cost += cost1;
3541 /* Bound the cost by target_spill_cost. The parts of complicated
3542 computations often are either loop invariant or at least can
3543 be shared between several iv uses, so letting this grow without
3544 limits would not give reasonable results. */
3545 return cost < target_spill_cost ? cost : target_spill_cost;
3548 /* Estimates cost of forcing EXPR into a variable. DEPENDS_ON is a set of the
3549 invariants the computation depends on. */
3551 static unsigned
3552 force_var_cost (struct ivopts_data *data,
3553 tree expr, bitmap *depends_on)
3555 if (depends_on)
3557 fd_ivopts_data = data;
3558 walk_tree (&expr, find_depends, depends_on, NULL);
3561 return force_expr_to_var_cost (expr);
3564 /* Estimates cost of expressing address ADDR as var + symbol + offset. The
3565 value of offset is added to OFFSET, SYMBOL_PRESENT and VAR_PRESENT are set
3566 to false if the corresponding part is missing. DEPENDS_ON is a set of the
3567 invariants the computation depends on. */
3569 static unsigned
3570 split_address_cost (struct ivopts_data *data,
3571 tree addr, bool *symbol_present, bool *var_present,
3572 unsigned HOST_WIDE_INT *offset, bitmap *depends_on)
3574 tree core;
3575 HOST_WIDE_INT bitsize;
3576 HOST_WIDE_INT bitpos;
3577 tree toffset;
3578 enum machine_mode mode;
3579 int unsignedp, volatilep;
3581 core = get_inner_reference (addr, &bitsize, &bitpos, &toffset, &mode,
3582 &unsignedp, &volatilep, false);
3584 if (toffset != 0
3585 || bitpos % BITS_PER_UNIT != 0
3586 || TREE_CODE (core) != VAR_DECL)
3588 *symbol_present = false;
3589 *var_present = true;
3590 fd_ivopts_data = data;
3591 walk_tree (&addr, find_depends, depends_on, NULL);
3592 return target_spill_cost;
3595 *offset += bitpos / BITS_PER_UNIT;
3596 if (TREE_STATIC (core)
3597 || DECL_EXTERNAL (core))
3599 *symbol_present = true;
3600 *var_present = false;
3601 return 0;
3604 *symbol_present = false;
3605 *var_present = true;
3606 return 0;
3609 /* Estimates cost of expressing difference of addresses E1 - E2 as
3610 var + symbol + offset. The value of offset is added to OFFSET,
3611 SYMBOL_PRESENT and VAR_PRESENT are set to false if the corresponding
3612 part is missing. DEPENDS_ON is a set of the invariants the computation
3613 depends on. */
3615 static unsigned
3616 ptr_difference_cost (struct ivopts_data *data,
3617 tree e1, tree e2, bool *symbol_present, bool *var_present,
3618 unsigned HOST_WIDE_INT *offset, bitmap *depends_on)
3620 HOST_WIDE_INT diff = 0;
3621 unsigned cost;
3623 gcc_assert (TREE_CODE (e1) == ADDR_EXPR);
3625 if (ptr_difference_const (e1, e2, &diff))
3627 *offset += diff;
3628 *symbol_present = false;
3629 *var_present = false;
3630 return 0;
3633 if (e2 == integer_zero_node)
3634 return split_address_cost (data, TREE_OPERAND (e1, 0),
3635 symbol_present, var_present, offset, depends_on);
3637 *symbol_present = false;
3638 *var_present = true;
3640 cost = force_var_cost (data, e1, depends_on);
3641 cost += force_var_cost (data, e2, depends_on);
3642 cost += add_cost (Pmode);
3644 return cost;
3647 /* Estimates cost of expressing difference E1 - E2 as
3648 var + symbol + offset. The value of offset is added to OFFSET,
3649 SYMBOL_PRESENT and VAR_PRESENT are set to false if the corresponding
3650 part is missing. DEPENDS_ON is a set of the invariants the computation
3651 depends on. */
3653 static unsigned
3654 difference_cost (struct ivopts_data *data,
3655 tree e1, tree e2, bool *symbol_present, bool *var_present,
3656 unsigned HOST_WIDE_INT *offset, bitmap *depends_on)
3658 unsigned cost;
3659 enum machine_mode mode = TYPE_MODE (TREE_TYPE (e1));
3660 unsigned HOST_WIDE_INT off1, off2;
3662 e1 = strip_offset (e1, &off1);
3663 e2 = strip_offset (e2, &off2);
3664 *offset += off1 - off2;
3666 STRIP_NOPS (e1);
3667 STRIP_NOPS (e2);
3669 if (TREE_CODE (e1) == ADDR_EXPR)
3670 return ptr_difference_cost (data, e1, e2, symbol_present, var_present, offset,
3671 depends_on);
3672 *symbol_present = false;
3674 if (operand_equal_p (e1, e2, 0))
3676 *var_present = false;
3677 return 0;
3679 *var_present = true;
3680 if (zero_p (e2))
3681 return force_var_cost (data, e1, depends_on);
3683 if (zero_p (e1))
3685 cost = force_var_cost (data, e2, depends_on);
3686 cost += multiply_by_cost (-1, mode);
3688 return cost;
3691 cost = force_var_cost (data, e1, depends_on);
3692 cost += force_var_cost (data, e2, depends_on);
3693 cost += add_cost (mode);
3695 return cost;
3698 /* Determines the cost of the computation by that USE is expressed
3699 from induction variable CAND. If ADDRESS_P is true, we just need
3700 to create an address from it, otherwise we want to get it into
3701 register. A set of invariants we depend on is stored in
3702 DEPENDS_ON. AT is the statement at that the value is computed. */
3704 static unsigned
3705 get_computation_cost_at (struct ivopts_data *data,
3706 struct iv_use *use, struct iv_cand *cand,
3707 bool address_p, bitmap *depends_on, tree at)
3709 tree ubase = use->iv->base, ustep = use->iv->step;
3710 tree cbase, cstep;
3711 tree utype = TREE_TYPE (ubase), ctype;
3712 unsigned HOST_WIDE_INT ustepi, cstepi, offset = 0;
3713 HOST_WIDE_INT ratio, aratio;
3714 bool var_present, symbol_present;
3715 unsigned cost = 0, n_sums;
3717 *depends_on = NULL;
3719 /* Only consider real candidates. */
3720 if (!cand->iv)
3721 return INFTY;
3723 cbase = cand->iv->base;
3724 cstep = cand->iv->step;
3725 ctype = TREE_TYPE (cbase);
3727 if (TYPE_PRECISION (utype) > TYPE_PRECISION (ctype))
3729 /* We do not have a precision to express the values of use. */
3730 return INFTY;
3733 if (address_p)
3735 /* Do not try to express address of an object with computation based
3736 on address of a different object. This may cause problems in rtl
3737 level alias analysis (that does not expect this to be happening,
3738 as this is illegal in C), and would be unlikely to be useful
3739 anyway. */
3740 if (use->iv->base_object
3741 && cand->iv->base_object
3742 && !operand_equal_p (use->iv->base_object, cand->iv->base_object, 0))
3743 return INFTY;
3746 if (TYPE_PRECISION (utype) != TYPE_PRECISION (ctype))
3748 /* TODO -- add direct handling of this case. */
3749 goto fallback;
3752 /* CSTEPI is removed from the offset in case statement is after the
3753 increment. If the step is not constant, we use zero instead.
3754 This is a bit imprecise (there is the extra addition), but
3755 redundancy elimination is likely to transform the code so that
3756 it uses value of the variable before increment anyway,
3757 so it is not that much unrealistic. */
3758 if (cst_and_fits_in_hwi (cstep))
3759 cstepi = int_cst_value (cstep);
3760 else
3761 cstepi = 0;
3763 if (cst_and_fits_in_hwi (ustep)
3764 && cst_and_fits_in_hwi (cstep))
3766 ustepi = int_cst_value (ustep);
3768 if (!divide (TYPE_PRECISION (utype), ustepi, cstepi, &ratio))
3769 return INFTY;
3771 else
3773 tree rat;
3775 rat = constant_multiple_of (utype, ustep, cstep);
3777 if (!rat)
3778 return INFTY;
3780 if (cst_and_fits_in_hwi (rat))
3781 ratio = int_cst_value (rat);
3782 else if (integer_onep (rat))
3783 ratio = 1;
3784 else if (integer_all_onesp (rat))
3785 ratio = -1;
3786 else
3787 return INFTY;
3790 /* use = ubase + ratio * (var - cbase). If either cbase is a constant
3791 or ratio == 1, it is better to handle this like
3793 ubase - ratio * cbase + ratio * var
3795 (also holds in the case ratio == -1, TODO. */
3797 if (cst_and_fits_in_hwi (cbase))
3799 offset = - ratio * int_cst_value (cbase);
3800 cost += difference_cost (data,
3801 ubase, integer_zero_node,
3802 &symbol_present, &var_present, &offset,
3803 depends_on);
3805 else if (ratio == 1)
3807 cost += difference_cost (data,
3808 ubase, cbase,
3809 &symbol_present, &var_present, &offset,
3810 depends_on);
3812 else
3814 cost += force_var_cost (data, cbase, depends_on);
3815 cost += add_cost (TYPE_MODE (ctype));
3816 cost += difference_cost (data,
3817 ubase, integer_zero_node,
3818 &symbol_present, &var_present, &offset,
3819 depends_on);
3822 /* If we are after the increment, the value of the candidate is higher by
3823 one iteration. */
3824 if (stmt_after_increment (data->current_loop, cand, at))
3825 offset -= ratio * cstepi;
3827 /* Now the computation is in shape symbol + var1 + const + ratio * var2.
3828 (symbol/var/const parts may be omitted). If we are looking for an address,
3829 find the cost of addressing this. */
3830 if (address_p)
3831 return cost + get_address_cost (symbol_present, var_present, offset, ratio);
3833 /* Otherwise estimate the costs for computing the expression. */
3834 aratio = ratio > 0 ? ratio : -ratio;
3835 if (!symbol_present && !var_present && !offset)
3837 if (ratio != 1)
3838 cost += multiply_by_cost (ratio, TYPE_MODE (ctype));
3840 return cost;
3843 if (aratio != 1)
3844 cost += multiply_by_cost (aratio, TYPE_MODE (ctype));
3846 n_sums = 1;
3847 if (var_present
3848 /* Symbol + offset should be compile-time computable. */
3849 && (symbol_present || offset))
3850 n_sums++;
3852 return cost + n_sums * add_cost (TYPE_MODE (ctype));
3854 fallback:
3856 /* Just get the expression, expand it and measure the cost. */
3857 tree comp = get_computation_at (data->current_loop, use, cand, at);
3859 if (!comp)
3860 return INFTY;
3862 if (address_p)
3863 comp = build1 (INDIRECT_REF, TREE_TYPE (TREE_TYPE (comp)), comp);
3865 return computation_cost (comp);
3869 /* Determines the cost of the computation by that USE is expressed
3870 from induction variable CAND. If ADDRESS_P is true, we just need
3871 to create an address from it, otherwise we want to get it into
3872 register. A set of invariants we depend on is stored in
3873 DEPENDS_ON. */
3875 static unsigned
3876 get_computation_cost (struct ivopts_data *data,
3877 struct iv_use *use, struct iv_cand *cand,
3878 bool address_p, bitmap *depends_on)
3880 return get_computation_cost_at (data,
3881 use, cand, address_p, depends_on, use->stmt);
3884 /* Determines cost of basing replacement of USE on CAND in a generic
3885 expression. */
3887 static bool
3888 determine_use_iv_cost_generic (struct ivopts_data *data,
3889 struct iv_use *use, struct iv_cand *cand)
3891 bitmap depends_on;
3892 unsigned cost;
3894 /* The simple case first -- if we need to express value of the preserved
3895 original biv, the cost is 0. This also prevents us from counting the
3896 cost of increment twice -- once at this use and once in the cost of
3897 the candidate. */
3898 if (cand->pos == IP_ORIGINAL
3899 && cand->incremented_at == use->stmt)
3901 set_use_iv_cost (data, use, cand, 0, NULL, NULL_TREE);
3902 return true;
3905 cost = get_computation_cost (data, use, cand, false, &depends_on);
3906 set_use_iv_cost (data, use, cand, cost, depends_on, NULL_TREE);
3908 return cost != INFTY;
3911 /* Determines cost of basing replacement of USE on CAND in an address. */
3913 static bool
3914 determine_use_iv_cost_address (struct ivopts_data *data,
3915 struct iv_use *use, struct iv_cand *cand)
3917 bitmap depends_on;
3918 unsigned cost = get_computation_cost (data, use, cand, true, &depends_on);
3920 set_use_iv_cost (data, use, cand, cost, depends_on, NULL_TREE);
3922 return cost != INFTY;
3925 /* Computes value of induction variable IV in iteration NITER. */
3927 static tree
3928 iv_value (struct iv *iv, tree niter)
3930 tree val;
3931 tree type = TREE_TYPE (iv->base);
3933 niter = fold_convert (type, niter);
3934 val = fold_build2 (MULT_EXPR, type, iv->step, niter);
3936 return fold_build2 (PLUS_EXPR, type, iv->base, val);
3939 /* Computes value of candidate CAND at position AT in iteration NITER. */
3941 static tree
3942 cand_value_at (struct loop *loop, struct iv_cand *cand, tree at, tree niter)
3944 tree val = iv_value (cand->iv, niter);
3945 tree type = TREE_TYPE (cand->iv->base);
3947 if (stmt_after_increment (loop, cand, at))
3948 val = fold_build2 (PLUS_EXPR, type, val, cand->iv->step);
3950 return val;
3953 /* Returns period of induction variable iv. */
3955 static tree
3956 iv_period (struct iv *iv)
3958 tree step = iv->step, period, type;
3959 tree pow2div;
3961 gcc_assert (step && TREE_CODE (step) == INTEGER_CST);
3963 /* Period of the iv is gcd (step, type range). Since type range is power
3964 of two, it suffices to determine the maximum power of two that divides
3965 step. */
3966 pow2div = num_ending_zeros (step);
3967 type = unsigned_type_for (TREE_TYPE (step));
3969 period = build_low_bits_mask (type,
3970 (TYPE_PRECISION (type)
3971 - tree_low_cst (pow2div, 1)));
3973 return period;
3976 /* Returns the comparison operator used when eliminating the iv USE. */
3978 static enum tree_code
3979 iv_elimination_compare (struct ivopts_data *data, struct iv_use *use)
3981 struct loop *loop = data->current_loop;
3982 basic_block ex_bb;
3983 edge exit;
3985 ex_bb = bb_for_stmt (use->stmt);
3986 exit = EDGE_SUCC (ex_bb, 0);
3987 if (flow_bb_inside_loop_p (loop, exit->dest))
3988 exit = EDGE_SUCC (ex_bb, 1);
3990 return (exit->flags & EDGE_TRUE_VALUE ? EQ_EXPR : NE_EXPR);
3993 /* Check whether it is possible to express the condition in USE by comparison
3994 of candidate CAND. If so, store the value compared with to BOUND. */
3996 static bool
3997 may_eliminate_iv (struct ivopts_data *data,
3998 struct iv_use *use, struct iv_cand *cand, tree *bound)
4000 basic_block ex_bb;
4001 edge exit;
4002 struct tree_niter_desc *niter;
4003 tree nit, nit_type;
4004 tree wider_type, period, per_type;
4005 struct loop *loop = data->current_loop;
4007 if (TREE_CODE (cand->iv->step) != INTEGER_CST)
4008 return false;
4010 /* For now works only for exits that dominate the loop latch. TODO -- extend
4011 for other conditions inside loop body. */
4012 ex_bb = bb_for_stmt (use->stmt);
4013 if (use->stmt != last_stmt (ex_bb)
4014 || TREE_CODE (use->stmt) != COND_EXPR)
4015 return false;
4016 if (!dominated_by_p (CDI_DOMINATORS, loop->latch, ex_bb))
4017 return false;
4019 exit = EDGE_SUCC (ex_bb, 0);
4020 if (flow_bb_inside_loop_p (loop, exit->dest))
4021 exit = EDGE_SUCC (ex_bb, 1);
4022 if (flow_bb_inside_loop_p (loop, exit->dest))
4023 return false;
4025 niter = niter_for_exit (data, exit);
4026 if (!niter
4027 || !zero_p (niter->may_be_zero))
4028 return false;
4030 nit = niter->niter;
4031 nit_type = TREE_TYPE (nit);
4033 /* Determine whether we may use the variable to test whether niter iterations
4034 elapsed. This is the case iff the period of the induction variable is
4035 greater than the number of iterations. */
4036 period = iv_period (cand->iv);
4037 if (!period)
4038 return false;
4039 per_type = TREE_TYPE (period);
4041 wider_type = TREE_TYPE (period);
4042 if (TYPE_PRECISION (nit_type) < TYPE_PRECISION (per_type))
4043 wider_type = per_type;
4044 else
4045 wider_type = nit_type;
4047 if (!integer_nonzerop (fold_build2 (GE_EXPR, boolean_type_node,
4048 fold_convert (wider_type, period),
4049 fold_convert (wider_type, nit))))
4050 return false;
4052 *bound = cand_value_at (loop, cand, use->stmt, nit);
4053 return true;
4056 /* Determines cost of basing replacement of USE on CAND in a condition. */
4058 static bool
4059 determine_use_iv_cost_condition (struct ivopts_data *data,
4060 struct iv_use *use, struct iv_cand *cand)
4062 tree bound = NULL_TREE, op, cond;
4063 bitmap depends_on = NULL;
4064 unsigned cost;
4066 /* Only consider real candidates. */
4067 if (!cand->iv)
4069 set_use_iv_cost (data, use, cand, INFTY, NULL, NULL_TREE);
4070 return false;
4073 if (may_eliminate_iv (data, use, cand, &bound))
4075 cost = force_var_cost (data, bound, &depends_on);
4077 set_use_iv_cost (data, use, cand, cost, depends_on, bound);
4078 return cost != INFTY;
4081 /* The induction variable elimination failed; just express the original
4082 giv. If it is compared with an invariant, note that we cannot get
4083 rid of it. */
4084 cost = get_computation_cost (data, use, cand, false, &depends_on);
4086 cond = *use->op_p;
4087 if (TREE_CODE (cond) != SSA_NAME)
4089 op = TREE_OPERAND (cond, 0);
4090 if (TREE_CODE (op) == SSA_NAME && !zero_p (get_iv (data, op)->step))
4091 op = TREE_OPERAND (cond, 1);
4092 if (TREE_CODE (op) == SSA_NAME)
4094 op = get_iv (data, op)->base;
4095 fd_ivopts_data = data;
4096 walk_tree (&op, find_depends, &depends_on, NULL);
4100 set_use_iv_cost (data, use, cand, cost, depends_on, NULL);
4101 return cost != INFTY;
4104 /* Checks whether it is possible to replace the final value of USE by
4105 a direct computation. If so, the formula is stored to *VALUE. */
4107 static bool
4108 may_replace_final_value (struct ivopts_data *data, struct iv_use *use,
4109 tree *value)
4111 struct loop *loop = data->current_loop;
4112 edge exit;
4113 struct tree_niter_desc *niter;
4115 exit = single_dom_exit (loop);
4116 if (!exit)
4117 return false;
4119 gcc_assert (dominated_by_p (CDI_DOMINATORS, exit->src,
4120 bb_for_stmt (use->stmt)));
4122 niter = niter_for_single_dom_exit (data);
4123 if (!niter
4124 || !zero_p (niter->may_be_zero))
4125 return false;
4127 *value = iv_value (use->iv, niter->niter);
4129 return true;
4132 /* Determines cost of replacing final value of USE using CAND. */
4134 static bool
4135 determine_use_iv_cost_outer (struct ivopts_data *data,
4136 struct iv_use *use, struct iv_cand *cand)
4138 bitmap depends_on;
4139 unsigned cost;
4140 edge exit;
4141 tree value = NULL_TREE;
4142 struct loop *loop = data->current_loop;
4144 /* The simple case first -- if we need to express value of the preserved
4145 original biv, the cost is 0. This also prevents us from counting the
4146 cost of increment twice -- once at this use and once in the cost of
4147 the candidate. */
4148 if (cand->pos == IP_ORIGINAL
4149 && cand->incremented_at == use->stmt)
4151 set_use_iv_cost (data, use, cand, 0, NULL, NULL_TREE);
4152 return true;
4155 if (!cand->iv)
4157 if (!may_replace_final_value (data, use, &value))
4159 set_use_iv_cost (data, use, cand, INFTY, NULL, NULL_TREE);
4160 return false;
4163 depends_on = NULL;
4164 cost = force_var_cost (data, value, &depends_on);
4166 cost /= AVG_LOOP_NITER (loop);
4168 set_use_iv_cost (data, use, cand, cost, depends_on, value);
4169 return cost != INFTY;
4172 exit = single_dom_exit (loop);
4173 if (exit)
4175 /* If there is just a single exit, we may use value of the candidate
4176 after we take it to determine the value of use. */
4177 cost = get_computation_cost_at (data, use, cand, false, &depends_on,
4178 last_stmt (exit->src));
4179 if (cost != INFTY)
4180 cost /= AVG_LOOP_NITER (loop);
4182 else
4184 /* Otherwise we just need to compute the iv. */
4185 cost = get_computation_cost (data, use, cand, false, &depends_on);
4188 set_use_iv_cost (data, use, cand, cost, depends_on, NULL_TREE);
4190 return cost != INFTY;
4193 /* Determines cost of basing replacement of USE on CAND. Returns false
4194 if USE cannot be based on CAND. */
4196 static bool
4197 determine_use_iv_cost (struct ivopts_data *data,
4198 struct iv_use *use, struct iv_cand *cand)
4200 switch (use->type)
4202 case USE_NONLINEAR_EXPR:
4203 return determine_use_iv_cost_generic (data, use, cand);
4205 case USE_OUTER:
4206 return determine_use_iv_cost_outer (data, use, cand);
4208 case USE_ADDRESS:
4209 return determine_use_iv_cost_address (data, use, cand);
4211 case USE_COMPARE:
4212 return determine_use_iv_cost_condition (data, use, cand);
4214 default:
4215 gcc_unreachable ();
4219 /* Determines costs of basing the use of the iv on an iv candidate. */
4221 static void
4222 determine_use_iv_costs (struct ivopts_data *data)
4224 unsigned i, j;
4225 struct iv_use *use;
4226 struct iv_cand *cand;
4227 bitmap to_clear = BITMAP_ALLOC (NULL);
4229 alloc_use_cost_map (data);
4231 for (i = 0; i < n_iv_uses (data); i++)
4233 use = iv_use (data, i);
4235 if (data->consider_all_candidates)
4237 for (j = 0; j < n_iv_cands (data); j++)
4239 cand = iv_cand (data, j);
4240 determine_use_iv_cost (data, use, cand);
4243 else
4245 bitmap_iterator bi;
4247 EXECUTE_IF_SET_IN_BITMAP (use->related_cands, 0, j, bi)
4249 cand = iv_cand (data, j);
4250 if (!determine_use_iv_cost (data, use, cand))
4251 bitmap_set_bit (to_clear, j);
4254 /* Remove the candidates for that the cost is infinite from
4255 the list of related candidates. */
4256 bitmap_and_compl_into (use->related_cands, to_clear);
4257 bitmap_clear (to_clear);
4261 BITMAP_FREE (to_clear);
4263 if (dump_file && (dump_flags & TDF_DETAILS))
4265 fprintf (dump_file, "Use-candidate costs:\n");
4267 for (i = 0; i < n_iv_uses (data); i++)
4269 use = iv_use (data, i);
4271 fprintf (dump_file, "Use %d:\n", i);
4272 fprintf (dump_file, " cand\tcost\tdepends on\n");
4273 for (j = 0; j < use->n_map_members; j++)
4275 if (!use->cost_map[j].cand
4276 || use->cost_map[j].cost == INFTY)
4277 continue;
4279 fprintf (dump_file, " %d\t%d\t",
4280 use->cost_map[j].cand->id,
4281 use->cost_map[j].cost);
4282 if (use->cost_map[j].depends_on)
4283 bitmap_print (dump_file,
4284 use->cost_map[j].depends_on, "","");
4285 fprintf (dump_file, "\n");
4288 fprintf (dump_file, "\n");
4290 fprintf (dump_file, "\n");
4294 /* Determines cost of the candidate CAND. */
4296 static void
4297 determine_iv_cost (struct ivopts_data *data, struct iv_cand *cand)
4299 unsigned cost_base, cost_step;
4300 tree base;
4302 if (!cand->iv)
4304 cand->cost = 0;
4305 return;
4308 /* There are two costs associated with the candidate -- its increment
4309 and its initialization. The second is almost negligible for any loop
4310 that rolls enough, so we take it just very little into account. */
4312 base = cand->iv->base;
4313 cost_base = force_var_cost (data, base, NULL);
4314 cost_step = add_cost (TYPE_MODE (TREE_TYPE (base)));
4316 cand->cost = cost_step + cost_base / AVG_LOOP_NITER (current_loop);
4318 /* Prefer the original iv unless we may gain something by replacing it;
4319 this is not really relevant for artificial ivs created by other
4320 passes. */
4321 if (cand->pos == IP_ORIGINAL
4322 && !DECL_ARTIFICIAL (SSA_NAME_VAR (cand->var_before)))
4323 cand->cost--;
4325 /* Prefer not to insert statements into latch unless there are some
4326 already (so that we do not create unnecessary jumps). */
4327 if (cand->pos == IP_END
4328 && empty_block_p (ip_end_pos (data->current_loop)))
4329 cand->cost++;
4332 /* Determines costs of computation of the candidates. */
4334 static void
4335 determine_iv_costs (struct ivopts_data *data)
4337 unsigned i;
4339 if (dump_file && (dump_flags & TDF_DETAILS))
4341 fprintf (dump_file, "Candidate costs:\n");
4342 fprintf (dump_file, " cand\tcost\n");
4345 for (i = 0; i < n_iv_cands (data); i++)
4347 struct iv_cand *cand = iv_cand (data, i);
4349 determine_iv_cost (data, cand);
4351 if (dump_file && (dump_flags & TDF_DETAILS))
4352 fprintf (dump_file, " %d\t%d\n", i, cand->cost);
4355 if (dump_file && (dump_flags & TDF_DETAILS))
4356 fprintf (dump_file, "\n");
4359 /* Calculates cost for having SIZE induction variables. */
4361 static unsigned
4362 ivopts_global_cost_for_size (struct ivopts_data *data, unsigned size)
4364 return global_cost_for_size (size,
4365 loop_data (data->current_loop)->regs_used,
4366 n_iv_uses (data));
4369 /* For each size of the induction variable set determine the penalty. */
4371 static void
4372 determine_set_costs (struct ivopts_data *data)
4374 unsigned j, n;
4375 tree phi, op;
4376 struct loop *loop = data->current_loop;
4377 bitmap_iterator bi;
4379 /* We use the following model (definitely improvable, especially the
4380 cost function -- TODO):
4382 We estimate the number of registers available (using MD data), name it A.
4384 We estimate the number of registers used by the loop, name it U. This
4385 number is obtained as the number of loop phi nodes (not counting virtual
4386 registers and bivs) + the number of variables from outside of the loop.
4388 We set a reserve R (free regs that are used for temporary computations,
4389 etc.). For now the reserve is a constant 3.
4391 Let I be the number of induction variables.
4393 -- if U + I + R <= A, the cost is I * SMALL_COST (just not to encourage
4394 make a lot of ivs without a reason).
4395 -- if A - R < U + I <= A, the cost is I * PRES_COST
4396 -- if U + I > A, the cost is I * PRES_COST and
4397 number of uses * SPILL_COST * (U + I - A) / (U + I) is added. */
4399 if (dump_file && (dump_flags & TDF_DETAILS))
4401 fprintf (dump_file, "Global costs:\n");
4402 fprintf (dump_file, " target_avail_regs %d\n", target_avail_regs);
4403 fprintf (dump_file, " target_small_cost %d\n", target_small_cost);
4404 fprintf (dump_file, " target_pres_cost %d\n", target_pres_cost);
4405 fprintf (dump_file, " target_spill_cost %d\n", target_spill_cost);
4408 n = 0;
4409 for (phi = phi_nodes (loop->header); phi; phi = PHI_CHAIN (phi))
4411 op = PHI_RESULT (phi);
4413 if (!is_gimple_reg (op))
4414 continue;
4416 if (get_iv (data, op))
4417 continue;
4419 n++;
4422 EXECUTE_IF_SET_IN_BITMAP (data->relevant, 0, j, bi)
4424 struct version_info *info = ver_info (data, j);
4426 if (info->inv_id && info->has_nonlin_use)
4427 n++;
4430 loop_data (loop)->regs_used = n;
4431 if (dump_file && (dump_flags & TDF_DETAILS))
4432 fprintf (dump_file, " regs_used %d\n", n);
4434 if (dump_file && (dump_flags & TDF_DETAILS))
4436 fprintf (dump_file, " cost for size:\n");
4437 fprintf (dump_file, " ivs\tcost\n");
4438 for (j = 0; j <= 2 * target_avail_regs; j++)
4439 fprintf (dump_file, " %d\t%d\n", j,
4440 ivopts_global_cost_for_size (data, j));
4441 fprintf (dump_file, "\n");
4445 /* Returns true if A is a cheaper cost pair than B. */
4447 static bool
4448 cheaper_cost_pair (struct cost_pair *a, struct cost_pair *b)
4450 if (!a)
4451 return false;
4453 if (!b)
4454 return true;
4456 if (a->cost < b->cost)
4457 return true;
4459 if (a->cost > b->cost)
4460 return false;
4462 /* In case the costs are the same, prefer the cheaper candidate. */
4463 if (a->cand->cost < b->cand->cost)
4464 return true;
4466 return false;
4469 /* Computes the cost field of IVS structure. */
4471 static void
4472 iv_ca_recount_cost (struct ivopts_data *data, struct iv_ca *ivs)
4474 unsigned cost = 0;
4476 cost += ivs->cand_use_cost;
4477 cost += ivs->cand_cost;
4478 cost += ivopts_global_cost_for_size (data, ivs->n_regs);
4480 ivs->cost = cost;
4483 /* Remove invariants in set INVS to set IVS. */
4485 static void
4486 iv_ca_set_remove_invariants (struct iv_ca *ivs, bitmap invs)
4488 bitmap_iterator bi;
4489 unsigned iid;
4491 if (!invs)
4492 return;
4494 EXECUTE_IF_SET_IN_BITMAP (invs, 0, iid, bi)
4496 ivs->n_invariant_uses[iid]--;
4497 if (ivs->n_invariant_uses[iid] == 0)
4498 ivs->n_regs--;
4502 /* Set USE not to be expressed by any candidate in IVS. */
4504 static void
4505 iv_ca_set_no_cp (struct ivopts_data *data, struct iv_ca *ivs,
4506 struct iv_use *use)
4508 unsigned uid = use->id, cid;
4509 struct cost_pair *cp;
4511 cp = ivs->cand_for_use[uid];
4512 if (!cp)
4513 return;
4514 cid = cp->cand->id;
4516 ivs->bad_uses++;
4517 ivs->cand_for_use[uid] = NULL;
4518 ivs->n_cand_uses[cid]--;
4520 if (ivs->n_cand_uses[cid] == 0)
4522 bitmap_clear_bit (ivs->cands, cid);
4523 /* Do not count the pseudocandidates. */
4524 if (cp->cand->iv)
4525 ivs->n_regs--;
4526 ivs->n_cands--;
4527 ivs->cand_cost -= cp->cand->cost;
4529 iv_ca_set_remove_invariants (ivs, cp->cand->depends_on);
4532 ivs->cand_use_cost -= cp->cost;
4534 iv_ca_set_remove_invariants (ivs, cp->depends_on);
4535 iv_ca_recount_cost (data, ivs);
4538 /* Add invariants in set INVS to set IVS. */
4540 static void
4541 iv_ca_set_add_invariants (struct iv_ca *ivs, bitmap invs)
4543 bitmap_iterator bi;
4544 unsigned iid;
4546 if (!invs)
4547 return;
4549 EXECUTE_IF_SET_IN_BITMAP (invs, 0, iid, bi)
4551 ivs->n_invariant_uses[iid]++;
4552 if (ivs->n_invariant_uses[iid] == 1)
4553 ivs->n_regs++;
4557 /* Set cost pair for USE in set IVS to CP. */
4559 static void
4560 iv_ca_set_cp (struct ivopts_data *data, struct iv_ca *ivs,
4561 struct iv_use *use, struct cost_pair *cp)
4563 unsigned uid = use->id, cid;
4565 if (ivs->cand_for_use[uid] == cp)
4566 return;
4568 if (ivs->cand_for_use[uid])
4569 iv_ca_set_no_cp (data, ivs, use);
4571 if (cp)
4573 cid = cp->cand->id;
4575 ivs->bad_uses--;
4576 ivs->cand_for_use[uid] = cp;
4577 ivs->n_cand_uses[cid]++;
4578 if (ivs->n_cand_uses[cid] == 1)
4580 bitmap_set_bit (ivs->cands, cid);
4581 /* Do not count the pseudocandidates. */
4582 if (cp->cand->iv)
4583 ivs->n_regs++;
4584 ivs->n_cands++;
4585 ivs->cand_cost += cp->cand->cost;
4587 iv_ca_set_add_invariants (ivs, cp->cand->depends_on);
4590 ivs->cand_use_cost += cp->cost;
4591 iv_ca_set_add_invariants (ivs, cp->depends_on);
4592 iv_ca_recount_cost (data, ivs);
4596 /* Extend set IVS by expressing USE by some of the candidates in it
4597 if possible. */
4599 static void
4600 iv_ca_add_use (struct ivopts_data *data, struct iv_ca *ivs,
4601 struct iv_use *use)
4603 struct cost_pair *best_cp = NULL, *cp;
4604 bitmap_iterator bi;
4605 unsigned i;
4607 gcc_assert (ivs->upto >= use->id);
4609 if (ivs->upto == use->id)
4611 ivs->upto++;
4612 ivs->bad_uses++;
4615 EXECUTE_IF_SET_IN_BITMAP (ivs->cands, 0, i, bi)
4617 cp = get_use_iv_cost (data, use, iv_cand (data, i));
4619 if (cheaper_cost_pair (cp, best_cp))
4620 best_cp = cp;
4623 iv_ca_set_cp (data, ivs, use, best_cp);
4626 /* Get cost for assignment IVS. */
4628 static unsigned
4629 iv_ca_cost (struct iv_ca *ivs)
4631 return (ivs->bad_uses ? INFTY : ivs->cost);
4634 /* Returns true if all dependences of CP are among invariants in IVS. */
4636 static bool
4637 iv_ca_has_deps (struct iv_ca *ivs, struct cost_pair *cp)
4639 unsigned i;
4640 bitmap_iterator bi;
4642 if (!cp->depends_on)
4643 return true;
4645 EXECUTE_IF_SET_IN_BITMAP (cp->depends_on, 0, i, bi)
4647 if (ivs->n_invariant_uses[i] == 0)
4648 return false;
4651 return true;
4654 /* Creates change of expressing USE by NEW_CP instead of OLD_CP and chains
4655 it before NEXT_CHANGE. */
4657 static struct iv_ca_delta *
4658 iv_ca_delta_add (struct iv_use *use, struct cost_pair *old_cp,
4659 struct cost_pair *new_cp, struct iv_ca_delta *next_change)
4661 struct iv_ca_delta *change = xmalloc (sizeof (struct iv_ca_delta));
4663 change->use = use;
4664 change->old_cp = old_cp;
4665 change->new_cp = new_cp;
4666 change->next_change = next_change;
4668 return change;
4671 /* Joins two lists of changes L1 and L2. Destructive -- old lists
4672 are rewritten. */
4674 static struct iv_ca_delta *
4675 iv_ca_delta_join (struct iv_ca_delta *l1, struct iv_ca_delta *l2)
4677 struct iv_ca_delta *last;
4679 if (!l2)
4680 return l1;
4682 if (!l1)
4683 return l2;
4685 for (last = l1; last->next_change; last = last->next_change)
4686 continue;
4687 last->next_change = l2;
4689 return l1;
4692 /* Returns candidate by that USE is expressed in IVS. */
4694 static struct cost_pair *
4695 iv_ca_cand_for_use (struct iv_ca *ivs, struct iv_use *use)
4697 return ivs->cand_for_use[use->id];
4700 /* Reverse the list of changes DELTA, forming the inverse to it. */
4702 static struct iv_ca_delta *
4703 iv_ca_delta_reverse (struct iv_ca_delta *delta)
4705 struct iv_ca_delta *act, *next, *prev = NULL;
4706 struct cost_pair *tmp;
4708 for (act = delta; act; act = next)
4710 next = act->next_change;
4711 act->next_change = prev;
4712 prev = act;
4714 tmp = act->old_cp;
4715 act->old_cp = act->new_cp;
4716 act->new_cp = tmp;
4719 return prev;
4722 /* Commit changes in DELTA to IVS. If FORWARD is false, the changes are
4723 reverted instead. */
4725 static void
4726 iv_ca_delta_commit (struct ivopts_data *data, struct iv_ca *ivs,
4727 struct iv_ca_delta *delta, bool forward)
4729 struct cost_pair *from, *to;
4730 struct iv_ca_delta *act;
4732 if (!forward)
4733 delta = iv_ca_delta_reverse (delta);
4735 for (act = delta; act; act = act->next_change)
4737 from = act->old_cp;
4738 to = act->new_cp;
4739 gcc_assert (iv_ca_cand_for_use (ivs, act->use) == from);
4740 iv_ca_set_cp (data, ivs, act->use, to);
4743 if (!forward)
4744 iv_ca_delta_reverse (delta);
4747 /* Returns true if CAND is used in IVS. */
4749 static bool
4750 iv_ca_cand_used_p (struct iv_ca *ivs, struct iv_cand *cand)
4752 return ivs->n_cand_uses[cand->id] > 0;
4755 /* Returns number of induction variable candidates in the set IVS. */
4757 static unsigned
4758 iv_ca_n_cands (struct iv_ca *ivs)
4760 return ivs->n_cands;
4763 /* Free the list of changes DELTA. */
4765 static void
4766 iv_ca_delta_free (struct iv_ca_delta **delta)
4768 struct iv_ca_delta *act, *next;
4770 for (act = *delta; act; act = next)
4772 next = act->next_change;
4773 free (act);
4776 *delta = NULL;
4779 /* Allocates new iv candidates assignment. */
4781 static struct iv_ca *
4782 iv_ca_new (struct ivopts_data *data)
4784 struct iv_ca *nw = xmalloc (sizeof (struct iv_ca));
4786 nw->upto = 0;
4787 nw->bad_uses = 0;
4788 nw->cand_for_use = xcalloc (n_iv_uses (data), sizeof (struct cost_pair *));
4789 nw->n_cand_uses = xcalloc (n_iv_cands (data), sizeof (unsigned));
4790 nw->cands = BITMAP_ALLOC (NULL);
4791 nw->n_cands = 0;
4792 nw->n_regs = 0;
4793 nw->cand_use_cost = 0;
4794 nw->cand_cost = 0;
4795 nw->n_invariant_uses = xcalloc (data->max_inv_id + 1, sizeof (unsigned));
4796 nw->cost = 0;
4798 return nw;
4801 /* Free memory occupied by the set IVS. */
4803 static void
4804 iv_ca_free (struct iv_ca **ivs)
4806 free ((*ivs)->cand_for_use);
4807 free ((*ivs)->n_cand_uses);
4808 BITMAP_FREE ((*ivs)->cands);
4809 free ((*ivs)->n_invariant_uses);
4810 free (*ivs);
4811 *ivs = NULL;
4814 /* Dumps IVS to FILE. */
4816 static void
4817 iv_ca_dump (struct ivopts_data *data, FILE *file, struct iv_ca *ivs)
4819 const char *pref = " invariants ";
4820 unsigned i;
4822 fprintf (file, " cost %d\n", iv_ca_cost (ivs));
4823 bitmap_print (file, ivs->cands, " candidates ","\n");
4825 for (i = 1; i <= data->max_inv_id; i++)
4826 if (ivs->n_invariant_uses[i])
4828 fprintf (file, "%s%d", pref, i);
4829 pref = ", ";
4831 fprintf (file, "\n");
4834 /* Try changing candidate in IVS to CAND for each use. Return cost of the
4835 new set, and store differences in DELTA. Number of induction variables
4836 in the new set is stored to N_IVS. */
4838 static unsigned
4839 iv_ca_extend (struct ivopts_data *data, struct iv_ca *ivs,
4840 struct iv_cand *cand, struct iv_ca_delta **delta,
4841 unsigned *n_ivs)
4843 unsigned i, cost;
4844 struct iv_use *use;
4845 struct cost_pair *old_cp, *new_cp;
4847 *delta = NULL;
4848 for (i = 0; i < ivs->upto; i++)
4850 use = iv_use (data, i);
4851 old_cp = iv_ca_cand_for_use (ivs, use);
4853 if (old_cp
4854 && old_cp->cand == cand)
4855 continue;
4857 new_cp = get_use_iv_cost (data, use, cand);
4858 if (!new_cp)
4859 continue;
4861 if (!iv_ca_has_deps (ivs, new_cp))
4862 continue;
4864 if (!cheaper_cost_pair (new_cp, old_cp))
4865 continue;
4867 *delta = iv_ca_delta_add (use, old_cp, new_cp, *delta);
4870 iv_ca_delta_commit (data, ivs, *delta, true);
4871 cost = iv_ca_cost (ivs);
4872 if (n_ivs)
4873 *n_ivs = iv_ca_n_cands (ivs);
4874 iv_ca_delta_commit (data, ivs, *delta, false);
4876 return cost;
4879 /* Try narrowing set IVS by removing CAND. Return the cost of
4880 the new set and store the differences in DELTA. */
4882 static unsigned
4883 iv_ca_narrow (struct ivopts_data *data, struct iv_ca *ivs,
4884 struct iv_cand *cand, struct iv_ca_delta **delta)
4886 unsigned i, ci;
4887 struct iv_use *use;
4888 struct cost_pair *old_cp, *new_cp, *cp;
4889 bitmap_iterator bi;
4890 struct iv_cand *cnd;
4891 unsigned cost;
4893 *delta = NULL;
4894 for (i = 0; i < n_iv_uses (data); i++)
4896 use = iv_use (data, i);
4898 old_cp = iv_ca_cand_for_use (ivs, use);
4899 if (old_cp->cand != cand)
4900 continue;
4902 new_cp = NULL;
4904 if (data->consider_all_candidates)
4906 EXECUTE_IF_SET_IN_BITMAP (ivs->cands, 0, ci, bi)
4908 if (ci == cand->id)
4909 continue;
4911 cnd = iv_cand (data, ci);
4913 cp = get_use_iv_cost (data, use, cnd);
4914 if (!cp)
4915 continue;
4916 if (!iv_ca_has_deps (ivs, cp))
4917 continue;
4919 if (!cheaper_cost_pair (cp, new_cp))
4920 continue;
4922 new_cp = cp;
4925 else
4927 EXECUTE_IF_AND_IN_BITMAP (use->related_cands, ivs->cands, 0, ci, bi)
4929 if (ci == cand->id)
4930 continue;
4932 cnd = iv_cand (data, ci);
4934 cp = get_use_iv_cost (data, use, cnd);
4935 if (!cp)
4936 continue;
4937 if (!iv_ca_has_deps (ivs, cp))
4938 continue;
4940 if (!cheaper_cost_pair (cp, new_cp))
4941 continue;
4943 new_cp = cp;
4947 if (!new_cp)
4949 iv_ca_delta_free (delta);
4950 return INFTY;
4953 *delta = iv_ca_delta_add (use, old_cp, new_cp, *delta);
4956 iv_ca_delta_commit (data, ivs, *delta, true);
4957 cost = iv_ca_cost (ivs);
4958 iv_ca_delta_commit (data, ivs, *delta, false);
4960 return cost;
4963 /* Try optimizing the set of candidates IVS by removing candidates different
4964 from to EXCEPT_CAND from it. Return cost of the new set, and store
4965 differences in DELTA. */
4967 static unsigned
4968 iv_ca_prune (struct ivopts_data *data, struct iv_ca *ivs,
4969 struct iv_cand *except_cand, struct iv_ca_delta **delta)
4971 bitmap_iterator bi;
4972 struct iv_ca_delta *act_delta, *best_delta;
4973 unsigned i, best_cost, acost;
4974 struct iv_cand *cand;
4976 best_delta = NULL;
4977 best_cost = iv_ca_cost (ivs);
4979 EXECUTE_IF_SET_IN_BITMAP (ivs->cands, 0, i, bi)
4981 cand = iv_cand (data, i);
4983 if (cand == except_cand)
4984 continue;
4986 acost = iv_ca_narrow (data, ivs, cand, &act_delta);
4988 if (acost < best_cost)
4990 best_cost = acost;
4991 iv_ca_delta_free (&best_delta);
4992 best_delta = act_delta;
4994 else
4995 iv_ca_delta_free (&act_delta);
4998 if (!best_delta)
5000 *delta = NULL;
5001 return best_cost;
5004 /* Recurse to possibly remove other unnecessary ivs. */
5005 iv_ca_delta_commit (data, ivs, best_delta, true);
5006 best_cost = iv_ca_prune (data, ivs, except_cand, delta);
5007 iv_ca_delta_commit (data, ivs, best_delta, false);
5008 *delta = iv_ca_delta_join (best_delta, *delta);
5009 return best_cost;
5012 /* Tries to extend the sets IVS in the best possible way in order
5013 to express the USE. */
5015 static bool
5016 try_add_cand_for (struct ivopts_data *data, struct iv_ca *ivs,
5017 struct iv_use *use)
5019 unsigned best_cost, act_cost;
5020 unsigned i;
5021 bitmap_iterator bi;
5022 struct iv_cand *cand;
5023 struct iv_ca_delta *best_delta = NULL, *act_delta;
5024 struct cost_pair *cp;
5026 iv_ca_add_use (data, ivs, use);
5027 best_cost = iv_ca_cost (ivs);
5029 cp = iv_ca_cand_for_use (ivs, use);
5030 if (cp)
5032 best_delta = iv_ca_delta_add (use, NULL, cp, NULL);
5033 iv_ca_set_no_cp (data, ivs, use);
5036 /* First try important candidates. Only if it fails, try the specific ones.
5037 Rationale -- in loops with many variables the best choice often is to use
5038 just one generic biv. If we added here many ivs specific to the uses,
5039 the optimization algorithm later would be likely to get stuck in a local
5040 minimum, thus causing us to create too many ivs. The approach from
5041 few ivs to more seems more likely to be successful -- starting from few
5042 ivs, replacing an expensive use by a specific iv should always be a
5043 win. */
5044 EXECUTE_IF_SET_IN_BITMAP (data->important_candidates, 0, i, bi)
5046 cand = iv_cand (data, i);
5048 if (iv_ca_cand_used_p (ivs, cand))
5049 continue;
5051 cp = get_use_iv_cost (data, use, cand);
5052 if (!cp)
5053 continue;
5055 iv_ca_set_cp (data, ivs, use, cp);
5056 act_cost = iv_ca_extend (data, ivs, cand, &act_delta, NULL);
5057 iv_ca_set_no_cp (data, ivs, use);
5058 act_delta = iv_ca_delta_add (use, NULL, cp, act_delta);
5060 if (act_cost < best_cost)
5062 best_cost = act_cost;
5064 iv_ca_delta_free (&best_delta);
5065 best_delta = act_delta;
5067 else
5068 iv_ca_delta_free (&act_delta);
5071 if (best_cost == INFTY)
5073 for (i = 0; i < use->n_map_members; i++)
5075 cp = use->cost_map + i;
5076 cand = cp->cand;
5077 if (!cand)
5078 continue;
5080 /* Already tried this. */
5081 if (cand->important)
5082 continue;
5084 if (iv_ca_cand_used_p (ivs, cand))
5085 continue;
5087 act_delta = NULL;
5088 iv_ca_set_cp (data, ivs, use, cp);
5089 act_cost = iv_ca_extend (data, ivs, cand, &act_delta, NULL);
5090 iv_ca_set_no_cp (data, ivs, use);
5091 act_delta = iv_ca_delta_add (use, iv_ca_cand_for_use (ivs, use),
5092 cp, act_delta);
5094 if (act_cost < best_cost)
5096 best_cost = act_cost;
5098 if (best_delta)
5099 iv_ca_delta_free (&best_delta);
5100 best_delta = act_delta;
5102 else
5103 iv_ca_delta_free (&act_delta);
5107 iv_ca_delta_commit (data, ivs, best_delta, true);
5108 iv_ca_delta_free (&best_delta);
5110 return (best_cost != INFTY);
5113 /* Finds an initial assignment of candidates to uses. */
5115 static struct iv_ca *
5116 get_initial_solution (struct ivopts_data *data)
5118 struct iv_ca *ivs = iv_ca_new (data);
5119 unsigned i;
5121 for (i = 0; i < n_iv_uses (data); i++)
5122 if (!try_add_cand_for (data, ivs, iv_use (data, i)))
5124 iv_ca_free (&ivs);
5125 return NULL;
5128 return ivs;
5131 /* Tries to improve set of induction variables IVS. */
5133 static bool
5134 try_improve_iv_set (struct ivopts_data *data, struct iv_ca *ivs)
5136 unsigned i, acost, best_cost = iv_ca_cost (ivs), n_ivs;
5137 struct iv_ca_delta *best_delta = NULL, *act_delta, *tmp_delta;
5138 struct iv_cand *cand;
5140 /* Try extending the set of induction variables by one. */
5141 for (i = 0; i < n_iv_cands (data); i++)
5143 cand = iv_cand (data, i);
5145 if (iv_ca_cand_used_p (ivs, cand))
5146 continue;
5148 acost = iv_ca_extend (data, ivs, cand, &act_delta, &n_ivs);
5149 if (!act_delta)
5150 continue;
5152 /* If we successfully added the candidate and the set is small enough,
5153 try optimizing it by removing other candidates. */
5154 if (n_ivs <= ALWAYS_PRUNE_CAND_SET_BOUND)
5156 iv_ca_delta_commit (data, ivs, act_delta, true);
5157 acost = iv_ca_prune (data, ivs, cand, &tmp_delta);
5158 iv_ca_delta_commit (data, ivs, act_delta, false);
5159 act_delta = iv_ca_delta_join (act_delta, tmp_delta);
5162 if (acost < best_cost)
5164 best_cost = acost;
5165 iv_ca_delta_free (&best_delta);
5166 best_delta = act_delta;
5168 else
5169 iv_ca_delta_free (&act_delta);
5172 if (!best_delta)
5174 /* Try removing the candidates from the set instead. */
5175 best_cost = iv_ca_prune (data, ivs, NULL, &best_delta);
5177 /* Nothing more we can do. */
5178 if (!best_delta)
5179 return false;
5182 iv_ca_delta_commit (data, ivs, best_delta, true);
5183 gcc_assert (best_cost == iv_ca_cost (ivs));
5184 iv_ca_delta_free (&best_delta);
5185 return true;
5188 /* Attempts to find the optimal set of induction variables. We do simple
5189 greedy heuristic -- we try to replace at most one candidate in the selected
5190 solution and remove the unused ivs while this improves the cost. */
5192 static struct iv_ca *
5193 find_optimal_iv_set (struct ivopts_data *data)
5195 unsigned i;
5196 struct iv_ca *set;
5197 struct iv_use *use;
5199 /* Get the initial solution. */
5200 set = get_initial_solution (data);
5201 if (!set)
5203 if (dump_file && (dump_flags & TDF_DETAILS))
5204 fprintf (dump_file, "Unable to substitute for ivs, failed.\n");
5205 return NULL;
5208 if (dump_file && (dump_flags & TDF_DETAILS))
5210 fprintf (dump_file, "Initial set of candidates:\n");
5211 iv_ca_dump (data, dump_file, set);
5214 while (try_improve_iv_set (data, set))
5216 if (dump_file && (dump_flags & TDF_DETAILS))
5218 fprintf (dump_file, "Improved to:\n");
5219 iv_ca_dump (data, dump_file, set);
5223 if (dump_file && (dump_flags & TDF_DETAILS))
5224 fprintf (dump_file, "Final cost %d\n\n", iv_ca_cost (set));
5226 for (i = 0; i < n_iv_uses (data); i++)
5228 use = iv_use (data, i);
5229 use->selected = iv_ca_cand_for_use (set, use)->cand;
5232 return set;
5235 /* Creates a new induction variable corresponding to CAND. */
5237 static void
5238 create_new_iv (struct ivopts_data *data, struct iv_cand *cand)
5240 block_stmt_iterator incr_pos;
5241 tree base;
5242 bool after = false;
5244 if (!cand->iv)
5245 return;
5247 switch (cand->pos)
5249 case IP_NORMAL:
5250 incr_pos = bsi_last (ip_normal_pos (data->current_loop));
5251 break;
5253 case IP_END:
5254 incr_pos = bsi_last (ip_end_pos (data->current_loop));
5255 after = true;
5256 break;
5258 case IP_ORIGINAL:
5259 /* Mark that the iv is preserved. */
5260 name_info (data, cand->var_before)->preserve_biv = true;
5261 name_info (data, cand->var_after)->preserve_biv = true;
5263 /* Rewrite the increment so that it uses var_before directly. */
5264 find_interesting_uses_op (data, cand->var_after)->selected = cand;
5266 return;
5269 gimple_add_tmp_var (cand->var_before);
5270 add_referenced_tmp_var (cand->var_before);
5272 base = unshare_expr (cand->iv->base);
5274 create_iv (base, unshare_expr (cand->iv->step),
5275 cand->var_before, data->current_loop,
5276 &incr_pos, after, &cand->var_before, &cand->var_after);
5279 /* Creates new induction variables described in SET. */
5281 static void
5282 create_new_ivs (struct ivopts_data *data, struct iv_ca *set)
5284 unsigned i;
5285 struct iv_cand *cand;
5286 bitmap_iterator bi;
5288 EXECUTE_IF_SET_IN_BITMAP (set->cands, 0, i, bi)
5290 cand = iv_cand (data, i);
5291 create_new_iv (data, cand);
5295 /* Removes statement STMT (real or a phi node). If INCLUDING_DEFINED_NAME
5296 is true, remove also the ssa name defined by the statement. */
5298 static void
5299 remove_statement (tree stmt, bool including_defined_name)
5301 if (TREE_CODE (stmt) == PHI_NODE)
5303 if (!including_defined_name)
5305 /* Prevent the ssa name defined by the statement from being removed. */
5306 SET_PHI_RESULT (stmt, NULL);
5308 remove_phi_node (stmt, NULL_TREE);
5310 else
5312 block_stmt_iterator bsi = bsi_for_stmt (stmt);
5314 bsi_remove (&bsi);
5318 /* Rewrites USE (definition of iv used in a nonlinear expression)
5319 using candidate CAND. */
5321 static void
5322 rewrite_use_nonlinear_expr (struct ivopts_data *data,
5323 struct iv_use *use, struct iv_cand *cand)
5325 tree comp;
5326 tree op, stmts, tgt, ass;
5327 block_stmt_iterator bsi, pbsi;
5329 /* An important special case -- if we are asked to express value of
5330 the original iv by itself, just exit; there is no need to
5331 introduce a new computation (that might also need casting the
5332 variable to unsigned and back). */
5333 if (cand->pos == IP_ORIGINAL
5334 && cand->incremented_at == use->stmt)
5336 tree step, ctype, utype;
5337 enum tree_code incr_code = PLUS_EXPR;
5339 gcc_assert (TREE_CODE (use->stmt) == MODIFY_EXPR);
5340 gcc_assert (TREE_OPERAND (use->stmt, 0) == cand->var_after);
5342 step = cand->iv->step;
5343 ctype = TREE_TYPE (step);
5344 utype = TREE_TYPE (cand->var_after);
5345 if (TREE_CODE (step) == NEGATE_EXPR)
5347 incr_code = MINUS_EXPR;
5348 step = TREE_OPERAND (step, 0);
5351 /* Check whether we may leave the computation unchanged.
5352 This is the case only if it does not rely on other
5353 computations in the loop -- otherwise, the computation
5354 we rely upon may be removed in remove_unused_ivs,
5355 thus leading to ICE. */
5356 op = TREE_OPERAND (use->stmt, 1);
5357 if (TREE_CODE (op) == PLUS_EXPR
5358 || TREE_CODE (op) == MINUS_EXPR)
5360 if (TREE_OPERAND (op, 0) == cand->var_before)
5361 op = TREE_OPERAND (op, 1);
5362 else if (TREE_CODE (op) == PLUS_EXPR
5363 && TREE_OPERAND (op, 1) == cand->var_before)
5364 op = TREE_OPERAND (op, 0);
5365 else
5366 op = NULL_TREE;
5368 else
5369 op = NULL_TREE;
5371 if (op
5372 && (TREE_CODE (op) == INTEGER_CST
5373 || operand_equal_p (op, step, 0)))
5374 return;
5376 /* Otherwise, add the necessary computations to express
5377 the iv. */
5378 op = fold_convert (ctype, cand->var_before);
5379 comp = fold_convert (utype,
5380 build2 (incr_code, ctype, op,
5381 unshare_expr (step)));
5383 else
5384 comp = get_computation (data->current_loop, use, cand);
5386 switch (TREE_CODE (use->stmt))
5388 case PHI_NODE:
5389 tgt = PHI_RESULT (use->stmt);
5391 /* If we should keep the biv, do not replace it. */
5392 if (name_info (data, tgt)->preserve_biv)
5393 return;
5395 pbsi = bsi = bsi_start (bb_for_stmt (use->stmt));
5396 while (!bsi_end_p (pbsi)
5397 && TREE_CODE (bsi_stmt (pbsi)) == LABEL_EXPR)
5399 bsi = pbsi;
5400 bsi_next (&pbsi);
5402 break;
5404 case MODIFY_EXPR:
5405 tgt = TREE_OPERAND (use->stmt, 0);
5406 bsi = bsi_for_stmt (use->stmt);
5407 break;
5409 default:
5410 gcc_unreachable ();
5413 op = force_gimple_operand (comp, &stmts, false, SSA_NAME_VAR (tgt));
5415 if (TREE_CODE (use->stmt) == PHI_NODE)
5417 if (stmts)
5418 bsi_insert_after (&bsi, stmts, BSI_CONTINUE_LINKING);
5419 ass = build2 (MODIFY_EXPR, TREE_TYPE (tgt), tgt, op);
5420 bsi_insert_after (&bsi, ass, BSI_NEW_STMT);
5421 remove_statement (use->stmt, false);
5422 SSA_NAME_DEF_STMT (tgt) = ass;
5424 else
5426 if (stmts)
5427 bsi_insert_before (&bsi, stmts, BSI_SAME_STMT);
5428 TREE_OPERAND (use->stmt, 1) = op;
5432 /* Replaces ssa name in index IDX by its basic variable. Callback for
5433 for_each_index. */
5435 static bool
5436 idx_remove_ssa_names (tree base, tree *idx,
5437 void *data ATTRIBUTE_UNUSED)
5439 tree *op;
5441 if (TREE_CODE (*idx) == SSA_NAME)
5442 *idx = SSA_NAME_VAR (*idx);
5444 if (TREE_CODE (base) == ARRAY_REF)
5446 op = &TREE_OPERAND (base, 2);
5447 if (*op
5448 && TREE_CODE (*op) == SSA_NAME)
5449 *op = SSA_NAME_VAR (*op);
5450 op = &TREE_OPERAND (base, 3);
5451 if (*op
5452 && TREE_CODE (*op) == SSA_NAME)
5453 *op = SSA_NAME_VAR (*op);
5456 return true;
5459 /* Unshares REF and replaces ssa names inside it by their basic variables. */
5461 static tree
5462 unshare_and_remove_ssa_names (tree ref)
5464 ref = unshare_expr (ref);
5465 for_each_index (&ref, idx_remove_ssa_names, NULL);
5467 return ref;
5470 /* Extract the alias analysis info for the memory reference REF. There are
5471 several ways how this information may be stored and what precisely is
5472 its semantics depending on the type of the reference, but there always is
5473 somewhere hidden one _DECL node that is used to determine the set of
5474 virtual operands for the reference. The code below deciphers this jungle
5475 and extracts this single useful piece of information. */
5477 static tree
5478 get_ref_tag (tree ref)
5480 tree var = get_base_address (ref);
5481 tree tag;
5483 if (!var)
5484 return NULL_TREE;
5486 if (TREE_CODE (var) == INDIRECT_REF)
5488 /* In case the base is a dereference of a pointer, first check its name
5489 mem tag, and if it does not have one, use type mem tag. */
5490 var = TREE_OPERAND (var, 0);
5491 if (TREE_CODE (var) != SSA_NAME)
5492 return NULL_TREE;
5494 if (SSA_NAME_PTR_INFO (var))
5496 tag = SSA_NAME_PTR_INFO (var)->name_mem_tag;
5497 if (tag)
5498 return tag;
5501 var = SSA_NAME_VAR (var);
5502 tag = var_ann (var)->type_mem_tag;
5503 gcc_assert (tag != NULL_TREE);
5504 return tag;
5506 else
5508 if (!DECL_P (var))
5509 return NULL_TREE;
5511 tag = var_ann (var)->type_mem_tag;
5512 if (tag)
5513 return tag;
5515 return var;
5519 /* Copies the reference information from OLD_REF to NEW_REF. */
5521 static void
5522 copy_ref_info (tree new_ref, tree old_ref)
5524 if (TREE_CODE (old_ref) == TARGET_MEM_REF)
5525 copy_mem_ref_info (new_ref, old_ref);
5526 else
5528 TMR_TAG (new_ref) = get_ref_tag (old_ref);
5529 TMR_ORIGINAL (new_ref) = unshare_and_remove_ssa_names (old_ref);
5533 /* Rewrites USE (address that is an iv) using candidate CAND. */
5535 static void
5536 rewrite_use_address (struct ivopts_data *data,
5537 struct iv_use *use, struct iv_cand *cand)
5539 struct affine_tree_combination aff;
5540 block_stmt_iterator bsi = bsi_for_stmt (use->stmt);
5541 tree ref;
5543 get_computation_aff (data->current_loop, use, cand, use->stmt, &aff);
5544 unshare_aff_combination (&aff);
5546 ref = create_mem_ref (&bsi, TREE_TYPE (*use->op_p), &aff);
5547 copy_ref_info (ref, *use->op_p);
5548 *use->op_p = ref;
5551 /* Rewrites USE (the condition such that one of the arguments is an iv) using
5552 candidate CAND. */
5554 static void
5555 rewrite_use_compare (struct ivopts_data *data,
5556 struct iv_use *use, struct iv_cand *cand)
5558 tree comp;
5559 tree *op_p, cond, op, stmts, bound;
5560 block_stmt_iterator bsi = bsi_for_stmt (use->stmt);
5561 enum tree_code compare;
5562 struct cost_pair *cp = get_use_iv_cost (data, use, cand);
5564 bound = cp->value;
5565 if (bound)
5567 tree var = var_at_stmt (data->current_loop, cand, use->stmt);
5568 tree var_type = TREE_TYPE (var);
5570 compare = iv_elimination_compare (data, use);
5571 bound = fold_convert (var_type, bound);
5572 op = force_gimple_operand (unshare_expr (bound), &stmts,
5573 true, NULL_TREE);
5575 if (stmts)
5576 bsi_insert_before (&bsi, stmts, BSI_SAME_STMT);
5578 *use->op_p = build2 (compare, boolean_type_node, var, op);
5579 update_stmt (use->stmt);
5580 return;
5583 /* The induction variable elimination failed; just express the original
5584 giv. */
5585 comp = get_computation (data->current_loop, use, cand);
5587 cond = *use->op_p;
5588 op_p = &TREE_OPERAND (cond, 0);
5589 if (TREE_CODE (*op_p) != SSA_NAME
5590 || zero_p (get_iv (data, *op_p)->step))
5591 op_p = &TREE_OPERAND (cond, 1);
5593 op = force_gimple_operand (comp, &stmts, true, SSA_NAME_VAR (*op_p));
5594 if (stmts)
5595 bsi_insert_before (&bsi, stmts, BSI_SAME_STMT);
5597 *op_p = op;
5600 /* Ensure that operand *OP_P may be used at the end of EXIT without
5601 violating loop closed ssa form. */
5603 static void
5604 protect_loop_closed_ssa_form_use (edge exit, use_operand_p op_p)
5606 basic_block def_bb;
5607 struct loop *def_loop;
5608 tree phi, use;
5610 use = USE_FROM_PTR (op_p);
5611 if (TREE_CODE (use) != SSA_NAME)
5612 return;
5614 def_bb = bb_for_stmt (SSA_NAME_DEF_STMT (use));
5615 if (!def_bb)
5616 return;
5618 def_loop = def_bb->loop_father;
5619 if (flow_bb_inside_loop_p (def_loop, exit->dest))
5620 return;
5622 /* Try finding a phi node that copies the value out of the loop. */
5623 for (phi = phi_nodes (exit->dest); phi; phi = PHI_CHAIN (phi))
5624 if (PHI_ARG_DEF_FROM_EDGE (phi, exit) == use)
5625 break;
5627 if (!phi)
5629 /* Create such a phi node. */
5630 tree new_name = duplicate_ssa_name (use, NULL);
5632 phi = create_phi_node (new_name, exit->dest);
5633 SSA_NAME_DEF_STMT (new_name) = phi;
5634 add_phi_arg (phi, use, exit);
5637 SET_USE (op_p, PHI_RESULT (phi));
5640 /* Ensure that operands of STMT may be used at the end of EXIT without
5641 violating loop closed ssa form. */
5643 static void
5644 protect_loop_closed_ssa_form (edge exit, tree stmt)
5646 ssa_op_iter iter;
5647 use_operand_p use_p;
5649 FOR_EACH_SSA_USE_OPERAND (use_p, stmt, iter, SSA_OP_ALL_USES)
5650 protect_loop_closed_ssa_form_use (exit, use_p);
5653 /* STMTS compute a value of a phi argument OP on EXIT of a loop. Arrange things
5654 so that they are emitted on the correct place, and so that the loop closed
5655 ssa form is preserved. */
5657 void
5658 compute_phi_arg_on_exit (edge exit, tree stmts, tree op)
5660 tree_stmt_iterator tsi;
5661 block_stmt_iterator bsi;
5662 tree phi, stmt, def, next;
5664 if (!single_pred_p (exit->dest))
5665 split_loop_exit_edge (exit);
5667 /* Ensure there is label in exit->dest, so that we can
5668 insert after it. */
5669 tree_block_label (exit->dest);
5670 bsi = bsi_after_labels (exit->dest);
5672 if (TREE_CODE (stmts) == STATEMENT_LIST)
5674 for (tsi = tsi_start (stmts); !tsi_end_p (tsi); tsi_next (&tsi))
5676 bsi_insert_after (&bsi, tsi_stmt (tsi), BSI_NEW_STMT);
5677 protect_loop_closed_ssa_form (exit, bsi_stmt (bsi));
5680 else
5682 bsi_insert_after (&bsi, stmts, BSI_NEW_STMT);
5683 protect_loop_closed_ssa_form (exit, bsi_stmt (bsi));
5686 if (!op)
5687 return;
5689 for (phi = phi_nodes (exit->dest); phi; phi = next)
5691 next = PHI_CHAIN (phi);
5693 if (PHI_ARG_DEF_FROM_EDGE (phi, exit) == op)
5695 def = PHI_RESULT (phi);
5696 remove_statement (phi, false);
5697 stmt = build2 (MODIFY_EXPR, TREE_TYPE (op),
5698 def, op);
5699 SSA_NAME_DEF_STMT (def) = stmt;
5700 bsi_insert_after (&bsi, stmt, BSI_CONTINUE_LINKING);
5705 /* Rewrites the final value of USE (that is only needed outside of the loop)
5706 using candidate CAND. */
5708 static void
5709 rewrite_use_outer (struct ivopts_data *data,
5710 struct iv_use *use, struct iv_cand *cand)
5712 edge exit;
5713 tree value, op, stmts, tgt;
5714 tree phi;
5716 switch (TREE_CODE (use->stmt))
5718 case PHI_NODE:
5719 tgt = PHI_RESULT (use->stmt);
5720 break;
5721 case MODIFY_EXPR:
5722 tgt = TREE_OPERAND (use->stmt, 0);
5723 break;
5724 default:
5725 gcc_unreachable ();
5728 exit = single_dom_exit (data->current_loop);
5730 if (exit)
5732 if (!cand->iv)
5734 struct cost_pair *cp = get_use_iv_cost (data, use, cand);
5735 value = unshare_expr (cp->value);
5737 else
5738 value = get_computation_at (data->current_loop,
5739 use, cand, last_stmt (exit->src));
5741 op = force_gimple_operand (value, &stmts, true, SSA_NAME_VAR (tgt));
5743 /* If we will preserve the iv anyway and we would need to perform
5744 some computation to replace the final value, do nothing. */
5745 if (stmts && name_info (data, tgt)->preserve_biv)
5746 return;
5748 for (phi = phi_nodes (exit->dest); phi; phi = PHI_CHAIN (phi))
5750 use_operand_p use_p = PHI_ARG_DEF_PTR_FROM_EDGE (phi, exit);
5752 if (USE_FROM_PTR (use_p) == tgt)
5753 SET_USE (use_p, op);
5756 if (stmts)
5757 compute_phi_arg_on_exit (exit, stmts, op);
5759 /* Enable removal of the statement. We cannot remove it directly,
5760 since we may still need the aliasing information attached to the
5761 ssa name defined by it. */
5762 name_info (data, tgt)->iv->have_use_for = false;
5763 return;
5766 /* If the variable is going to be preserved anyway, there is nothing to
5767 do. */
5768 if (name_info (data, tgt)->preserve_biv)
5769 return;
5771 /* Otherwise we just need to compute the iv. */
5772 rewrite_use_nonlinear_expr (data, use, cand);
5775 /* Rewrites USE using candidate CAND. */
5777 static void
5778 rewrite_use (struct ivopts_data *data,
5779 struct iv_use *use, struct iv_cand *cand)
5781 switch (use->type)
5783 case USE_NONLINEAR_EXPR:
5784 rewrite_use_nonlinear_expr (data, use, cand);
5785 break;
5787 case USE_OUTER:
5788 rewrite_use_outer (data, use, cand);
5789 break;
5791 case USE_ADDRESS:
5792 rewrite_use_address (data, use, cand);
5793 break;
5795 case USE_COMPARE:
5796 rewrite_use_compare (data, use, cand);
5797 break;
5799 default:
5800 gcc_unreachable ();
5802 update_stmt (use->stmt);
5805 /* Rewrite the uses using the selected induction variables. */
5807 static void
5808 rewrite_uses (struct ivopts_data *data)
5810 unsigned i;
5811 struct iv_cand *cand;
5812 struct iv_use *use;
5814 for (i = 0; i < n_iv_uses (data); i++)
5816 use = iv_use (data, i);
5817 cand = use->selected;
5818 gcc_assert (cand);
5820 rewrite_use (data, use, cand);
5824 /* Removes the ivs that are not used after rewriting. */
5826 static void
5827 remove_unused_ivs (struct ivopts_data *data)
5829 unsigned j;
5830 bitmap_iterator bi;
5832 EXECUTE_IF_SET_IN_BITMAP (data->relevant, 0, j, bi)
5834 struct version_info *info;
5836 info = ver_info (data, j);
5837 if (info->iv
5838 && !zero_p (info->iv->step)
5839 && !info->inv_id
5840 && !info->iv->have_use_for
5841 && !info->preserve_biv)
5842 remove_statement (SSA_NAME_DEF_STMT (info->iv->ssa_name), true);
5846 /* Frees data allocated by the optimization of a single loop. */
5848 static void
5849 free_loop_data (struct ivopts_data *data)
5851 unsigned i, j;
5852 bitmap_iterator bi;
5853 tree obj;
5855 htab_empty (data->niters);
5857 EXECUTE_IF_SET_IN_BITMAP (data->relevant, 0, i, bi)
5859 struct version_info *info;
5861 info = ver_info (data, i);
5862 if (info->iv)
5863 free (info->iv);
5864 info->iv = NULL;
5865 info->has_nonlin_use = false;
5866 info->preserve_biv = false;
5867 info->inv_id = 0;
5869 bitmap_clear (data->relevant);
5870 bitmap_clear (data->important_candidates);
5872 for (i = 0; i < n_iv_uses (data); i++)
5874 struct iv_use *use = iv_use (data, i);
5876 free (use->iv);
5877 BITMAP_FREE (use->related_cands);
5878 for (j = 0; j < use->n_map_members; j++)
5879 if (use->cost_map[j].depends_on)
5880 BITMAP_FREE (use->cost_map[j].depends_on);
5881 free (use->cost_map);
5882 free (use);
5884 VEC_truncate (iv_use_p, data->iv_uses, 0);
5886 for (i = 0; i < n_iv_cands (data); i++)
5888 struct iv_cand *cand = iv_cand (data, i);
5890 if (cand->iv)
5891 free (cand->iv);
5892 if (cand->depends_on)
5893 BITMAP_FREE (cand->depends_on);
5894 free (cand);
5896 VEC_truncate (iv_cand_p, data->iv_candidates, 0);
5898 if (data->version_info_size < num_ssa_names)
5900 data->version_info_size = 2 * num_ssa_names;
5901 free (data->version_info);
5902 data->version_info = xcalloc (data->version_info_size,
5903 sizeof (struct version_info));
5906 data->max_inv_id = 0;
5908 for (i = 0; VEC_iterate (tree, decl_rtl_to_reset, i, obj); i++)
5909 SET_DECL_RTL (obj, NULL_RTX);
5911 VEC_truncate (tree, decl_rtl_to_reset, 0);
5914 /* Finalizes data structures used by the iv optimization pass. LOOPS is the
5915 loop tree. */
5917 static void
5918 tree_ssa_iv_optimize_finalize (struct loops *loops, struct ivopts_data *data)
5920 unsigned i;
5922 for (i = 1; i < loops->num; i++)
5923 if (loops->parray[i])
5925 free (loops->parray[i]->aux);
5926 loops->parray[i]->aux = NULL;
5929 free_loop_data (data);
5930 free (data->version_info);
5931 BITMAP_FREE (data->relevant);
5932 BITMAP_FREE (data->important_candidates);
5933 htab_delete (data->niters);
5935 VEC_free (tree, heap, decl_rtl_to_reset);
5936 VEC_free (iv_use_p, heap, data->iv_uses);
5937 VEC_free (iv_cand_p, heap, data->iv_candidates);
5940 /* Optimizes the LOOP. Returns true if anything changed. */
5942 static bool
5943 tree_ssa_iv_optimize_loop (struct ivopts_data *data, struct loop *loop)
5945 bool changed = false;
5946 struct iv_ca *iv_ca;
5947 edge exit;
5949 data->current_loop = loop;
5951 if (dump_file && (dump_flags & TDF_DETAILS))
5953 fprintf (dump_file, "Processing loop %d\n", loop->num);
5955 exit = single_dom_exit (loop);
5956 if (exit)
5958 fprintf (dump_file, " single exit %d -> %d, exit condition ",
5959 exit->src->index, exit->dest->index);
5960 print_generic_expr (dump_file, last_stmt (exit->src), TDF_SLIM);
5961 fprintf (dump_file, "\n");
5964 fprintf (dump_file, "\n");
5967 /* For each ssa name determines whether it behaves as an induction variable
5968 in some loop. */
5969 if (!find_induction_variables (data))
5970 goto finish;
5972 /* Finds interesting uses (item 1). */
5973 find_interesting_uses (data);
5974 if (n_iv_uses (data) > MAX_CONSIDERED_USES)
5975 goto finish;
5977 /* Finds candidates for the induction variables (item 2). */
5978 find_iv_candidates (data);
5980 /* Calculates the costs (item 3, part 1). */
5981 determine_use_iv_costs (data);
5982 determine_iv_costs (data);
5983 determine_set_costs (data);
5985 /* Find the optimal set of induction variables (item 3, part 2). */
5986 iv_ca = find_optimal_iv_set (data);
5987 if (!iv_ca)
5988 goto finish;
5989 changed = true;
5991 /* Create the new induction variables (item 4, part 1). */
5992 create_new_ivs (data, iv_ca);
5993 iv_ca_free (&iv_ca);
5995 /* Rewrite the uses (item 4, part 2). */
5996 rewrite_uses (data);
5998 /* Remove the ivs that are unused after rewriting. */
5999 remove_unused_ivs (data);
6001 /* We have changed the structure of induction variables; it might happen
6002 that definitions in the scev database refer to some of them that were
6003 eliminated. */
6004 scev_reset ();
6006 finish:
6007 free_loop_data (data);
6009 return changed;
6012 /* Main entry point. Optimizes induction variables in LOOPS. */
6014 void
6015 tree_ssa_iv_optimize (struct loops *loops)
6017 struct loop *loop;
6018 struct ivopts_data data;
6020 tree_ssa_iv_optimize_init (loops, &data);
6022 /* Optimize the loops starting with the innermost ones. */
6023 loop = loops->tree_root;
6024 while (loop->inner)
6025 loop = loop->inner;
6027 /* Scan the loops, inner ones first. */
6028 while (loop != loops->tree_root)
6030 if (dump_file && (dump_flags & TDF_DETAILS))
6031 flow_loop_dump (loop, dump_file, NULL, 1);
6033 tree_ssa_iv_optimize_loop (&data, loop);
6035 if (loop->next)
6037 loop = loop->next;
6038 while (loop->inner)
6039 loop = loop->inner;
6041 else
6042 loop = loop->outer;
6045 tree_ssa_iv_optimize_finalize (loops, &data);