2015-10-18 Paul Thomas <pault@gcc.gnu.org>
[official-gcc.git] / gcc / tree-if-conv.c
blobf201ab5fdb17b77e9b48d897b9348079a2e8659a
1 /* If-conversion for vectorizer.
2 Copyright (C) 2004-2015 Free Software Foundation, Inc.
3 Contributed by Devang Patel <dpatel@apple.com>
5 This file is part of GCC.
7 GCC is free software; you can redistribute it and/or modify it under
8 the terms of the GNU General Public License as published by the Free
9 Software Foundation; either version 3, or (at your option) any later
10 version.
12 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
13 WARRANTY; without even the implied warranty of MERCHANTABILITY or
14 FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
15 for more details.
17 You should have received a copy of the GNU General Public License
18 along with GCC; see the file COPYING3. If not see
19 <http://www.gnu.org/licenses/>. */
21 /* This pass implements a tree level if-conversion of loops. Its
22 initial goal is to help the vectorizer to vectorize loops with
23 conditions.
25 A short description of if-conversion:
27 o Decide if a loop is if-convertible or not.
28 o Walk all loop basic blocks in breadth first order (BFS order).
29 o Remove conditional statements (at the end of basic block)
30 and propagate condition into destination basic blocks'
31 predicate list.
32 o Replace modify expression with conditional modify expression
33 using current basic block's condition.
34 o Merge all basic blocks
35 o Replace phi nodes with conditional modify expr
36 o Merge all basic blocks into header
38 Sample transformation:
40 INPUT
41 -----
43 # i_23 = PHI <0(0), i_18(10)>;
44 <L0>:;
45 j_15 = A[i_23];
46 if (j_15 > 41) goto <L1>; else goto <L17>;
48 <L17>:;
49 goto <bb 3> (<L3>);
51 <L1>:;
53 # iftmp.2_4 = PHI <0(8), 42(2)>;
54 <L3>:;
55 A[i_23] = iftmp.2_4;
56 i_18 = i_23 + 1;
57 if (i_18 <= 15) goto <L19>; else goto <L18>;
59 <L19>:;
60 goto <bb 1> (<L0>);
62 <L18>:;
64 OUTPUT
65 ------
67 # i_23 = PHI <0(0), i_18(10)>;
68 <L0>:;
69 j_15 = A[i_23];
71 <L3>:;
72 iftmp.2_4 = j_15 > 41 ? 42 : 0;
73 A[i_23] = iftmp.2_4;
74 i_18 = i_23 + 1;
75 if (i_18 <= 15) goto <L19>; else goto <L18>;
77 <L19>:;
78 goto <bb 1> (<L0>);
80 <L18>:;
83 #include "config.h"
84 #include "system.h"
85 #include "coretypes.h"
86 #include "backend.h"
87 #include "cfghooks.h"
88 #include "tree.h"
89 #include "gimple.h"
90 #include "rtl.h"
91 #include "ssa.h"
92 #include "alias.h"
93 #include "fold-const.h"
94 #include "stor-layout.h"
95 #include "flags.h"
96 #include "gimple-pretty-print.h"
97 #include "internal-fn.h"
98 #include "gimple-fold.h"
99 #include "gimplify.h"
100 #include "gimple-iterator.h"
101 #include "gimplify-me.h"
102 #include "tree-cfg.h"
103 #include "tree-into-ssa.h"
104 #include "tree-ssa.h"
105 #include "cfgloop.h"
106 #include "tree-chrec.h"
107 #include "tree-data-ref.h"
108 #include "tree-scalar-evolution.h"
109 #include "tree-ssa-loop-ivopts.h"
110 #include "tree-ssa-address.h"
111 #include "tree-pass.h"
112 #include "dbgcnt.h"
113 #include "insn-config.h"
114 #include "expmed.h"
115 #include "dojump.h"
116 #include "explow.h"
117 #include "calls.h"
118 #include "emit-rtl.h"
119 #include "varasm.h"
120 #include "stmt.h"
121 #include "expr.h"
122 #include "insn-codes.h"
123 #include "optabs-query.h"
124 #include "tree-hash-traits.h"
126 /* List of basic blocks in if-conversion-suitable order. */
127 static basic_block *ifc_bbs;
129 /* Apply more aggressive (extended) if-conversion if true. */
130 static bool aggressive_if_conv;
132 /* Structure used to predicate basic blocks. This is attached to the
133 ->aux field of the BBs in the loop to be if-converted. */
134 struct bb_predicate {
136 /* The condition under which this basic block is executed. */
137 tree predicate;
139 /* PREDICATE is gimplified, and the sequence of statements is
140 recorded here, in order to avoid the duplication of computations
141 that occur in previous conditions. See PR44483. */
142 gimple_seq predicate_gimplified_stmts;
145 /* Returns true when the basic block BB has a predicate. */
147 static inline bool
148 bb_has_predicate (basic_block bb)
150 return bb->aux != NULL;
153 /* Returns the gimplified predicate for basic block BB. */
155 static inline tree
156 bb_predicate (basic_block bb)
158 return ((struct bb_predicate *) bb->aux)->predicate;
161 /* Sets the gimplified predicate COND for basic block BB. */
163 static inline void
164 set_bb_predicate (basic_block bb, tree cond)
166 gcc_assert ((TREE_CODE (cond) == TRUTH_NOT_EXPR
167 && is_gimple_condexpr (TREE_OPERAND (cond, 0)))
168 || is_gimple_condexpr (cond));
169 ((struct bb_predicate *) bb->aux)->predicate = cond;
172 /* Returns the sequence of statements of the gimplification of the
173 predicate for basic block BB. */
175 static inline gimple_seq
176 bb_predicate_gimplified_stmts (basic_block bb)
178 return ((struct bb_predicate *) bb->aux)->predicate_gimplified_stmts;
181 /* Sets the sequence of statements STMTS of the gimplification of the
182 predicate for basic block BB. */
184 static inline void
185 set_bb_predicate_gimplified_stmts (basic_block bb, gimple_seq stmts)
187 ((struct bb_predicate *) bb->aux)->predicate_gimplified_stmts = stmts;
190 /* Adds the sequence of statements STMTS to the sequence of statements
191 of the predicate for basic block BB. */
193 static inline void
194 add_bb_predicate_gimplified_stmts (basic_block bb, gimple_seq stmts)
196 gimple_seq_add_seq
197 (&(((struct bb_predicate *) bb->aux)->predicate_gimplified_stmts), stmts);
200 /* Initializes to TRUE the predicate of basic block BB. */
202 static inline void
203 init_bb_predicate (basic_block bb)
205 bb->aux = XNEW (struct bb_predicate);
206 set_bb_predicate_gimplified_stmts (bb, NULL);
207 set_bb_predicate (bb, boolean_true_node);
210 /* Release the SSA_NAMEs associated with the predicate of basic block BB,
211 but don't actually free it. */
213 static inline void
214 release_bb_predicate (basic_block bb)
216 gimple_seq stmts = bb_predicate_gimplified_stmts (bb);
217 if (stmts)
219 gimple_stmt_iterator i;
221 for (i = gsi_start (stmts); !gsi_end_p (i); gsi_next (&i))
222 free_stmt_operands (cfun, gsi_stmt (i));
223 set_bb_predicate_gimplified_stmts (bb, NULL);
227 /* Free the predicate of basic block BB. */
229 static inline void
230 free_bb_predicate (basic_block bb)
232 if (!bb_has_predicate (bb))
233 return;
235 release_bb_predicate (bb);
236 free (bb->aux);
237 bb->aux = NULL;
240 /* Reinitialize predicate of BB with the true predicate. */
242 static inline void
243 reset_bb_predicate (basic_block bb)
245 if (!bb_has_predicate (bb))
246 init_bb_predicate (bb);
247 else
249 release_bb_predicate (bb);
250 set_bb_predicate (bb, boolean_true_node);
254 /* Returns a new SSA_NAME of type TYPE that is assigned the value of
255 the expression EXPR. Inserts the statement created for this
256 computation before GSI and leaves the iterator GSI at the same
257 statement. */
259 static tree
260 ifc_temp_var (tree type, tree expr, gimple_stmt_iterator *gsi)
262 tree new_name = make_temp_ssa_name (type, NULL, "_ifc_");
263 gimple *stmt = gimple_build_assign (new_name, expr);
264 gsi_insert_before (gsi, stmt, GSI_SAME_STMT);
265 return new_name;
268 /* Return true when COND is a true predicate. */
270 static inline bool
271 is_true_predicate (tree cond)
273 return (cond == NULL_TREE
274 || cond == boolean_true_node
275 || integer_onep (cond));
278 /* Returns true when BB has a predicate that is not trivial: true or
279 NULL_TREE. */
281 static inline bool
282 is_predicated (basic_block bb)
284 return !is_true_predicate (bb_predicate (bb));
287 /* Parses the predicate COND and returns its comparison code and
288 operands OP0 and OP1. */
290 static enum tree_code
291 parse_predicate (tree cond, tree *op0, tree *op1)
293 gimple *s;
295 if (TREE_CODE (cond) == SSA_NAME
296 && is_gimple_assign (s = SSA_NAME_DEF_STMT (cond)))
298 if (TREE_CODE_CLASS (gimple_assign_rhs_code (s)) == tcc_comparison)
300 *op0 = gimple_assign_rhs1 (s);
301 *op1 = gimple_assign_rhs2 (s);
302 return gimple_assign_rhs_code (s);
305 else if (gimple_assign_rhs_code (s) == TRUTH_NOT_EXPR)
307 tree op = gimple_assign_rhs1 (s);
308 tree type = TREE_TYPE (op);
309 enum tree_code code = parse_predicate (op, op0, op1);
311 return code == ERROR_MARK ? ERROR_MARK
312 : invert_tree_comparison (code, HONOR_NANS (type));
315 return ERROR_MARK;
318 if (COMPARISON_CLASS_P (cond))
320 *op0 = TREE_OPERAND (cond, 0);
321 *op1 = TREE_OPERAND (cond, 1);
322 return TREE_CODE (cond);
325 return ERROR_MARK;
328 /* Returns the fold of predicate C1 OR C2 at location LOC. */
330 static tree
331 fold_or_predicates (location_t loc, tree c1, tree c2)
333 tree op1a, op1b, op2a, op2b;
334 enum tree_code code1 = parse_predicate (c1, &op1a, &op1b);
335 enum tree_code code2 = parse_predicate (c2, &op2a, &op2b);
337 if (code1 != ERROR_MARK && code2 != ERROR_MARK)
339 tree t = maybe_fold_or_comparisons (code1, op1a, op1b,
340 code2, op2a, op2b);
341 if (t)
342 return t;
345 return fold_build2_loc (loc, TRUTH_OR_EXPR, boolean_type_node, c1, c2);
348 /* Returns true if N is either a constant or a SSA_NAME. */
350 static bool
351 constant_or_ssa_name (tree n)
353 switch (TREE_CODE (n))
355 case SSA_NAME:
356 case INTEGER_CST:
357 case REAL_CST:
358 case COMPLEX_CST:
359 case VECTOR_CST:
360 return true;
361 default:
362 return false;
366 /* Returns either a COND_EXPR or the folded expression if the folded
367 expression is a MIN_EXPR, a MAX_EXPR, an ABS_EXPR,
368 a constant or a SSA_NAME. */
370 static tree
371 fold_build_cond_expr (tree type, tree cond, tree rhs, tree lhs)
373 tree rhs1, lhs1, cond_expr;
375 /* If COND is comparison r != 0 and r has boolean type, convert COND
376 to SSA_NAME to accept by vect bool pattern. */
377 if (TREE_CODE (cond) == NE_EXPR)
379 tree op0 = TREE_OPERAND (cond, 0);
380 tree op1 = TREE_OPERAND (cond, 1);
381 if (TREE_CODE (op0) == SSA_NAME
382 && TREE_CODE (TREE_TYPE (op0)) == BOOLEAN_TYPE
383 && (integer_zerop (op1)))
384 cond = op0;
386 cond_expr = fold_ternary (COND_EXPR, type, cond,
387 rhs, lhs);
389 if (cond_expr == NULL_TREE)
390 return build3 (COND_EXPR, type, cond, rhs, lhs);
392 STRIP_USELESS_TYPE_CONVERSION (cond_expr);
394 if (constant_or_ssa_name (cond_expr))
395 return cond_expr;
397 if (TREE_CODE (cond_expr) == ABS_EXPR)
399 rhs1 = TREE_OPERAND (cond_expr, 1);
400 STRIP_USELESS_TYPE_CONVERSION (rhs1);
401 if (constant_or_ssa_name (rhs1))
402 return build1 (ABS_EXPR, type, rhs1);
405 if (TREE_CODE (cond_expr) == MIN_EXPR
406 || TREE_CODE (cond_expr) == MAX_EXPR)
408 lhs1 = TREE_OPERAND (cond_expr, 0);
409 STRIP_USELESS_TYPE_CONVERSION (lhs1);
410 rhs1 = TREE_OPERAND (cond_expr, 1);
411 STRIP_USELESS_TYPE_CONVERSION (rhs1);
412 if (constant_or_ssa_name (rhs1)
413 && constant_or_ssa_name (lhs1))
414 return build2 (TREE_CODE (cond_expr), type, lhs1, rhs1);
416 return build3 (COND_EXPR, type, cond, rhs, lhs);
419 /* Add condition NC to the predicate list of basic block BB. LOOP is
420 the loop to be if-converted. Use predicate of cd-equivalent block
421 for join bb if it exists: we call basic blocks bb1 and bb2
422 cd-equivalent if they are executed under the same condition. */
424 static inline void
425 add_to_predicate_list (struct loop *loop, basic_block bb, tree nc)
427 tree bc, *tp;
428 basic_block dom_bb;
430 if (is_true_predicate (nc))
431 return;
433 /* If dominance tells us this basic block is always executed,
434 don't record any predicates for it. */
435 if (dominated_by_p (CDI_DOMINATORS, loop->latch, bb))
436 return;
438 dom_bb = get_immediate_dominator (CDI_DOMINATORS, bb);
439 /* We use notion of cd equivalence to get simpler predicate for
440 join block, e.g. if join block has 2 predecessors with predicates
441 p1 & p2 and p1 & !p2, we'd like to get p1 for it instead of
442 p1 & p2 | p1 & !p2. */
443 if (dom_bb != loop->header
444 && get_immediate_dominator (CDI_POST_DOMINATORS, dom_bb) == bb)
446 gcc_assert (flow_bb_inside_loop_p (loop, dom_bb));
447 bc = bb_predicate (dom_bb);
448 if (!is_true_predicate (bc))
449 set_bb_predicate (bb, bc);
450 else
451 gcc_assert (is_true_predicate (bb_predicate (bb)));
452 if (dump_file && (dump_flags & TDF_DETAILS))
453 fprintf (dump_file, "Use predicate of bb#%d for bb#%d\n",
454 dom_bb->index, bb->index);
455 return;
458 if (!is_predicated (bb))
459 bc = nc;
460 else
462 bc = bb_predicate (bb);
463 bc = fold_or_predicates (EXPR_LOCATION (bc), nc, bc);
464 if (is_true_predicate (bc))
466 reset_bb_predicate (bb);
467 return;
471 /* Allow a TRUTH_NOT_EXPR around the main predicate. */
472 if (TREE_CODE (bc) == TRUTH_NOT_EXPR)
473 tp = &TREE_OPERAND (bc, 0);
474 else
475 tp = &bc;
476 if (!is_gimple_condexpr (*tp))
478 gimple_seq stmts;
479 *tp = force_gimple_operand_1 (*tp, &stmts, is_gimple_condexpr, NULL_TREE);
480 add_bb_predicate_gimplified_stmts (bb, stmts);
482 set_bb_predicate (bb, bc);
485 /* Add the condition COND to the previous condition PREV_COND, and add
486 this to the predicate list of the destination of edge E. LOOP is
487 the loop to be if-converted. */
489 static void
490 add_to_dst_predicate_list (struct loop *loop, edge e,
491 tree prev_cond, tree cond)
493 if (!flow_bb_inside_loop_p (loop, e->dest))
494 return;
496 if (!is_true_predicate (prev_cond))
497 cond = fold_build2 (TRUTH_AND_EXPR, boolean_type_node,
498 prev_cond, cond);
500 if (!dominated_by_p (CDI_DOMINATORS, loop->latch, e->dest))
501 add_to_predicate_list (loop, e->dest, cond);
504 /* Return true if one of the successor edges of BB exits LOOP. */
506 static bool
507 bb_with_exit_edge_p (struct loop *loop, basic_block bb)
509 edge e;
510 edge_iterator ei;
512 FOR_EACH_EDGE (e, ei, bb->succs)
513 if (loop_exit_edge_p (loop, e))
514 return true;
516 return false;
519 /* Return true when PHI is if-convertible. PHI is part of loop LOOP
520 and it belongs to basic block BB.
522 PHI is not if-convertible if:
523 - it has more than 2 arguments.
525 When the flag_tree_loop_if_convert_stores is not set, PHI is not
526 if-convertible if:
527 - a virtual PHI is immediately used in another PHI node,
528 - there is a virtual PHI in a BB other than the loop->header.
529 When the aggressive_if_conv is set, PHI can have more than
530 two arguments. */
532 static bool
533 if_convertible_phi_p (struct loop *loop, basic_block bb, gphi *phi,
534 bool any_mask_load_store)
536 if (dump_file && (dump_flags & TDF_DETAILS))
538 fprintf (dump_file, "-------------------------\n");
539 print_gimple_stmt (dump_file, phi, 0, TDF_SLIM);
542 if (bb != loop->header)
544 if (gimple_phi_num_args (phi) != 2
545 && !aggressive_if_conv)
547 if (dump_file && (dump_flags & TDF_DETAILS))
548 fprintf (dump_file, "More than two phi node args.\n");
549 return false;
553 if (flag_tree_loop_if_convert_stores || any_mask_load_store)
554 return true;
556 /* When the flag_tree_loop_if_convert_stores is not set, check
557 that there are no memory writes in the branches of the loop to be
558 if-converted. */
559 if (virtual_operand_p (gimple_phi_result (phi)))
561 imm_use_iterator imm_iter;
562 use_operand_p use_p;
564 if (bb != loop->header)
566 if (dump_file && (dump_flags & TDF_DETAILS))
567 fprintf (dump_file, "Virtual phi not on loop->header.\n");
568 return false;
571 FOR_EACH_IMM_USE_FAST (use_p, imm_iter, gimple_phi_result (phi))
573 if (gimple_code (USE_STMT (use_p)) == GIMPLE_PHI
574 && USE_STMT (use_p) != phi)
576 if (dump_file && (dump_flags & TDF_DETAILS))
577 fprintf (dump_file, "Difficult to handle this virtual phi.\n");
578 return false;
583 return true;
586 /* Records the status of a data reference. This struct is attached to
587 each DR->aux field. */
589 struct ifc_dr {
590 /* -1 when not initialized, 0 when false, 1 when true. */
591 int written_at_least_once;
593 /* -1 when not initialized, 0 when false, 1 when true. */
594 int rw_unconditionally;
597 #define IFC_DR(DR) ((struct ifc_dr *) (DR)->aux)
598 #define DR_WRITTEN_AT_LEAST_ONCE(DR) (IFC_DR (DR)->written_at_least_once)
599 #define DR_RW_UNCONDITIONALLY(DR) (IFC_DR (DR)->rw_unconditionally)
601 /* Returns true when the memory references of STMT are read or written
602 unconditionally. In other words, this function returns true when
603 for every data reference A in STMT there exist other accesses to
604 a data reference with the same base with predicates that add up (OR-up) to
605 the true predicate: this ensures that the data reference A is touched
606 (read or written) on every iteration of the if-converted loop. */
608 static bool
609 memrefs_read_or_written_unconditionally (gimple *stmt,
610 vec<data_reference_p> drs)
612 int i, j;
613 data_reference_p a, b;
614 tree ca = bb_predicate (gimple_bb (stmt));
616 for (i = 0; drs.iterate (i, &a); i++)
617 if (DR_STMT (a) == stmt)
619 bool found = false;
620 int x = DR_RW_UNCONDITIONALLY (a);
622 if (x == 0)
623 return false;
625 if (x == 1)
626 continue;
628 for (j = 0; drs.iterate (j, &b); j++)
630 tree ref_base_a = DR_REF (a);
631 tree ref_base_b = DR_REF (b);
633 if (DR_STMT (b) == stmt)
634 continue;
636 while (TREE_CODE (ref_base_a) == COMPONENT_REF
637 || TREE_CODE (ref_base_a) == IMAGPART_EXPR
638 || TREE_CODE (ref_base_a) == REALPART_EXPR)
639 ref_base_a = TREE_OPERAND (ref_base_a, 0);
641 while (TREE_CODE (ref_base_b) == COMPONENT_REF
642 || TREE_CODE (ref_base_b) == IMAGPART_EXPR
643 || TREE_CODE (ref_base_b) == REALPART_EXPR)
644 ref_base_b = TREE_OPERAND (ref_base_b, 0);
646 if (operand_equal_p (ref_base_a, ref_base_b, 0))
648 tree cb = bb_predicate (gimple_bb (DR_STMT (b)));
650 if (DR_RW_UNCONDITIONALLY (b) == 1
651 || is_true_predicate (cb)
652 || is_true_predicate (ca
653 = fold_or_predicates (EXPR_LOCATION (cb), ca, cb)))
655 DR_RW_UNCONDITIONALLY (a) = 1;
656 DR_RW_UNCONDITIONALLY (b) = 1;
657 found = true;
658 break;
663 if (!found)
665 DR_RW_UNCONDITIONALLY (a) = 0;
666 return false;
670 return true;
673 /* Returns true when the memory references of STMT are unconditionally
674 written. In other words, this function returns true when for every
675 data reference A written in STMT, there exist other writes to the
676 same data reference with predicates that add up (OR-up) to the true
677 predicate: this ensures that the data reference A is written on
678 every iteration of the if-converted loop. */
680 static bool
681 write_memrefs_written_at_least_once (gimple *stmt,
682 vec<data_reference_p> drs)
684 int i, j;
685 data_reference_p a, b;
686 tree ca = bb_predicate (gimple_bb (stmt));
688 for (i = 0; drs.iterate (i, &a); i++)
689 if (DR_STMT (a) == stmt
690 && DR_IS_WRITE (a))
692 bool found = false;
693 int x = DR_WRITTEN_AT_LEAST_ONCE (a);
695 if (x == 0)
696 return false;
698 if (x == 1)
699 continue;
701 for (j = 0; drs.iterate (j, &b); j++)
702 if (DR_STMT (b) != stmt
703 && DR_IS_WRITE (b)
704 && same_data_refs_base_objects (a, b))
706 tree cb = bb_predicate (gimple_bb (DR_STMT (b)));
708 if (DR_WRITTEN_AT_LEAST_ONCE (b) == 1
709 || is_true_predicate (cb)
710 || is_true_predicate (ca = fold_or_predicates (EXPR_LOCATION (cb),
711 ca, cb)))
713 DR_WRITTEN_AT_LEAST_ONCE (a) = 1;
714 DR_WRITTEN_AT_LEAST_ONCE (b) = 1;
715 found = true;
716 break;
720 if (!found)
722 DR_WRITTEN_AT_LEAST_ONCE (a) = 0;
723 return false;
727 return true;
730 /* Return true when the memory references of STMT won't trap in the
731 if-converted code. There are two things that we have to check for:
733 - writes to memory occur to writable memory: if-conversion of
734 memory writes transforms the conditional memory writes into
735 unconditional writes, i.e. "if (cond) A[i] = foo" is transformed
736 into "A[i] = cond ? foo : A[i]", and as the write to memory may not
737 be executed at all in the original code, it may be a readonly
738 memory. To check that A is not const-qualified, we check that
739 there exists at least an unconditional write to A in the current
740 function.
742 - reads or writes to memory are valid memory accesses for every
743 iteration. To check that the memory accesses are correctly formed
744 and that we are allowed to read and write in these locations, we
745 check that the memory accesses to be if-converted occur at every
746 iteration unconditionally. */
748 static bool
749 ifcvt_memrefs_wont_trap (gimple *stmt, vec<data_reference_p> refs)
751 return write_memrefs_written_at_least_once (stmt, refs)
752 && memrefs_read_or_written_unconditionally (stmt, refs);
755 /* Wrapper around gimple_could_trap_p refined for the needs of the
756 if-conversion. Try to prove that the memory accesses of STMT could
757 not trap in the innermost loop containing STMT. */
759 static bool
760 ifcvt_could_trap_p (gimple *stmt, vec<data_reference_p> refs)
762 if (gimple_vuse (stmt)
763 && !gimple_could_trap_p_1 (stmt, false, false)
764 && ifcvt_memrefs_wont_trap (stmt, refs))
765 return false;
767 return gimple_could_trap_p (stmt);
770 /* Return true if STMT could be converted into a masked load or store
771 (conditional load or store based on a mask computed from bb predicate). */
773 static bool
774 ifcvt_can_use_mask_load_store (gimple *stmt)
776 tree lhs, ref;
777 machine_mode mode;
778 basic_block bb = gimple_bb (stmt);
779 bool is_load;
781 if (!(flag_tree_loop_vectorize || bb->loop_father->force_vectorize)
782 || bb->loop_father->dont_vectorize
783 || !gimple_assign_single_p (stmt)
784 || gimple_has_volatile_ops (stmt))
785 return false;
787 /* Check whether this is a load or store. */
788 lhs = gimple_assign_lhs (stmt);
789 if (gimple_store_p (stmt))
791 if (!is_gimple_val (gimple_assign_rhs1 (stmt)))
792 return false;
793 is_load = false;
794 ref = lhs;
796 else if (gimple_assign_load_p (stmt))
798 is_load = true;
799 ref = gimple_assign_rhs1 (stmt);
801 else
802 return false;
804 if (may_be_nonaddressable_p (ref))
805 return false;
807 /* Mask should be integer mode of the same size as the load/store
808 mode. */
809 mode = TYPE_MODE (TREE_TYPE (lhs));
810 if (int_mode_for_mode (mode) == BLKmode
811 || VECTOR_MODE_P (mode))
812 return false;
814 if (can_vec_mask_load_store_p (mode, is_load))
815 return true;
817 return false;
820 /* Return true when STMT is if-convertible.
822 GIMPLE_ASSIGN statement is not if-convertible if,
823 - it is not movable,
824 - it could trap,
825 - LHS is not var decl. */
827 static bool
828 if_convertible_gimple_assign_stmt_p (gimple *stmt,
829 vec<data_reference_p> refs,
830 bool *any_mask_load_store)
832 tree lhs = gimple_assign_lhs (stmt);
833 basic_block bb;
835 if (dump_file && (dump_flags & TDF_DETAILS))
837 fprintf (dump_file, "-------------------------\n");
838 print_gimple_stmt (dump_file, stmt, 0, TDF_SLIM);
841 if (!is_gimple_reg_type (TREE_TYPE (lhs)))
842 return false;
844 /* Some of these constrains might be too conservative. */
845 if (stmt_ends_bb_p (stmt)
846 || gimple_has_volatile_ops (stmt)
847 || (TREE_CODE (lhs) == SSA_NAME
848 && SSA_NAME_OCCURS_IN_ABNORMAL_PHI (lhs))
849 || gimple_has_side_effects (stmt))
851 if (dump_file && (dump_flags & TDF_DETAILS))
852 fprintf (dump_file, "stmt not suitable for ifcvt\n");
853 return false;
856 /* tree-into-ssa.c uses GF_PLF_1, so avoid it, because
857 in between if_convertible_loop_p and combine_blocks
858 we can perform loop versioning. */
859 gimple_set_plf (stmt, GF_PLF_2, false);
861 if (flag_tree_loop_if_convert_stores)
863 if (ifcvt_could_trap_p (stmt, refs))
865 if (ifcvt_can_use_mask_load_store (stmt))
867 gimple_set_plf (stmt, GF_PLF_2, true);
868 *any_mask_load_store = true;
869 return true;
871 if (dump_file && (dump_flags & TDF_DETAILS))
872 fprintf (dump_file, "tree could trap...\n");
873 return false;
875 return true;
878 if (ifcvt_could_trap_p (stmt, refs))
880 if (ifcvt_can_use_mask_load_store (stmt))
882 gimple_set_plf (stmt, GF_PLF_2, true);
883 *any_mask_load_store = true;
884 return true;
886 if (dump_file && (dump_flags & TDF_DETAILS))
887 fprintf (dump_file, "tree could trap...\n");
888 return false;
891 bb = gimple_bb (stmt);
893 if (TREE_CODE (lhs) != SSA_NAME
894 && bb != bb->loop_father->header
895 && !bb_with_exit_edge_p (bb->loop_father, bb))
897 if (ifcvt_can_use_mask_load_store (stmt))
899 gimple_set_plf (stmt, GF_PLF_2, true);
900 *any_mask_load_store = true;
901 return true;
903 if (dump_file && (dump_flags & TDF_DETAILS))
905 fprintf (dump_file, "LHS is not var\n");
906 print_gimple_stmt (dump_file, stmt, 0, TDF_SLIM);
908 return false;
911 return true;
914 /* Return true when STMT is if-convertible.
916 A statement is if-convertible if:
917 - it is an if-convertible GIMPLE_ASSIGN,
918 - it is a GIMPLE_LABEL or a GIMPLE_COND,
919 - it is builtins call. */
921 static bool
922 if_convertible_stmt_p (gimple *stmt, vec<data_reference_p> refs,
923 bool *any_mask_load_store)
925 switch (gimple_code (stmt))
927 case GIMPLE_LABEL:
928 case GIMPLE_DEBUG:
929 case GIMPLE_COND:
930 return true;
932 case GIMPLE_ASSIGN:
933 return if_convertible_gimple_assign_stmt_p (stmt, refs,
934 any_mask_load_store);
936 case GIMPLE_CALL:
938 tree fndecl = gimple_call_fndecl (stmt);
939 if (fndecl)
941 int flags = gimple_call_flags (stmt);
942 if ((flags & ECF_CONST)
943 && !(flags & ECF_LOOPING_CONST_OR_PURE)
944 /* We can only vectorize some builtins at the moment,
945 so restrict if-conversion to those. */
946 && DECL_BUILT_IN (fndecl))
947 return true;
949 return false;
952 default:
953 /* Don't know what to do with 'em so don't do anything. */
954 if (dump_file && (dump_flags & TDF_DETAILS))
956 fprintf (dump_file, "don't know what to do\n");
957 print_gimple_stmt (dump_file, stmt, 0, TDF_SLIM);
959 return false;
960 break;
963 return true;
966 /* Assumes that BB has more than 1 predecessors.
967 Returns false if at least one successor is not on critical edge
968 and true otherwise. */
970 static inline bool
971 all_preds_critical_p (basic_block bb)
973 edge e;
974 edge_iterator ei;
976 FOR_EACH_EDGE (e, ei, bb->preds)
977 if (EDGE_COUNT (e->src->succs) == 1)
978 return false;
979 return true;
982 /* Returns true if at least one successor in on critical edge. */
983 static inline bool
984 has_pred_critical_p (basic_block bb)
986 edge e;
987 edge_iterator ei;
989 FOR_EACH_EDGE (e, ei, bb->preds)
990 if (EDGE_COUNT (e->src->succs) > 1)
991 return true;
992 return false;
995 /* Return true when BB is if-convertible. This routine does not check
996 basic block's statements and phis.
998 A basic block is not if-convertible if:
999 - it is non-empty and it is after the exit block (in BFS order),
1000 - it is after the exit block but before the latch,
1001 - its edges are not normal.
1003 Last restriction is valid if aggressive_if_conv is false.
1005 EXIT_BB is the basic block containing the exit of the LOOP. BB is
1006 inside LOOP. */
1008 static bool
1009 if_convertible_bb_p (struct loop *loop, basic_block bb, basic_block exit_bb)
1011 edge e;
1012 edge_iterator ei;
1014 if (dump_file && (dump_flags & TDF_DETAILS))
1015 fprintf (dump_file, "----------[%d]-------------\n", bb->index);
1017 if (EDGE_COUNT (bb->succs) > 2)
1018 return false;
1020 if (EDGE_COUNT (bb->preds) > 2
1021 && !aggressive_if_conv)
1022 return false;
1024 if (exit_bb)
1026 if (bb != loop->latch)
1028 if (dump_file && (dump_flags & TDF_DETAILS))
1029 fprintf (dump_file, "basic block after exit bb but before latch\n");
1030 return false;
1032 else if (!empty_block_p (bb))
1034 if (dump_file && (dump_flags & TDF_DETAILS))
1035 fprintf (dump_file, "non empty basic block after exit bb\n");
1036 return false;
1038 else if (bb == loop->latch
1039 && bb != exit_bb
1040 && !dominated_by_p (CDI_DOMINATORS, bb, exit_bb))
1042 if (dump_file && (dump_flags & TDF_DETAILS))
1043 fprintf (dump_file, "latch is not dominated by exit_block\n");
1044 return false;
1048 /* Be less adventurous and handle only normal edges. */
1049 FOR_EACH_EDGE (e, ei, bb->succs)
1050 if (e->flags & (EDGE_EH | EDGE_ABNORMAL | EDGE_IRREDUCIBLE_LOOP))
1052 if (dump_file && (dump_flags & TDF_DETAILS))
1053 fprintf (dump_file, "Difficult to handle edges\n");
1054 return false;
1057 /* At least one incoming edge has to be non-critical as otherwise edge
1058 predicates are not equal to basic-block predicates of the edge
1059 source. This check is skipped if aggressive_if_conv is true. */
1060 if (!aggressive_if_conv
1061 && EDGE_COUNT (bb->preds) > 1
1062 && bb != loop->header
1063 && all_preds_critical_p (bb))
1065 if (dump_file && (dump_flags & TDF_DETAILS))
1066 fprintf (dump_file, "only critical predecessors\n");
1067 return false;
1070 return true;
1073 /* Return true when all predecessor blocks of BB are visited. The
1074 VISITED bitmap keeps track of the visited blocks. */
1076 static bool
1077 pred_blocks_visited_p (basic_block bb, bitmap *visited)
1079 edge e;
1080 edge_iterator ei;
1081 FOR_EACH_EDGE (e, ei, bb->preds)
1082 if (!bitmap_bit_p (*visited, e->src->index))
1083 return false;
1085 return true;
1088 /* Get body of a LOOP in suitable order for if-conversion. It is
1089 caller's responsibility to deallocate basic block list.
1090 If-conversion suitable order is, breadth first sort (BFS) order
1091 with an additional constraint: select a block only if all its
1092 predecessors are already selected. */
1094 static basic_block *
1095 get_loop_body_in_if_conv_order (const struct loop *loop)
1097 basic_block *blocks, *blocks_in_bfs_order;
1098 basic_block bb;
1099 bitmap visited;
1100 unsigned int index = 0;
1101 unsigned int visited_count = 0;
1103 gcc_assert (loop->num_nodes);
1104 gcc_assert (loop->latch != EXIT_BLOCK_PTR_FOR_FN (cfun));
1106 blocks = XCNEWVEC (basic_block, loop->num_nodes);
1107 visited = BITMAP_ALLOC (NULL);
1109 blocks_in_bfs_order = get_loop_body_in_bfs_order (loop);
1111 index = 0;
1112 while (index < loop->num_nodes)
1114 bb = blocks_in_bfs_order [index];
1116 if (bb->flags & BB_IRREDUCIBLE_LOOP)
1118 free (blocks_in_bfs_order);
1119 BITMAP_FREE (visited);
1120 free (blocks);
1121 return NULL;
1124 if (!bitmap_bit_p (visited, bb->index))
1126 if (pred_blocks_visited_p (bb, &visited)
1127 || bb == loop->header)
1129 /* This block is now visited. */
1130 bitmap_set_bit (visited, bb->index);
1131 blocks[visited_count++] = bb;
1135 index++;
1137 if (index == loop->num_nodes
1138 && visited_count != loop->num_nodes)
1139 /* Not done yet. */
1140 index = 0;
1142 free (blocks_in_bfs_order);
1143 BITMAP_FREE (visited);
1144 return blocks;
1147 /* Returns true when the analysis of the predicates for all the basic
1148 blocks in LOOP succeeded.
1150 predicate_bbs first allocates the predicates of the basic blocks.
1151 These fields are then initialized with the tree expressions
1152 representing the predicates under which a basic block is executed
1153 in the LOOP. As the loop->header is executed at each iteration, it
1154 has the "true" predicate. Other statements executed under a
1155 condition are predicated with that condition, for example
1157 | if (x)
1158 | S1;
1159 | else
1160 | S2;
1162 S1 will be predicated with "x", and
1163 S2 will be predicated with "!x". */
1165 static void
1166 predicate_bbs (loop_p loop)
1168 unsigned int i;
1170 for (i = 0; i < loop->num_nodes; i++)
1171 init_bb_predicate (ifc_bbs[i]);
1173 for (i = 0; i < loop->num_nodes; i++)
1175 basic_block bb = ifc_bbs[i];
1176 tree cond;
1177 gimple *stmt;
1179 /* The loop latch and loop exit block are always executed and
1180 have no extra conditions to be processed: skip them. */
1181 if (bb == loop->latch
1182 || bb_with_exit_edge_p (loop, bb))
1184 reset_bb_predicate (bb);
1185 continue;
1188 cond = bb_predicate (bb);
1189 stmt = last_stmt (bb);
1190 if (stmt && gimple_code (stmt) == GIMPLE_COND)
1192 tree c2;
1193 edge true_edge, false_edge;
1194 location_t loc = gimple_location (stmt);
1195 tree c = build2_loc (loc, gimple_cond_code (stmt),
1196 boolean_type_node,
1197 gimple_cond_lhs (stmt),
1198 gimple_cond_rhs (stmt));
1200 /* Add new condition into destination's predicate list. */
1201 extract_true_false_edges_from_block (gimple_bb (stmt),
1202 &true_edge, &false_edge);
1204 /* If C is true, then TRUE_EDGE is taken. */
1205 add_to_dst_predicate_list (loop, true_edge, unshare_expr (cond),
1206 unshare_expr (c));
1208 /* If C is false, then FALSE_EDGE is taken. */
1209 c2 = build1_loc (loc, TRUTH_NOT_EXPR, boolean_type_node,
1210 unshare_expr (c));
1211 add_to_dst_predicate_list (loop, false_edge,
1212 unshare_expr (cond), c2);
1214 cond = NULL_TREE;
1217 /* If current bb has only one successor, then consider it as an
1218 unconditional goto. */
1219 if (single_succ_p (bb))
1221 basic_block bb_n = single_succ (bb);
1223 /* The successor bb inherits the predicate of its
1224 predecessor. If there is no predicate in the predecessor
1225 bb, then consider the successor bb as always executed. */
1226 if (cond == NULL_TREE)
1227 cond = boolean_true_node;
1229 add_to_predicate_list (loop, bb_n, cond);
1233 /* The loop header is always executed. */
1234 reset_bb_predicate (loop->header);
1235 gcc_assert (bb_predicate_gimplified_stmts (loop->header) == NULL
1236 && bb_predicate_gimplified_stmts (loop->latch) == NULL);
1239 /* Return true when LOOP is if-convertible. This is a helper function
1240 for if_convertible_loop_p. REFS and DDRS are initialized and freed
1241 in if_convertible_loop_p. */
1243 static bool
1244 if_convertible_loop_p_1 (struct loop *loop,
1245 vec<loop_p> *loop_nest,
1246 vec<data_reference_p> *refs,
1247 vec<ddr_p> *ddrs, bool *any_mask_load_store)
1249 bool res;
1250 unsigned int i;
1251 basic_block exit_bb = NULL;
1253 /* Don't if-convert the loop when the data dependences cannot be
1254 computed: the loop won't be vectorized in that case. */
1255 res = compute_data_dependences_for_loop (loop, true, loop_nest, refs, ddrs);
1256 if (!res)
1257 return false;
1259 calculate_dominance_info (CDI_DOMINATORS);
1260 calculate_dominance_info (CDI_POST_DOMINATORS);
1262 /* Allow statements that can be handled during if-conversion. */
1263 ifc_bbs = get_loop_body_in_if_conv_order (loop);
1264 if (!ifc_bbs)
1266 if (dump_file && (dump_flags & TDF_DETAILS))
1267 fprintf (dump_file, "Irreducible loop\n");
1268 return false;
1271 for (i = 0; i < loop->num_nodes; i++)
1273 basic_block bb = ifc_bbs[i];
1275 if (!if_convertible_bb_p (loop, bb, exit_bb))
1276 return false;
1278 if (bb_with_exit_edge_p (loop, bb))
1279 exit_bb = bb;
1282 for (i = 0; i < loop->num_nodes; i++)
1284 basic_block bb = ifc_bbs[i];
1285 gimple_stmt_iterator gsi;
1287 for (gsi = gsi_start_bb (bb); !gsi_end_p (gsi); gsi_next (&gsi))
1288 switch (gimple_code (gsi_stmt (gsi)))
1290 case GIMPLE_LABEL:
1291 case GIMPLE_ASSIGN:
1292 case GIMPLE_CALL:
1293 case GIMPLE_DEBUG:
1294 case GIMPLE_COND:
1295 break;
1296 default:
1297 return false;
1301 data_reference_p dr;
1303 for (i = 0; refs->iterate (i, &dr); i++)
1305 dr->aux = XNEW (struct ifc_dr);
1306 DR_WRITTEN_AT_LEAST_ONCE (dr) = -1;
1307 DR_RW_UNCONDITIONALLY (dr) = -1;
1309 predicate_bbs (loop);
1311 for (i = 0; i < loop->num_nodes; i++)
1313 basic_block bb = ifc_bbs[i];
1314 gimple_stmt_iterator itr;
1316 /* Check the if-convertibility of statements in predicated BBs. */
1317 if (!dominated_by_p (CDI_DOMINATORS, loop->latch, bb))
1318 for (itr = gsi_start_bb (bb); !gsi_end_p (itr); gsi_next (&itr))
1319 if (!if_convertible_stmt_p (gsi_stmt (itr), *refs,
1320 any_mask_load_store))
1321 return false;
1324 for (i = 0; i < loop->num_nodes; i++)
1325 free_bb_predicate (ifc_bbs[i]);
1327 /* Checking PHIs needs to be done after stmts, as the fact whether there
1328 are any masked loads or stores affects the tests. */
1329 for (i = 0; i < loop->num_nodes; i++)
1331 basic_block bb = ifc_bbs[i];
1332 gphi_iterator itr;
1334 for (itr = gsi_start_phis (bb); !gsi_end_p (itr); gsi_next (&itr))
1335 if (!if_convertible_phi_p (loop, bb, itr.phi (),
1336 *any_mask_load_store))
1337 return false;
1340 if (dump_file)
1341 fprintf (dump_file, "Applying if-conversion\n");
1343 return true;
1346 /* Return true when LOOP is if-convertible.
1347 LOOP is if-convertible if:
1348 - it is innermost,
1349 - it has two or more basic blocks,
1350 - it has only one exit,
1351 - loop header is not the exit edge,
1352 - if its basic blocks and phi nodes are if convertible. */
1354 static bool
1355 if_convertible_loop_p (struct loop *loop, bool *any_mask_load_store)
1357 edge e;
1358 edge_iterator ei;
1359 bool res = false;
1360 vec<data_reference_p> refs;
1361 vec<ddr_p> ddrs;
1363 /* Handle only innermost loop. */
1364 if (!loop || loop->inner)
1366 if (dump_file && (dump_flags & TDF_DETAILS))
1367 fprintf (dump_file, "not innermost loop\n");
1368 return false;
1371 /* If only one block, no need for if-conversion. */
1372 if (loop->num_nodes <= 2)
1374 if (dump_file && (dump_flags & TDF_DETAILS))
1375 fprintf (dump_file, "less than 2 basic blocks\n");
1376 return false;
1379 /* More than one loop exit is too much to handle. */
1380 if (!single_exit (loop))
1382 if (dump_file && (dump_flags & TDF_DETAILS))
1383 fprintf (dump_file, "multiple exits\n");
1384 return false;
1387 /* If one of the loop header's edge is an exit edge then do not
1388 apply if-conversion. */
1389 FOR_EACH_EDGE (e, ei, loop->header->succs)
1390 if (loop_exit_edge_p (loop, e))
1391 return false;
1393 refs.create (5);
1394 ddrs.create (25);
1395 auto_vec<loop_p, 3> loop_nest;
1396 res = if_convertible_loop_p_1 (loop, &loop_nest, &refs, &ddrs,
1397 any_mask_load_store);
1399 data_reference_p dr;
1400 unsigned int i;
1401 for (i = 0; refs.iterate (i, &dr); i++)
1402 free (dr->aux);
1404 free_data_refs (refs);
1405 free_dependence_relations (ddrs);
1406 return res;
1409 /* Returns true if def-stmt for phi argument ARG is simple increment/decrement
1410 which is in predicated basic block.
1411 In fact, the following PHI pattern is searching:
1412 loop-header:
1413 reduc_1 = PHI <..., reduc_2>
1415 if (...)
1416 reduc_3 = ...
1417 reduc_2 = PHI <reduc_1, reduc_3>
1419 ARG_0 and ARG_1 are correspondent PHI arguments.
1420 REDUC, OP0 and OP1 contain reduction stmt and its operands.
1421 EXTENDED is true if PHI has > 2 arguments. */
1423 static bool
1424 is_cond_scalar_reduction (gimple *phi, gimple **reduc, tree arg_0, tree arg_1,
1425 tree *op0, tree *op1, bool extended)
1427 tree lhs, r_op1, r_op2;
1428 gimple *stmt;
1429 gimple *header_phi = NULL;
1430 enum tree_code reduction_op;
1431 basic_block bb = gimple_bb (phi);
1432 struct loop *loop = bb->loop_father;
1433 edge latch_e = loop_latch_edge (loop);
1434 imm_use_iterator imm_iter;
1435 use_operand_p use_p;
1436 edge e;
1437 edge_iterator ei;
1438 bool result = false;
1439 if (TREE_CODE (arg_0) != SSA_NAME || TREE_CODE (arg_1) != SSA_NAME)
1440 return false;
1442 if (!extended && gimple_code (SSA_NAME_DEF_STMT (arg_0)) == GIMPLE_PHI)
1444 lhs = arg_1;
1445 header_phi = SSA_NAME_DEF_STMT (arg_0);
1446 stmt = SSA_NAME_DEF_STMT (arg_1);
1448 else if (gimple_code (SSA_NAME_DEF_STMT (arg_1)) == GIMPLE_PHI)
1450 lhs = arg_0;
1451 header_phi = SSA_NAME_DEF_STMT (arg_1);
1452 stmt = SSA_NAME_DEF_STMT (arg_0);
1454 else
1455 return false;
1456 if (gimple_bb (header_phi) != loop->header)
1457 return false;
1459 if (PHI_ARG_DEF_FROM_EDGE (header_phi, latch_e) != PHI_RESULT (phi))
1460 return false;
1462 if (gimple_code (stmt) != GIMPLE_ASSIGN
1463 || gimple_has_volatile_ops (stmt))
1464 return false;
1466 if (!flow_bb_inside_loop_p (loop, gimple_bb (stmt)))
1467 return false;
1469 if (!is_predicated (gimple_bb (stmt)))
1470 return false;
1472 /* Check that stmt-block is predecessor of phi-block. */
1473 FOR_EACH_EDGE (e, ei, gimple_bb (stmt)->succs)
1474 if (e->dest == bb)
1476 result = true;
1477 break;
1479 if (!result)
1480 return false;
1482 if (!has_single_use (lhs))
1483 return false;
1485 reduction_op = gimple_assign_rhs_code (stmt);
1486 if (reduction_op != PLUS_EXPR && reduction_op != MINUS_EXPR)
1487 return false;
1488 r_op1 = gimple_assign_rhs1 (stmt);
1489 r_op2 = gimple_assign_rhs2 (stmt);
1491 /* Make R_OP1 to hold reduction variable. */
1492 if (r_op2 == PHI_RESULT (header_phi)
1493 && reduction_op == PLUS_EXPR)
1494 std::swap (r_op1, r_op2);
1495 else if (r_op1 != PHI_RESULT (header_phi))
1496 return false;
1498 /* Check that R_OP1 is used in reduction stmt or in PHI only. */
1499 FOR_EACH_IMM_USE_FAST (use_p, imm_iter, r_op1)
1501 gimple *use_stmt = USE_STMT (use_p);
1502 if (is_gimple_debug (use_stmt))
1503 continue;
1504 if (use_stmt == stmt)
1505 continue;
1506 if (gimple_code (use_stmt) != GIMPLE_PHI)
1507 return false;
1510 *op0 = r_op1; *op1 = r_op2;
1511 *reduc = stmt;
1512 return true;
1515 /* Converts conditional scalar reduction into unconditional form, e.g.
1516 bb_4
1517 if (_5 != 0) goto bb_5 else goto bb_6
1518 end_bb_4
1519 bb_5
1520 res_6 = res_13 + 1;
1521 end_bb_5
1522 bb_6
1523 # res_2 = PHI <res_13(4), res_6(5)>
1524 end_bb_6
1526 will be converted into sequence
1527 _ifc__1 = _5 != 0 ? 1 : 0;
1528 res_2 = res_13 + _ifc__1;
1529 Argument SWAP tells that arguments of conditional expression should be
1530 swapped.
1531 Returns rhs of resulting PHI assignment. */
1533 static tree
1534 convert_scalar_cond_reduction (gimple *reduc, gimple_stmt_iterator *gsi,
1535 tree cond, tree op0, tree op1, bool swap)
1537 gimple_stmt_iterator stmt_it;
1538 gimple *new_assign;
1539 tree rhs;
1540 tree rhs1 = gimple_assign_rhs1 (reduc);
1541 tree tmp = make_temp_ssa_name (TREE_TYPE (rhs1), NULL, "_ifc_");
1542 tree c;
1543 tree zero = build_zero_cst (TREE_TYPE (rhs1));
1545 if (dump_file && (dump_flags & TDF_DETAILS))
1547 fprintf (dump_file, "Found cond scalar reduction.\n");
1548 print_gimple_stmt (dump_file, reduc, 0, TDF_SLIM);
1551 /* Build cond expression using COND and constant operand
1552 of reduction rhs. */
1553 c = fold_build_cond_expr (TREE_TYPE (rhs1),
1554 unshare_expr (cond),
1555 swap ? zero : op1,
1556 swap ? op1 : zero);
1558 /* Create assignment stmt and insert it at GSI. */
1559 new_assign = gimple_build_assign (tmp, c);
1560 gsi_insert_before (gsi, new_assign, GSI_SAME_STMT);
1561 /* Build rhs for unconditional increment/decrement. */
1562 rhs = fold_build2 (gimple_assign_rhs_code (reduc),
1563 TREE_TYPE (rhs1), op0, tmp);
1565 /* Delete original reduction stmt. */
1566 stmt_it = gsi_for_stmt (reduc);
1567 gsi_remove (&stmt_it, true);
1568 release_defs (reduc);
1569 return rhs;
1572 /* Produce condition for all occurrences of ARG in PHI node. */
1574 static tree
1575 gen_phi_arg_condition (gphi *phi, vec<int> *occur,
1576 gimple_stmt_iterator *gsi)
1578 int len;
1579 int i;
1580 tree cond = NULL_TREE;
1581 tree c;
1582 edge e;
1584 len = occur->length ();
1585 gcc_assert (len > 0);
1586 for (i = 0; i < len; i++)
1588 e = gimple_phi_arg_edge (phi, (*occur)[i]);
1589 c = bb_predicate (e->src);
1590 if (is_true_predicate (c))
1591 continue;
1592 c = force_gimple_operand_gsi_1 (gsi, unshare_expr (c),
1593 is_gimple_condexpr, NULL_TREE,
1594 true, GSI_SAME_STMT);
1595 if (cond != NULL_TREE)
1597 /* Must build OR expression. */
1598 cond = fold_or_predicates (EXPR_LOCATION (c), c, cond);
1599 cond = force_gimple_operand_gsi_1 (gsi, unshare_expr (cond),
1600 is_gimple_condexpr, NULL_TREE,
1601 true, GSI_SAME_STMT);
1603 else
1604 cond = c;
1606 gcc_assert (cond != NULL_TREE);
1607 return cond;
1610 /* Replace a scalar PHI node with a COND_EXPR using COND as condition.
1611 This routine can handle PHI nodes with more than two arguments.
1613 For example,
1614 S1: A = PHI <x1(1), x2(5)>
1615 is converted into,
1616 S2: A = cond ? x1 : x2;
1618 The generated code is inserted at GSI that points to the top of
1619 basic block's statement list.
1620 If PHI node has more than two arguments a chain of conditional
1621 expression is produced. */
1624 static void
1625 predicate_scalar_phi (gphi *phi, gimple_stmt_iterator *gsi)
1627 gimple *new_stmt = NULL, *reduc;
1628 tree rhs, res, arg0, arg1, op0, op1, scev;
1629 tree cond;
1630 unsigned int index0;
1631 unsigned int max, args_len;
1632 edge e;
1633 basic_block bb;
1634 unsigned int i;
1636 res = gimple_phi_result (phi);
1637 if (virtual_operand_p (res))
1638 return;
1640 if ((rhs = degenerate_phi_result (phi))
1641 || ((scev = analyze_scalar_evolution (gimple_bb (phi)->loop_father,
1642 res))
1643 && !chrec_contains_undetermined (scev)
1644 && scev != res
1645 && (rhs = gimple_phi_arg_def (phi, 0))))
1647 if (dump_file && (dump_flags & TDF_DETAILS))
1649 fprintf (dump_file, "Degenerate phi!\n");
1650 print_gimple_stmt (dump_file, phi, 0, TDF_SLIM);
1652 new_stmt = gimple_build_assign (res, rhs);
1653 gsi_insert_before (gsi, new_stmt, GSI_SAME_STMT);
1654 update_stmt (new_stmt);
1655 return;
1658 bb = gimple_bb (phi);
1659 if (EDGE_COUNT (bb->preds) == 2)
1661 /* Predicate ordinary PHI node with 2 arguments. */
1662 edge first_edge, second_edge;
1663 basic_block true_bb;
1664 first_edge = EDGE_PRED (bb, 0);
1665 second_edge = EDGE_PRED (bb, 1);
1666 cond = bb_predicate (first_edge->src);
1667 if (TREE_CODE (cond) == TRUTH_NOT_EXPR)
1668 std::swap (first_edge, second_edge);
1669 if (EDGE_COUNT (first_edge->src->succs) > 1)
1671 cond = bb_predicate (second_edge->src);
1672 if (TREE_CODE (cond) == TRUTH_NOT_EXPR)
1673 cond = TREE_OPERAND (cond, 0);
1674 else
1675 first_edge = second_edge;
1677 else
1678 cond = bb_predicate (first_edge->src);
1679 /* Gimplify the condition to a valid cond-expr conditonal operand. */
1680 cond = force_gimple_operand_gsi_1 (gsi, unshare_expr (cond),
1681 is_gimple_condexpr, NULL_TREE,
1682 true, GSI_SAME_STMT);
1683 true_bb = first_edge->src;
1684 if (EDGE_PRED (bb, 1)->src == true_bb)
1686 arg0 = gimple_phi_arg_def (phi, 1);
1687 arg1 = gimple_phi_arg_def (phi, 0);
1689 else
1691 arg0 = gimple_phi_arg_def (phi, 0);
1692 arg1 = gimple_phi_arg_def (phi, 1);
1694 if (is_cond_scalar_reduction (phi, &reduc, arg0, arg1,
1695 &op0, &op1, false))
1696 /* Convert reduction stmt into vectorizable form. */
1697 rhs = convert_scalar_cond_reduction (reduc, gsi, cond, op0, op1,
1698 true_bb != gimple_bb (reduc));
1699 else
1700 /* Build new RHS using selected condition and arguments. */
1701 rhs = fold_build_cond_expr (TREE_TYPE (res), unshare_expr (cond),
1702 arg0, arg1);
1703 new_stmt = gimple_build_assign (res, rhs);
1704 gsi_insert_before (gsi, new_stmt, GSI_SAME_STMT);
1705 update_stmt (new_stmt);
1707 if (dump_file && (dump_flags & TDF_DETAILS))
1709 fprintf (dump_file, "new phi replacement stmt\n");
1710 print_gimple_stmt (dump_file, new_stmt, 0, TDF_SLIM);
1712 return;
1715 /* Create hashmap for PHI node which contain vector of argument indexes
1716 having the same value. */
1717 bool swap = false;
1718 hash_map<tree_operand_hash, auto_vec<int> > phi_arg_map;
1719 unsigned int num_args = gimple_phi_num_args (phi);
1720 int max_ind = -1;
1721 /* Vector of different PHI argument values. */
1722 auto_vec<tree> args (num_args);
1724 /* Compute phi_arg_map. */
1725 for (i = 0; i < num_args; i++)
1727 tree arg;
1729 arg = gimple_phi_arg_def (phi, i);
1730 if (!phi_arg_map.get (arg))
1731 args.quick_push (arg);
1732 phi_arg_map.get_or_insert (arg).safe_push (i);
1735 /* Determine element with max number of occurrences. */
1736 max_ind = -1;
1737 max = 1;
1738 args_len = args.length ();
1739 for (i = 0; i < args_len; i++)
1741 unsigned int len;
1742 if ((len = phi_arg_map.get (args[i])->length ()) > max)
1744 max_ind = (int) i;
1745 max = len;
1749 /* Put element with max number of occurences to the end of ARGS. */
1750 if (max_ind != -1 && max_ind +1 != (int) args_len)
1751 std::swap (args[args_len - 1], args[max_ind]);
1753 /* Handle one special case when number of arguments with different values
1754 is equal 2 and one argument has the only occurrence. Such PHI can be
1755 handled as if would have only 2 arguments. */
1756 if (args_len == 2 && phi_arg_map.get (args[0])->length () == 1)
1758 vec<int> *indexes;
1759 indexes = phi_arg_map.get (args[0]);
1760 index0 = (*indexes)[0];
1761 arg0 = args[0];
1762 arg1 = args[1];
1763 e = gimple_phi_arg_edge (phi, index0);
1764 cond = bb_predicate (e->src);
1765 if (TREE_CODE (cond) == TRUTH_NOT_EXPR)
1767 swap = true;
1768 cond = TREE_OPERAND (cond, 0);
1770 /* Gimplify the condition to a valid cond-expr conditonal operand. */
1771 cond = force_gimple_operand_gsi_1 (gsi, unshare_expr (cond),
1772 is_gimple_condexpr, NULL_TREE,
1773 true, GSI_SAME_STMT);
1774 if (!(is_cond_scalar_reduction (phi, &reduc, arg0 , arg1,
1775 &op0, &op1, true)))
1776 rhs = fold_build_cond_expr (TREE_TYPE (res), unshare_expr (cond),
1777 swap? arg1 : arg0,
1778 swap? arg0 : arg1);
1779 else
1780 /* Convert reduction stmt into vectorizable form. */
1781 rhs = convert_scalar_cond_reduction (reduc, gsi, cond, op0, op1,
1782 swap);
1783 new_stmt = gimple_build_assign (res, rhs);
1784 gsi_insert_before (gsi, new_stmt, GSI_SAME_STMT);
1785 update_stmt (new_stmt);
1787 else
1789 /* Common case. */
1790 vec<int> *indexes;
1791 tree type = TREE_TYPE (gimple_phi_result (phi));
1792 tree lhs;
1793 arg1 = args[1];
1794 for (i = 0; i < args_len; i++)
1796 arg0 = args[i];
1797 indexes = phi_arg_map.get (args[i]);
1798 if (i != args_len - 1)
1799 lhs = make_temp_ssa_name (type, NULL, "_ifc_");
1800 else
1801 lhs = res;
1802 cond = gen_phi_arg_condition (phi, indexes, gsi);
1803 rhs = fold_build_cond_expr (type, unshare_expr (cond),
1804 arg0, arg1);
1805 new_stmt = gimple_build_assign (lhs, rhs);
1806 gsi_insert_before (gsi, new_stmt, GSI_SAME_STMT);
1807 update_stmt (new_stmt);
1808 arg1 = lhs;
1812 if (dump_file && (dump_flags & TDF_DETAILS))
1814 fprintf (dump_file, "new extended phi replacement stmt\n");
1815 print_gimple_stmt (dump_file, new_stmt, 0, TDF_SLIM);
1819 /* Replaces in LOOP all the scalar phi nodes other than those in the
1820 LOOP->header block with conditional modify expressions. */
1822 static void
1823 predicate_all_scalar_phis (struct loop *loop)
1825 basic_block bb;
1826 unsigned int orig_loop_num_nodes = loop->num_nodes;
1827 unsigned int i;
1829 for (i = 1; i < orig_loop_num_nodes; i++)
1831 gphi *phi;
1832 gimple_stmt_iterator gsi;
1833 gphi_iterator phi_gsi;
1834 bb = ifc_bbs[i];
1836 if (bb == loop->header)
1837 continue;
1839 if (EDGE_COUNT (bb->preds) == 1)
1840 continue;
1842 phi_gsi = gsi_start_phis (bb);
1843 if (gsi_end_p (phi_gsi))
1844 continue;
1846 gsi = gsi_after_labels (bb);
1847 while (!gsi_end_p (phi_gsi))
1849 phi = phi_gsi.phi ();
1850 predicate_scalar_phi (phi, &gsi);
1851 release_phi_node (phi);
1852 gsi_next (&phi_gsi);
1855 set_phi_nodes (bb, NULL);
1859 /* Insert in each basic block of LOOP the statements produced by the
1860 gimplification of the predicates. */
1862 static void
1863 insert_gimplified_predicates (loop_p loop, bool any_mask_load_store)
1865 unsigned int i;
1867 for (i = 0; i < loop->num_nodes; i++)
1869 basic_block bb = ifc_bbs[i];
1870 gimple_seq stmts;
1871 if (!is_predicated (bb))
1872 gcc_assert (bb_predicate_gimplified_stmts (bb) == NULL);
1873 if (!is_predicated (bb))
1875 /* Do not insert statements for a basic block that is not
1876 predicated. Also make sure that the predicate of the
1877 basic block is set to true. */
1878 reset_bb_predicate (bb);
1879 continue;
1882 stmts = bb_predicate_gimplified_stmts (bb);
1883 if (stmts)
1885 if (flag_tree_loop_if_convert_stores
1886 || any_mask_load_store)
1888 /* Insert the predicate of the BB just after the label,
1889 as the if-conversion of memory writes will use this
1890 predicate. */
1891 gimple_stmt_iterator gsi = gsi_after_labels (bb);
1892 gsi_insert_seq_before (&gsi, stmts, GSI_SAME_STMT);
1894 else
1896 /* Insert the predicate of the BB at the end of the BB
1897 as this would reduce the register pressure: the only
1898 use of this predicate will be in successor BBs. */
1899 gimple_stmt_iterator gsi = gsi_last_bb (bb);
1901 if (gsi_end_p (gsi)
1902 || stmt_ends_bb_p (gsi_stmt (gsi)))
1903 gsi_insert_seq_before (&gsi, stmts, GSI_SAME_STMT);
1904 else
1905 gsi_insert_seq_after (&gsi, stmts, GSI_SAME_STMT);
1908 /* Once the sequence is code generated, set it to NULL. */
1909 set_bb_predicate_gimplified_stmts (bb, NULL);
1914 /* Helper function for predicate_mem_writes. Returns index of existent
1915 mask if it was created for given SIZE and -1 otherwise. */
1917 static int
1918 mask_exists (int size, vec<int> vec)
1920 unsigned int ix;
1921 int v;
1922 FOR_EACH_VEC_ELT (vec, ix, v)
1923 if (v == size)
1924 return (int) ix;
1925 return -1;
1928 /* Predicate each write to memory in LOOP.
1930 This function transforms control flow constructs containing memory
1931 writes of the form:
1933 | for (i = 0; i < N; i++)
1934 | if (cond)
1935 | A[i] = expr;
1937 into the following form that does not contain control flow:
1939 | for (i = 0; i < N; i++)
1940 | A[i] = cond ? expr : A[i];
1942 The original CFG looks like this:
1944 | bb_0
1945 | i = 0
1946 | end_bb_0
1948 | bb_1
1949 | if (i < N) goto bb_5 else goto bb_2
1950 | end_bb_1
1952 | bb_2
1953 | cond = some_computation;
1954 | if (cond) goto bb_3 else goto bb_4
1955 | end_bb_2
1957 | bb_3
1958 | A[i] = expr;
1959 | goto bb_4
1960 | end_bb_3
1962 | bb_4
1963 | goto bb_1
1964 | end_bb_4
1966 insert_gimplified_predicates inserts the computation of the COND
1967 expression at the beginning of the destination basic block:
1969 | bb_0
1970 | i = 0
1971 | end_bb_0
1973 | bb_1
1974 | if (i < N) goto bb_5 else goto bb_2
1975 | end_bb_1
1977 | bb_2
1978 | cond = some_computation;
1979 | if (cond) goto bb_3 else goto bb_4
1980 | end_bb_2
1982 | bb_3
1983 | cond = some_computation;
1984 | A[i] = expr;
1985 | goto bb_4
1986 | end_bb_3
1988 | bb_4
1989 | goto bb_1
1990 | end_bb_4
1992 predicate_mem_writes is then predicating the memory write as follows:
1994 | bb_0
1995 | i = 0
1996 | end_bb_0
1998 | bb_1
1999 | if (i < N) goto bb_5 else goto bb_2
2000 | end_bb_1
2002 | bb_2
2003 | if (cond) goto bb_3 else goto bb_4
2004 | end_bb_2
2006 | bb_3
2007 | cond = some_computation;
2008 | A[i] = cond ? expr : A[i];
2009 | goto bb_4
2010 | end_bb_3
2012 | bb_4
2013 | goto bb_1
2014 | end_bb_4
2016 and finally combine_blocks removes the basic block boundaries making
2017 the loop vectorizable:
2019 | bb_0
2020 | i = 0
2021 | if (i < N) goto bb_5 else goto bb_1
2022 | end_bb_0
2024 | bb_1
2025 | cond = some_computation;
2026 | A[i] = cond ? expr : A[i];
2027 | if (i < N) goto bb_5 else goto bb_4
2028 | end_bb_1
2030 | bb_4
2031 | goto bb_1
2032 | end_bb_4
2035 static void
2036 predicate_mem_writes (loop_p loop)
2038 unsigned int i, orig_loop_num_nodes = loop->num_nodes;
2039 auto_vec<int, 1> vect_sizes;
2040 auto_vec<tree, 1> vect_masks;
2042 for (i = 1; i < orig_loop_num_nodes; i++)
2044 gimple_stmt_iterator gsi;
2045 basic_block bb = ifc_bbs[i];
2046 tree cond = bb_predicate (bb);
2047 bool swap;
2048 gimple *stmt;
2049 int index;
2051 if (is_true_predicate (cond))
2052 continue;
2054 swap = false;
2055 if (TREE_CODE (cond) == TRUTH_NOT_EXPR)
2057 swap = true;
2058 cond = TREE_OPERAND (cond, 0);
2061 vect_sizes.truncate (0);
2062 vect_masks.truncate (0);
2064 for (gsi = gsi_start_bb (bb); !gsi_end_p (gsi); gsi_next (&gsi))
2065 if (!gimple_assign_single_p (stmt = gsi_stmt (gsi)))
2066 continue;
2067 else if (gimple_plf (stmt, GF_PLF_2))
2069 tree lhs = gimple_assign_lhs (stmt);
2070 tree rhs = gimple_assign_rhs1 (stmt);
2071 tree ref, addr, ptr, masktype, mask_op0, mask_op1, mask;
2072 gimple *new_stmt;
2073 int bitsize = GET_MODE_BITSIZE (TYPE_MODE (TREE_TYPE (lhs)));
2074 ref = TREE_CODE (lhs) == SSA_NAME ? rhs : lhs;
2075 mark_addressable (ref);
2076 addr = force_gimple_operand_gsi (&gsi, build_fold_addr_expr (ref),
2077 true, NULL_TREE, true,
2078 GSI_SAME_STMT);
2079 if (!vect_sizes.is_empty ()
2080 && (index = mask_exists (bitsize, vect_sizes)) != -1)
2081 /* Use created mask. */
2082 mask = vect_masks[index];
2083 else
2085 masktype = build_nonstandard_integer_type (bitsize, 1);
2086 mask_op0 = build_int_cst (masktype, swap ? 0 : -1);
2087 mask_op1 = build_int_cst (masktype, swap ? -1 : 0);
2088 cond = force_gimple_operand_gsi_1 (&gsi, unshare_expr (cond),
2089 is_gimple_condexpr,
2090 NULL_TREE,
2091 true, GSI_SAME_STMT);
2092 mask = fold_build_cond_expr (masktype, unshare_expr (cond),
2093 mask_op0, mask_op1);
2094 mask = ifc_temp_var (masktype, mask, &gsi);
2095 /* Save mask and its size for further use. */
2096 vect_sizes.safe_push (bitsize);
2097 vect_masks.safe_push (mask);
2099 ptr = build_int_cst (reference_alias_ptr_type (ref), 0);
2100 /* Copy points-to info if possible. */
2101 if (TREE_CODE (addr) == SSA_NAME && !SSA_NAME_PTR_INFO (addr))
2102 copy_ref_info (build2 (MEM_REF, TREE_TYPE (ref), addr, ptr),
2103 ref);
2104 if (TREE_CODE (lhs) == SSA_NAME)
2106 new_stmt
2107 = gimple_build_call_internal (IFN_MASK_LOAD, 3, addr,
2108 ptr, mask);
2109 gimple_call_set_lhs (new_stmt, lhs);
2111 else
2112 new_stmt
2113 = gimple_build_call_internal (IFN_MASK_STORE, 4, addr, ptr,
2114 mask, rhs);
2115 gsi_replace (&gsi, new_stmt, true);
2117 else if (gimple_vdef (stmt))
2119 tree lhs = gimple_assign_lhs (stmt);
2120 tree rhs = gimple_assign_rhs1 (stmt);
2121 tree type = TREE_TYPE (lhs);
2123 lhs = ifc_temp_var (type, unshare_expr (lhs), &gsi);
2124 rhs = ifc_temp_var (type, unshare_expr (rhs), &gsi);
2125 if (swap)
2126 std::swap (lhs, rhs);
2127 cond = force_gimple_operand_gsi_1 (&gsi, unshare_expr (cond),
2128 is_gimple_condexpr, NULL_TREE,
2129 true, GSI_SAME_STMT);
2130 rhs = fold_build_cond_expr (type, unshare_expr (cond), rhs, lhs);
2131 gimple_assign_set_rhs1 (stmt, ifc_temp_var (type, rhs, &gsi));
2132 update_stmt (stmt);
2137 /* Remove all GIMPLE_CONDs and GIMPLE_LABELs of all the basic blocks
2138 other than the exit and latch of the LOOP. Also resets the
2139 GIMPLE_DEBUG information. */
2141 static void
2142 remove_conditions_and_labels (loop_p loop)
2144 gimple_stmt_iterator gsi;
2145 unsigned int i;
2147 for (i = 0; i < loop->num_nodes; i++)
2149 basic_block bb = ifc_bbs[i];
2151 if (bb_with_exit_edge_p (loop, bb)
2152 || bb == loop->latch)
2153 continue;
2155 for (gsi = gsi_start_bb (bb); !gsi_end_p (gsi); )
2156 switch (gimple_code (gsi_stmt (gsi)))
2158 case GIMPLE_COND:
2159 case GIMPLE_LABEL:
2160 gsi_remove (&gsi, true);
2161 break;
2163 case GIMPLE_DEBUG:
2164 /* ??? Should there be conditional GIMPLE_DEBUG_BINDs? */
2165 if (gimple_debug_bind_p (gsi_stmt (gsi)))
2167 gimple_debug_bind_reset_value (gsi_stmt (gsi));
2168 update_stmt (gsi_stmt (gsi));
2170 gsi_next (&gsi);
2171 break;
2173 default:
2174 gsi_next (&gsi);
2179 /* Combine all the basic blocks from LOOP into one or two super basic
2180 blocks. Replace PHI nodes with conditional modify expressions. */
2182 static void
2183 combine_blocks (struct loop *loop, bool any_mask_load_store)
2185 basic_block bb, exit_bb, merge_target_bb;
2186 unsigned int orig_loop_num_nodes = loop->num_nodes;
2187 unsigned int i;
2188 edge e;
2189 edge_iterator ei;
2191 predicate_bbs (loop);
2192 remove_conditions_and_labels (loop);
2193 insert_gimplified_predicates (loop, any_mask_load_store);
2194 predicate_all_scalar_phis (loop);
2196 if (flag_tree_loop_if_convert_stores || any_mask_load_store)
2197 predicate_mem_writes (loop);
2199 /* Merge basic blocks: first remove all the edges in the loop,
2200 except for those from the exit block. */
2201 exit_bb = NULL;
2202 bool *predicated = XNEWVEC (bool, orig_loop_num_nodes);
2203 for (i = 0; i < orig_loop_num_nodes; i++)
2205 bb = ifc_bbs[i];
2206 predicated[i] = !is_true_predicate (bb_predicate (bb));
2207 free_bb_predicate (bb);
2208 if (bb_with_exit_edge_p (loop, bb))
2210 gcc_assert (exit_bb == NULL);
2211 exit_bb = bb;
2214 gcc_assert (exit_bb != loop->latch);
2216 for (i = 1; i < orig_loop_num_nodes; i++)
2218 bb = ifc_bbs[i];
2220 for (ei = ei_start (bb->preds); (e = ei_safe_edge (ei));)
2222 if (e->src == exit_bb)
2223 ei_next (&ei);
2224 else
2225 remove_edge (e);
2229 if (exit_bb != NULL)
2231 if (exit_bb != loop->header)
2233 /* Connect this node to loop header. */
2234 make_edge (loop->header, exit_bb, EDGE_FALLTHRU);
2235 set_immediate_dominator (CDI_DOMINATORS, exit_bb, loop->header);
2238 /* Redirect non-exit edges to loop->latch. */
2239 FOR_EACH_EDGE (e, ei, exit_bb->succs)
2241 if (!loop_exit_edge_p (loop, e))
2242 redirect_edge_and_branch (e, loop->latch);
2244 set_immediate_dominator (CDI_DOMINATORS, loop->latch, exit_bb);
2246 else
2248 /* If the loop does not have an exit, reconnect header and latch. */
2249 make_edge (loop->header, loop->latch, EDGE_FALLTHRU);
2250 set_immediate_dominator (CDI_DOMINATORS, loop->latch, loop->header);
2253 merge_target_bb = loop->header;
2254 for (i = 1; i < orig_loop_num_nodes; i++)
2256 gimple_stmt_iterator gsi;
2257 gimple_stmt_iterator last;
2259 bb = ifc_bbs[i];
2261 if (bb == exit_bb || bb == loop->latch)
2262 continue;
2264 /* Make stmts member of loop->header and clear range info from all stmts
2265 in BB which is now no longer executed conditional on a predicate we
2266 could have derived it from. */
2267 for (gsi = gsi_start_bb (bb); !gsi_end_p (gsi); gsi_next (&gsi))
2269 gimple *stmt = gsi_stmt (gsi);
2270 gimple_set_bb (stmt, merge_target_bb);
2271 if (predicated[i])
2273 ssa_op_iter i;
2274 tree op;
2275 FOR_EACH_SSA_TREE_OPERAND (op, stmt, i, SSA_OP_DEF)
2276 reset_flow_sensitive_info (op);
2280 /* Update stmt list. */
2281 last = gsi_last_bb (merge_target_bb);
2282 gsi_insert_seq_after (&last, bb_seq (bb), GSI_NEW_STMT);
2283 set_bb_seq (bb, NULL);
2285 delete_basic_block (bb);
2288 /* If possible, merge loop header to the block with the exit edge.
2289 This reduces the number of basic blocks to two, to please the
2290 vectorizer that handles only loops with two nodes. */
2291 if (exit_bb
2292 && exit_bb != loop->header
2293 && can_merge_blocks_p (loop->header, exit_bb))
2294 merge_blocks (loop->header, exit_bb);
2296 free (ifc_bbs);
2297 ifc_bbs = NULL;
2298 free (predicated);
2301 /* Version LOOP before if-converting it; the original loop
2302 will be if-converted, the new copy of the loop will not,
2303 and the LOOP_VECTORIZED internal call will be guarding which
2304 loop to execute. The vectorizer pass will fold this
2305 internal call into either true or false. */
2307 static bool
2308 version_loop_for_if_conversion (struct loop *loop)
2310 basic_block cond_bb;
2311 tree cond = make_ssa_name (boolean_type_node);
2312 struct loop *new_loop;
2313 gimple *g;
2314 gimple_stmt_iterator gsi;
2316 g = gimple_build_call_internal (IFN_LOOP_VECTORIZED, 2,
2317 build_int_cst (integer_type_node, loop->num),
2318 integer_zero_node);
2319 gimple_call_set_lhs (g, cond);
2321 initialize_original_copy_tables ();
2322 new_loop = loop_version (loop, cond, &cond_bb,
2323 REG_BR_PROB_BASE, REG_BR_PROB_BASE,
2324 REG_BR_PROB_BASE, true);
2325 free_original_copy_tables ();
2326 if (new_loop == NULL)
2327 return false;
2328 new_loop->dont_vectorize = true;
2329 new_loop->force_vectorize = false;
2330 gsi = gsi_last_bb (cond_bb);
2331 gimple_call_set_arg (g, 1, build_int_cst (integer_type_node, new_loop->num));
2332 gsi_insert_before (&gsi, g, GSI_SAME_STMT);
2333 update_ssa (TODO_update_ssa);
2334 return true;
2337 /* Performs splitting of critical edges if aggressive_if_conv is true.
2338 Returns false if loop won't be if converted and true otherwise. */
2340 static bool
2341 ifcvt_split_critical_edges (struct loop *loop)
2343 basic_block *body;
2344 basic_block bb;
2345 unsigned int num = loop->num_nodes;
2346 unsigned int i;
2347 gimple *stmt;
2348 edge e;
2349 edge_iterator ei;
2351 if (num <= 2)
2352 return false;
2353 if (loop->inner)
2354 return false;
2355 if (!single_exit (loop))
2356 return false;
2358 body = get_loop_body (loop);
2359 for (i = 0; i < num; i++)
2361 bb = body[i];
2362 if (bb == loop->latch
2363 || bb_with_exit_edge_p (loop, bb))
2364 continue;
2365 stmt = last_stmt (bb);
2366 /* Skip basic blocks not ending with conditional branch. */
2367 if (!(stmt && gimple_code (stmt) == GIMPLE_COND))
2368 continue;
2369 FOR_EACH_EDGE (e, ei, bb->succs)
2370 if (EDGE_CRITICAL_P (e) && e->dest->loop_father == loop)
2371 split_edge (e);
2373 free (body);
2374 return true;
2377 /* Assumes that lhs of DEF_STMT have multiple uses.
2378 Delete one use by (1) creation of copy DEF_STMT with
2379 unique lhs; (2) change original use of lhs in one
2380 use statement with newly created lhs. */
2382 static void
2383 ifcvt_split_def_stmt (gimple *def_stmt, gimple *use_stmt)
2385 tree var;
2386 tree lhs;
2387 gimple *copy_stmt;
2388 gimple_stmt_iterator gsi;
2389 use_operand_p use_p;
2390 imm_use_iterator imm_iter;
2392 var = gimple_assign_lhs (def_stmt);
2393 copy_stmt = gimple_copy (def_stmt);
2394 lhs = make_temp_ssa_name (TREE_TYPE (var), NULL, "_ifc_");
2395 gimple_assign_set_lhs (copy_stmt, lhs);
2396 SSA_NAME_DEF_STMT (lhs) = copy_stmt;
2397 /* Insert copy of DEF_STMT. */
2398 gsi = gsi_for_stmt (def_stmt);
2399 gsi_insert_after (&gsi, copy_stmt, GSI_SAME_STMT);
2400 /* Change use of var to lhs in use_stmt. */
2401 if (dump_file && (dump_flags & TDF_DETAILS))
2403 fprintf (dump_file, "Change use of var ");
2404 print_generic_expr (dump_file, var, TDF_SLIM);
2405 fprintf (dump_file, " to ");
2406 print_generic_expr (dump_file, lhs, TDF_SLIM);
2407 fprintf (dump_file, "\n");
2409 FOR_EACH_IMM_USE_FAST (use_p, imm_iter, var)
2411 if (USE_STMT (use_p) != use_stmt)
2412 continue;
2413 SET_USE (use_p, lhs);
2414 break;
2418 /* Traverse bool pattern recursively starting from VAR.
2419 Save its def and use statements to defuse_list if VAR does
2420 not have single use. */
2422 static void
2423 ifcvt_walk_pattern_tree (tree var, vec<gimple *> *defuse_list,
2424 gimple *use_stmt)
2426 tree rhs1, rhs2;
2427 enum tree_code code;
2428 gimple *def_stmt;
2430 def_stmt = SSA_NAME_DEF_STMT (var);
2431 if (gimple_code (def_stmt) != GIMPLE_ASSIGN)
2432 return;
2433 if (!has_single_use (var))
2435 /* Put def and use stmts into defuse_list. */
2436 defuse_list->safe_push (def_stmt);
2437 defuse_list->safe_push (use_stmt);
2438 if (dump_file && (dump_flags & TDF_DETAILS))
2440 fprintf (dump_file, "Multiple lhs uses in stmt\n");
2441 print_gimple_stmt (dump_file, def_stmt, 0, TDF_SLIM);
2444 rhs1 = gimple_assign_rhs1 (def_stmt);
2445 code = gimple_assign_rhs_code (def_stmt);
2446 switch (code)
2448 case SSA_NAME:
2449 ifcvt_walk_pattern_tree (rhs1, defuse_list, def_stmt);
2450 break;
2451 CASE_CONVERT:
2452 if ((TYPE_PRECISION (TREE_TYPE (rhs1)) != 1
2453 || !TYPE_UNSIGNED (TREE_TYPE (rhs1)))
2454 && TREE_CODE (TREE_TYPE (rhs1)) != BOOLEAN_TYPE)
2455 break;
2456 ifcvt_walk_pattern_tree (rhs1, defuse_list, def_stmt);
2457 break;
2458 case BIT_NOT_EXPR:
2459 ifcvt_walk_pattern_tree (rhs1, defuse_list, def_stmt);
2460 break;
2461 case BIT_AND_EXPR:
2462 case BIT_IOR_EXPR:
2463 case BIT_XOR_EXPR:
2464 ifcvt_walk_pattern_tree (rhs1, defuse_list, def_stmt);
2465 rhs2 = gimple_assign_rhs2 (def_stmt);
2466 ifcvt_walk_pattern_tree (rhs2, defuse_list, def_stmt);
2467 break;
2468 default:
2469 break;
2471 return;
2474 /* Returns true if STMT can be a root of bool pattern applied
2475 by vectorizer. */
2477 static bool
2478 stmt_is_root_of_bool_pattern (gimple *stmt)
2480 enum tree_code code;
2481 tree lhs, rhs;
2483 code = gimple_assign_rhs_code (stmt);
2484 if (CONVERT_EXPR_CODE_P (code))
2486 lhs = gimple_assign_lhs (stmt);
2487 rhs = gimple_assign_rhs1 (stmt);
2488 if (TREE_CODE (TREE_TYPE (rhs)) != BOOLEAN_TYPE)
2489 return false;
2490 if (TREE_CODE (TREE_TYPE (lhs)) == BOOLEAN_TYPE)
2491 return false;
2492 return true;
2494 else if (code == COND_EXPR)
2496 rhs = gimple_assign_rhs1 (stmt);
2497 if (TREE_CODE (rhs) != SSA_NAME)
2498 return false;
2499 return true;
2501 return false;
2504 /* Traverse all statements in BB which correspond to loop header to
2505 find out all statements which can start bool pattern applied by
2506 vectorizer and convert multiple uses in it to conform pattern
2507 restrictions. Such case can occur if the same predicate is used both
2508 for phi node conversion and load/store mask. */
2510 static void
2511 ifcvt_repair_bool_pattern (basic_block bb)
2513 tree rhs;
2514 gimple *stmt;
2515 gimple_stmt_iterator gsi;
2516 vec<gimple *> defuse_list = vNULL;
2517 vec<gimple *> pattern_roots = vNULL;
2518 bool repeat = true;
2519 int niter = 0;
2520 unsigned int ix;
2522 /* Collect all root pattern statements. */
2523 for (gsi = gsi_start_bb (bb); !gsi_end_p (gsi); gsi_next (&gsi))
2525 stmt = gsi_stmt (gsi);
2526 if (gimple_code (stmt) != GIMPLE_ASSIGN)
2527 continue;
2528 if (!stmt_is_root_of_bool_pattern (stmt))
2529 continue;
2530 pattern_roots.safe_push (stmt);
2533 if (pattern_roots.is_empty ())
2534 return;
2536 /* Split all statements with multiple uses iteratively since splitting
2537 may create new multiple uses. */
2538 while (repeat)
2540 repeat = false;
2541 niter++;
2542 FOR_EACH_VEC_ELT (pattern_roots, ix, stmt)
2544 rhs = gimple_assign_rhs1 (stmt);
2545 ifcvt_walk_pattern_tree (rhs, &defuse_list, stmt);
2546 while (defuse_list.length () > 0)
2548 repeat = true;
2549 gimple *def_stmt, *use_stmt;
2550 use_stmt = defuse_list.pop ();
2551 def_stmt = defuse_list.pop ();
2552 ifcvt_split_def_stmt (def_stmt, use_stmt);
2557 if (dump_file && (dump_flags & TDF_DETAILS))
2558 fprintf (dump_file, "Repair bool pattern takes %d iterations. \n",
2559 niter);
2562 /* Delete redundant statements produced by predication which prevents
2563 loop vectorization. */
2565 static void
2566 ifcvt_local_dce (basic_block bb)
2568 gimple *stmt;
2569 gimple *stmt1;
2570 gimple *phi;
2571 gimple_stmt_iterator gsi;
2572 vec<gimple *> worklist;
2573 enum gimple_code code;
2574 use_operand_p use_p;
2575 imm_use_iterator imm_iter;
2577 worklist.create (64);
2578 /* Consider all phi as live statements. */
2579 for (gsi = gsi_start_phis (bb); !gsi_end_p (gsi); gsi_next (&gsi))
2581 phi = gsi_stmt (gsi);
2582 gimple_set_plf (phi, GF_PLF_2, true);
2583 worklist.safe_push (phi);
2585 /* Consider load/store statements, CALL and COND as live. */
2586 for (gsi = gsi_start_bb (bb); !gsi_end_p (gsi); gsi_next (&gsi))
2588 stmt = gsi_stmt (gsi);
2589 if (gimple_store_p (stmt)
2590 || gimple_assign_load_p (stmt)
2591 || is_gimple_debug (stmt))
2593 gimple_set_plf (stmt, GF_PLF_2, true);
2594 worklist.safe_push (stmt);
2595 continue;
2597 code = gimple_code (stmt);
2598 if (code == GIMPLE_COND || code == GIMPLE_CALL)
2600 gimple_set_plf (stmt, GF_PLF_2, true);
2601 worklist.safe_push (stmt);
2602 continue;
2604 gimple_set_plf (stmt, GF_PLF_2, false);
2606 if (code == GIMPLE_ASSIGN)
2608 tree lhs = gimple_assign_lhs (stmt);
2609 FOR_EACH_IMM_USE_FAST (use_p, imm_iter, lhs)
2611 stmt1 = USE_STMT (use_p);
2612 if (gimple_bb (stmt1) != bb)
2614 gimple_set_plf (stmt, GF_PLF_2, true);
2615 worklist.safe_push (stmt);
2616 break;
2621 /* Propagate liveness through arguments of live stmt. */
2622 while (worklist.length () > 0)
2624 ssa_op_iter iter;
2625 use_operand_p use_p;
2626 tree use;
2628 stmt = worklist.pop ();
2629 FOR_EACH_PHI_OR_STMT_USE (use_p, stmt, iter, SSA_OP_USE)
2631 use = USE_FROM_PTR (use_p);
2632 if (TREE_CODE (use) != SSA_NAME)
2633 continue;
2634 stmt1 = SSA_NAME_DEF_STMT (use);
2635 if (gimple_bb (stmt1) != bb
2636 || gimple_plf (stmt1, GF_PLF_2))
2637 continue;
2638 gimple_set_plf (stmt1, GF_PLF_2, true);
2639 worklist.safe_push (stmt1);
2642 /* Delete dead statements. */
2643 gsi = gsi_start_bb (bb);
2644 while (!gsi_end_p (gsi))
2646 stmt = gsi_stmt (gsi);
2647 if (gimple_plf (stmt, GF_PLF_2))
2649 gsi_next (&gsi);
2650 continue;
2652 if (dump_file && (dump_flags & TDF_DETAILS))
2654 fprintf (dump_file, "Delete dead stmt in bb#%d\n", bb->index);
2655 print_gimple_stmt (dump_file, stmt, 0, TDF_SLIM);
2657 gsi_remove (&gsi, true);
2658 release_defs (stmt);
2662 /* If-convert LOOP when it is legal. For the moment this pass has no
2663 profitability analysis. Returns non-zero todo flags when something
2664 changed. */
2666 static unsigned int
2667 tree_if_conversion (struct loop *loop)
2669 unsigned int todo = 0;
2670 ifc_bbs = NULL;
2671 bool any_mask_load_store = false;
2673 /* Set up aggressive if-conversion for loops marked with simd pragma. */
2674 aggressive_if_conv = loop->force_vectorize;
2675 /* Check either outer loop was marked with simd pragma. */
2676 if (!aggressive_if_conv)
2678 struct loop *outer_loop = loop_outer (loop);
2679 if (outer_loop && outer_loop->force_vectorize)
2680 aggressive_if_conv = true;
2683 if (aggressive_if_conv)
2684 if (!ifcvt_split_critical_edges (loop))
2685 goto cleanup;
2687 if (!if_convertible_loop_p (loop, &any_mask_load_store)
2688 || !dbg_cnt (if_conversion_tree))
2689 goto cleanup;
2691 if (any_mask_load_store
2692 && ((!flag_tree_loop_vectorize && !loop->force_vectorize)
2693 || loop->dont_vectorize))
2694 goto cleanup;
2696 if (any_mask_load_store && !version_loop_for_if_conversion (loop))
2697 goto cleanup;
2699 /* Now all statements are if-convertible. Combine all the basic
2700 blocks into one huge basic block doing the if-conversion
2701 on-the-fly. */
2702 combine_blocks (loop, any_mask_load_store);
2704 /* Delete dead predicate computations and repair tree correspondent
2705 to bool pattern to delete multiple uses of predicates. */
2706 if (aggressive_if_conv)
2708 ifcvt_local_dce (loop->header);
2709 ifcvt_repair_bool_pattern (loop->header);
2712 todo |= TODO_cleanup_cfg;
2713 if (flag_tree_loop_if_convert_stores || any_mask_load_store)
2715 mark_virtual_operands_for_renaming (cfun);
2716 todo |= TODO_update_ssa_only_virtuals;
2719 cleanup:
2720 if (ifc_bbs)
2722 unsigned int i;
2724 for (i = 0; i < loop->num_nodes; i++)
2725 free_bb_predicate (ifc_bbs[i]);
2727 free (ifc_bbs);
2728 ifc_bbs = NULL;
2730 free_dominance_info (CDI_POST_DOMINATORS);
2732 return todo;
2735 /* Tree if-conversion pass management. */
2737 namespace {
2739 const pass_data pass_data_if_conversion =
2741 GIMPLE_PASS, /* type */
2742 "ifcvt", /* name */
2743 OPTGROUP_NONE, /* optinfo_flags */
2744 TV_NONE, /* tv_id */
2745 ( PROP_cfg | PROP_ssa ), /* properties_required */
2746 0, /* properties_provided */
2747 0, /* properties_destroyed */
2748 0, /* todo_flags_start */
2749 0, /* todo_flags_finish */
2752 class pass_if_conversion : public gimple_opt_pass
2754 public:
2755 pass_if_conversion (gcc::context *ctxt)
2756 : gimple_opt_pass (pass_data_if_conversion, ctxt)
2759 /* opt_pass methods: */
2760 virtual bool gate (function *);
2761 virtual unsigned int execute (function *);
2763 }; // class pass_if_conversion
2765 bool
2766 pass_if_conversion::gate (function *fun)
2768 return (((flag_tree_loop_vectorize || fun->has_force_vectorize_loops)
2769 && flag_tree_loop_if_convert != 0)
2770 || flag_tree_loop_if_convert == 1
2771 || flag_tree_loop_if_convert_stores == 1);
2774 unsigned int
2775 pass_if_conversion::execute (function *fun)
2777 struct loop *loop;
2778 unsigned todo = 0;
2780 if (number_of_loops (fun) <= 1)
2781 return 0;
2783 FOR_EACH_LOOP (loop, 0)
2784 if (flag_tree_loop_if_convert == 1
2785 || flag_tree_loop_if_convert_stores == 1
2786 || ((flag_tree_loop_vectorize || loop->force_vectorize)
2787 && !loop->dont_vectorize))
2788 todo |= tree_if_conversion (loop);
2790 #ifdef ENABLE_CHECKING
2792 basic_block bb;
2793 FOR_EACH_BB_FN (bb, fun)
2794 gcc_assert (!bb->aux);
2796 #endif
2798 return todo;
2801 } // anon namespace
2803 gimple_opt_pass *
2804 make_pass_if_conversion (gcc::context *ctxt)
2806 return new pass_if_conversion (ctxt);