gcc/
[official-gcc.git] / gcc / tree-parloops.c
blobac469b39d7a94d2712899c24647080f864ce3e70
1 /* Loop autoparallelization.
2 Copyright (C) 2006-2015 Free Software Foundation, Inc.
3 Contributed by Sebastian Pop <pop@cri.ensmp.fr>
4 Zdenek Dvorak <dvorakz@suse.cz> and Razya Ladelsky <razya@il.ibm.com>.
6 This file is part of GCC.
8 GCC is free software; you can redistribute it and/or modify it under
9 the terms of the GNU General Public License as published by the Free
10 Software Foundation; either version 3, or (at your option) any later
11 version.
13 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
14 WARRANTY; without even the implied warranty of MERCHANTABILITY or
15 FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
16 for more details.
18 You should have received a copy of the GNU General Public License
19 along with GCC; see the file COPYING3. If not see
20 <http://www.gnu.org/licenses/>. */
22 #include "config.h"
23 #include "system.h"
24 #include "coretypes.h"
25 #include "alias.h"
26 #include "symtab.h"
27 #include "options.h"
28 #include "tree.h"
29 #include "fold-const.h"
30 #include "predict.h"
31 #include "tm.h"
32 #include "hard-reg-set.h"
33 #include "function.h"
34 #include "dominance.h"
35 #include "cfg.h"
36 #include "basic-block.h"
37 #include "tree-ssa-alias.h"
38 #include "internal-fn.h"
39 #include "gimple-expr.h"
40 #include "gimple.h"
41 #include "gimplify.h"
42 #include "gimple-iterator.h"
43 #include "gimplify-me.h"
44 #include "gimple-walk.h"
45 #include "stor-layout.h"
46 #include "tree-nested.h"
47 #include "gimple-ssa.h"
48 #include "tree-cfg.h"
49 #include "tree-phinodes.h"
50 #include "ssa-iterators.h"
51 #include "stringpool.h"
52 #include "tree-ssanames.h"
53 #include "tree-ssa-loop-ivopts.h"
54 #include "tree-ssa-loop-manip.h"
55 #include "tree-ssa-loop-niter.h"
56 #include "tree-ssa-loop.h"
57 #include "tree-into-ssa.h"
58 #include "cfgloop.h"
59 #include "tree-data-ref.h"
60 #include "tree-scalar-evolution.h"
61 #include "gimple-pretty-print.h"
62 #include "tree-pass.h"
63 #include "langhooks.h"
64 #include "tree-vectorizer.h"
65 #include "tree-hasher.h"
66 #include "tree-parloops.h"
67 #include "omp-low.h"
68 #include "tree-nested.h"
69 #include "plugin-api.h"
70 #include "ipa-ref.h"
71 #include "cgraph.h"
72 #include "tree-ssa.h"
74 /* This pass tries to distribute iterations of loops into several threads.
75 The implementation is straightforward -- for each loop we test whether its
76 iterations are independent, and if it is the case (and some additional
77 conditions regarding profitability and correctness are satisfied), we
78 add GIMPLE_OMP_PARALLEL and GIMPLE_OMP_FOR codes and let omp expansion
79 machinery do its job.
81 The most of the complexity is in bringing the code into shape expected
82 by the omp expanders:
83 -- for GIMPLE_OMP_FOR, ensuring that the loop has only one induction
84 variable and that the exit test is at the start of the loop body
85 -- for GIMPLE_OMP_PARALLEL, replacing the references to local addressable
86 variables by accesses through pointers, and breaking up ssa chains
87 by storing the values incoming to the parallelized loop to a structure
88 passed to the new function as an argument (something similar is done
89 in omp gimplification, unfortunately only a small part of the code
90 can be shared).
92 TODO:
93 -- if there are several parallelizable loops in a function, it may be
94 possible to generate the threads just once (using synchronization to
95 ensure that cross-loop dependences are obeyed).
96 -- handling of common reduction patterns for outer loops.
98 More info can also be found at http://gcc.gnu.org/wiki/AutoParInGCC */
100 Reduction handling:
101 currently we use vect_force_simple_reduction() to detect reduction patterns.
102 The code transformation will be introduced by an example.
105 parloop
107 int sum=1;
109 for (i = 0; i < N; i++)
111 x[i] = i + 3;
112 sum+=x[i];
116 gimple-like code:
117 header_bb:
119 # sum_29 = PHI <sum_11(5), 1(3)>
120 # i_28 = PHI <i_12(5), 0(3)>
121 D.1795_8 = i_28 + 3;
122 x[i_28] = D.1795_8;
123 sum_11 = D.1795_8 + sum_29;
124 i_12 = i_28 + 1;
125 if (N_6(D) > i_12)
126 goto header_bb;
129 exit_bb:
131 # sum_21 = PHI <sum_11(4)>
132 printf (&"%d"[0], sum_21);
135 after reduction transformation (only relevant parts):
137 parloop
140 ....
143 # Storing the initial value given by the user. #
145 .paral_data_store.32.sum.27 = 1;
147 #pragma omp parallel num_threads(4)
149 #pragma omp for schedule(static)
151 # The neutral element corresponding to the particular
152 reduction's operation, e.g. 0 for PLUS_EXPR,
153 1 for MULT_EXPR, etc. replaces the user's initial value. #
155 # sum.27_29 = PHI <sum.27_11, 0>
157 sum.27_11 = D.1827_8 + sum.27_29;
159 GIMPLE_OMP_CONTINUE
161 # Adding this reduction phi is done at create_phi_for_local_result() #
162 # sum.27_56 = PHI <sum.27_11, 0>
163 GIMPLE_OMP_RETURN
165 # Creating the atomic operation is done at
166 create_call_for_reduction_1() #
168 #pragma omp atomic_load
169 D.1839_59 = *&.paral_data_load.33_51->reduction.23;
170 D.1840_60 = sum.27_56 + D.1839_59;
171 #pragma omp atomic_store (D.1840_60);
173 GIMPLE_OMP_RETURN
175 # collecting the result after the join of the threads is done at
176 create_loads_for_reductions().
177 The value computed by the threads is loaded from the
178 shared struct. #
181 .paral_data_load.33_52 = &.paral_data_store.32;
182 sum_37 = .paral_data_load.33_52->sum.27;
183 sum_43 = D.1795_41 + sum_37;
185 exit bb:
186 # sum_21 = PHI <sum_43, sum_26>
187 printf (&"%d"[0], sum_21);
195 /* Minimal number of iterations of a loop that should be executed in each
196 thread. */
197 #define MIN_PER_THREAD 100
199 /* Element of the hashtable, representing a
200 reduction in the current loop. */
201 struct reduction_info
203 gimple reduc_stmt; /* reduction statement. */
204 gimple reduc_phi; /* The phi node defining the reduction. */
205 enum tree_code reduction_code;/* code for the reduction operation. */
206 unsigned reduc_version; /* SSA_NAME_VERSION of original reduc_phi
207 result. */
208 gphi *keep_res; /* The PHI_RESULT of this phi is the resulting value
209 of the reduction variable when existing the loop. */
210 tree initial_value; /* The initial value of the reduction var before entering the loop. */
211 tree field; /* the name of the field in the parloop data structure intended for reduction. */
212 tree init; /* reduction initialization value. */
213 gphi *new_phi; /* (helper field) Newly created phi node whose result
214 will be passed to the atomic operation. Represents
215 the local result each thread computed for the reduction
216 operation. */
219 /* Reduction info hashtable helpers. */
221 struct reduction_hasher : free_ptr_hash <reduction_info>
223 static inline hashval_t hash (const reduction_info *);
224 static inline bool equal (const reduction_info *, const reduction_info *);
227 /* Equality and hash functions for hashtab code. */
229 inline bool
230 reduction_hasher::equal (const reduction_info *a, const reduction_info *b)
232 return (a->reduc_phi == b->reduc_phi);
235 inline hashval_t
236 reduction_hasher::hash (const reduction_info *a)
238 return a->reduc_version;
241 typedef hash_table<reduction_hasher> reduction_info_table_type;
244 static struct reduction_info *
245 reduction_phi (reduction_info_table_type *reduction_list, gimple phi)
247 struct reduction_info tmpred, *red;
249 if (reduction_list->elements () == 0 || phi == NULL)
250 return NULL;
252 tmpred.reduc_phi = phi;
253 tmpred.reduc_version = gimple_uid (phi);
254 red = reduction_list->find (&tmpred);
256 return red;
259 /* Element of hashtable of names to copy. */
261 struct name_to_copy_elt
263 unsigned version; /* The version of the name to copy. */
264 tree new_name; /* The new name used in the copy. */
265 tree field; /* The field of the structure used to pass the
266 value. */
269 /* Name copies hashtable helpers. */
271 struct name_to_copy_hasher : free_ptr_hash <name_to_copy_elt>
273 static inline hashval_t hash (const name_to_copy_elt *);
274 static inline bool equal (const name_to_copy_elt *, const name_to_copy_elt *);
277 /* Equality and hash functions for hashtab code. */
279 inline bool
280 name_to_copy_hasher::equal (const name_to_copy_elt *a, const name_to_copy_elt *b)
282 return a->version == b->version;
285 inline hashval_t
286 name_to_copy_hasher::hash (const name_to_copy_elt *a)
288 return (hashval_t) a->version;
291 typedef hash_table<name_to_copy_hasher> name_to_copy_table_type;
293 /* A transformation matrix, which is a self-contained ROWSIZE x COLSIZE
294 matrix. Rather than use floats, we simply keep a single DENOMINATOR that
295 represents the denominator for every element in the matrix. */
296 typedef struct lambda_trans_matrix_s
298 lambda_matrix matrix;
299 int rowsize;
300 int colsize;
301 int denominator;
302 } *lambda_trans_matrix;
303 #define LTM_MATRIX(T) ((T)->matrix)
304 #define LTM_ROWSIZE(T) ((T)->rowsize)
305 #define LTM_COLSIZE(T) ((T)->colsize)
306 #define LTM_DENOMINATOR(T) ((T)->denominator)
308 /* Allocate a new transformation matrix. */
310 static lambda_trans_matrix
311 lambda_trans_matrix_new (int colsize, int rowsize,
312 struct obstack * lambda_obstack)
314 lambda_trans_matrix ret;
316 ret = (lambda_trans_matrix)
317 obstack_alloc (lambda_obstack, sizeof (struct lambda_trans_matrix_s));
318 LTM_MATRIX (ret) = lambda_matrix_new (rowsize, colsize, lambda_obstack);
319 LTM_ROWSIZE (ret) = rowsize;
320 LTM_COLSIZE (ret) = colsize;
321 LTM_DENOMINATOR (ret) = 1;
322 return ret;
325 /* Multiply a vector VEC by a matrix MAT.
326 MAT is an M*N matrix, and VEC is a vector with length N. The result
327 is stored in DEST which must be a vector of length M. */
329 static void
330 lambda_matrix_vector_mult (lambda_matrix matrix, int m, int n,
331 lambda_vector vec, lambda_vector dest)
333 int i, j;
335 lambda_vector_clear (dest, m);
336 for (i = 0; i < m; i++)
337 for (j = 0; j < n; j++)
338 dest[i] += matrix[i][j] * vec[j];
341 /* Return true if TRANS is a legal transformation matrix that respects
342 the dependence vectors in DISTS and DIRS. The conservative answer
343 is false.
345 "Wolfe proves that a unimodular transformation represented by the
346 matrix T is legal when applied to a loop nest with a set of
347 lexicographically non-negative distance vectors RDG if and only if
348 for each vector d in RDG, (T.d >= 0) is lexicographically positive.
349 i.e.: if and only if it transforms the lexicographically positive
350 distance vectors to lexicographically positive vectors. Note that
351 a unimodular matrix must transform the zero vector (and only it) to
352 the zero vector." S.Muchnick. */
354 static bool
355 lambda_transform_legal_p (lambda_trans_matrix trans,
356 int nb_loops,
357 vec<ddr_p> dependence_relations)
359 unsigned int i, j;
360 lambda_vector distres;
361 struct data_dependence_relation *ddr;
363 gcc_assert (LTM_COLSIZE (trans) == nb_loops
364 && LTM_ROWSIZE (trans) == nb_loops);
366 /* When there are no dependences, the transformation is correct. */
367 if (dependence_relations.length () == 0)
368 return true;
370 ddr = dependence_relations[0];
371 if (ddr == NULL)
372 return true;
374 /* When there is an unknown relation in the dependence_relations, we
375 know that it is no worth looking at this loop nest: give up. */
376 if (DDR_ARE_DEPENDENT (ddr) == chrec_dont_know)
377 return false;
379 distres = lambda_vector_new (nb_loops);
381 /* For each distance vector in the dependence graph. */
382 FOR_EACH_VEC_ELT (dependence_relations, i, ddr)
384 /* Don't care about relations for which we know that there is no
385 dependence, nor about read-read (aka. output-dependences):
386 these data accesses can happen in any order. */
387 if (DDR_ARE_DEPENDENT (ddr) == chrec_known
388 || (DR_IS_READ (DDR_A (ddr)) && DR_IS_READ (DDR_B (ddr))))
389 continue;
391 /* Conservatively answer: "this transformation is not valid". */
392 if (DDR_ARE_DEPENDENT (ddr) == chrec_dont_know)
393 return false;
395 /* If the dependence could not be captured by a distance vector,
396 conservatively answer that the transform is not valid. */
397 if (DDR_NUM_DIST_VECTS (ddr) == 0)
398 return false;
400 /* Compute trans.dist_vect */
401 for (j = 0; j < DDR_NUM_DIST_VECTS (ddr); j++)
403 lambda_matrix_vector_mult (LTM_MATRIX (trans), nb_loops, nb_loops,
404 DDR_DIST_VECT (ddr, j), distres);
406 if (!lambda_vector_lexico_pos (distres, nb_loops))
407 return false;
410 return true;
413 /* Data dependency analysis. Returns true if the iterations of LOOP
414 are independent on each other (that is, if we can execute them
415 in parallel). */
417 static bool
418 loop_parallel_p (struct loop *loop, struct obstack * parloop_obstack)
420 vec<ddr_p> dependence_relations;
421 vec<data_reference_p> datarefs;
422 lambda_trans_matrix trans;
423 bool ret = false;
425 if (dump_file && (dump_flags & TDF_DETAILS))
427 fprintf (dump_file, "Considering loop %d\n", loop->num);
428 if (!loop->inner)
429 fprintf (dump_file, "loop is innermost\n");
430 else
431 fprintf (dump_file, "loop NOT innermost\n");
434 /* Check for problems with dependences. If the loop can be reversed,
435 the iterations are independent. */
436 auto_vec<loop_p, 3> loop_nest;
437 datarefs.create (10);
438 dependence_relations.create (100);
439 if (! compute_data_dependences_for_loop (loop, true, &loop_nest, &datarefs,
440 &dependence_relations))
442 if (dump_file && (dump_flags & TDF_DETAILS))
443 fprintf (dump_file, " FAILED: cannot analyze data dependencies\n");
444 ret = false;
445 goto end;
447 if (dump_file && (dump_flags & TDF_DETAILS))
448 dump_data_dependence_relations (dump_file, dependence_relations);
450 trans = lambda_trans_matrix_new (1, 1, parloop_obstack);
451 LTM_MATRIX (trans)[0][0] = -1;
453 if (lambda_transform_legal_p (trans, 1, dependence_relations))
455 ret = true;
456 if (dump_file && (dump_flags & TDF_DETAILS))
457 fprintf (dump_file, " SUCCESS: may be parallelized\n");
459 else if (dump_file && (dump_flags & TDF_DETAILS))
460 fprintf (dump_file,
461 " FAILED: data dependencies exist across iterations\n");
463 end:
464 free_dependence_relations (dependence_relations);
465 free_data_refs (datarefs);
467 return ret;
470 /* Return true when LOOP contains basic blocks marked with the
471 BB_IRREDUCIBLE_LOOP flag. */
473 static inline bool
474 loop_has_blocks_with_irreducible_flag (struct loop *loop)
476 unsigned i;
477 basic_block *bbs = get_loop_body_in_dom_order (loop);
478 bool res = true;
480 for (i = 0; i < loop->num_nodes; i++)
481 if (bbs[i]->flags & BB_IRREDUCIBLE_LOOP)
482 goto end;
484 res = false;
485 end:
486 free (bbs);
487 return res;
490 /* Assigns the address of OBJ in TYPE to an ssa name, and returns this name.
491 The assignment statement is placed on edge ENTRY. DECL_ADDRESS maps decls
492 to their addresses that can be reused. The address of OBJ is known to
493 be invariant in the whole function. Other needed statements are placed
494 right before GSI. */
496 static tree
497 take_address_of (tree obj, tree type, edge entry,
498 int_tree_htab_type *decl_address, gimple_stmt_iterator *gsi)
500 int uid;
501 tree *var_p, name, addr;
502 gassign *stmt;
503 gimple_seq stmts;
505 /* Since the address of OBJ is invariant, the trees may be shared.
506 Avoid rewriting unrelated parts of the code. */
507 obj = unshare_expr (obj);
508 for (var_p = &obj;
509 handled_component_p (*var_p);
510 var_p = &TREE_OPERAND (*var_p, 0))
511 continue;
513 /* Canonicalize the access to base on a MEM_REF. */
514 if (DECL_P (*var_p))
515 *var_p = build_simple_mem_ref (build_fold_addr_expr (*var_p));
517 /* Assign a canonical SSA name to the address of the base decl used
518 in the address and share it for all accesses and addresses based
519 on it. */
520 uid = DECL_UID (TREE_OPERAND (TREE_OPERAND (*var_p, 0), 0));
521 int_tree_map elt;
522 elt.uid = uid;
523 int_tree_map *slot = decl_address->find_slot (elt, INSERT);
524 if (!slot->to)
526 if (gsi == NULL)
527 return NULL;
528 addr = TREE_OPERAND (*var_p, 0);
529 const char *obj_name
530 = get_name (TREE_OPERAND (TREE_OPERAND (*var_p, 0), 0));
531 if (obj_name)
532 name = make_temp_ssa_name (TREE_TYPE (addr), NULL, obj_name);
533 else
534 name = make_ssa_name (TREE_TYPE (addr));
535 stmt = gimple_build_assign (name, addr);
536 gsi_insert_on_edge_immediate (entry, stmt);
538 slot->uid = uid;
539 slot->to = name;
541 else
542 name = slot->to;
544 /* Express the address in terms of the canonical SSA name. */
545 TREE_OPERAND (*var_p, 0) = name;
546 if (gsi == NULL)
547 return build_fold_addr_expr_with_type (obj, type);
549 name = force_gimple_operand (build_addr (obj, current_function_decl),
550 &stmts, true, NULL_TREE);
551 if (!gimple_seq_empty_p (stmts))
552 gsi_insert_seq_before (gsi, stmts, GSI_SAME_STMT);
554 if (!useless_type_conversion_p (type, TREE_TYPE (name)))
556 name = force_gimple_operand (fold_convert (type, name), &stmts, true,
557 NULL_TREE);
558 if (!gimple_seq_empty_p (stmts))
559 gsi_insert_seq_before (gsi, stmts, GSI_SAME_STMT);
562 return name;
565 /* Callback for htab_traverse. Create the initialization statement
566 for reduction described in SLOT, and place it at the preheader of
567 the loop described in DATA. */
570 initialize_reductions (reduction_info **slot, struct loop *loop)
572 tree init, c;
573 tree bvar, type, arg;
574 edge e;
576 struct reduction_info *const reduc = *slot;
578 /* Create initialization in preheader:
579 reduction_variable = initialization value of reduction. */
581 /* In the phi node at the header, replace the argument coming
582 from the preheader with the reduction initialization value. */
584 /* Create a new variable to initialize the reduction. */
585 type = TREE_TYPE (PHI_RESULT (reduc->reduc_phi));
586 bvar = create_tmp_var (type, "reduction");
588 c = build_omp_clause (gimple_location (reduc->reduc_stmt),
589 OMP_CLAUSE_REDUCTION);
590 OMP_CLAUSE_REDUCTION_CODE (c) = reduc->reduction_code;
591 OMP_CLAUSE_DECL (c) = SSA_NAME_VAR (gimple_assign_lhs (reduc->reduc_stmt));
593 init = omp_reduction_init (c, TREE_TYPE (bvar));
594 reduc->init = init;
596 /* Replace the argument representing the initialization value
597 with the initialization value for the reduction (neutral
598 element for the particular operation, e.g. 0 for PLUS_EXPR,
599 1 for MULT_EXPR, etc).
600 Keep the old value in a new variable "reduction_initial",
601 that will be taken in consideration after the parallel
602 computing is done. */
604 e = loop_preheader_edge (loop);
605 arg = PHI_ARG_DEF_FROM_EDGE (reduc->reduc_phi, e);
606 /* Create new variable to hold the initial value. */
608 SET_USE (PHI_ARG_DEF_PTR_FROM_EDGE
609 (reduc->reduc_phi, loop_preheader_edge (loop)), init);
610 reduc->initial_value = arg;
611 return 1;
614 struct elv_data
616 struct walk_stmt_info info;
617 edge entry;
618 int_tree_htab_type *decl_address;
619 gimple_stmt_iterator *gsi;
620 bool changed;
621 bool reset;
624 /* Eliminates references to local variables in *TP out of the single
625 entry single exit region starting at DTA->ENTRY.
626 DECL_ADDRESS contains addresses of the references that had their
627 address taken already. If the expression is changed, CHANGED is
628 set to true. Callback for walk_tree. */
630 static tree
631 eliminate_local_variables_1 (tree *tp, int *walk_subtrees, void *data)
633 struct elv_data *const dta = (struct elv_data *) data;
634 tree t = *tp, var, addr, addr_type, type, obj;
636 if (DECL_P (t))
638 *walk_subtrees = 0;
640 if (!SSA_VAR_P (t) || DECL_EXTERNAL (t))
641 return NULL_TREE;
643 type = TREE_TYPE (t);
644 addr_type = build_pointer_type (type);
645 addr = take_address_of (t, addr_type, dta->entry, dta->decl_address,
646 dta->gsi);
647 if (dta->gsi == NULL && addr == NULL_TREE)
649 dta->reset = true;
650 return NULL_TREE;
653 *tp = build_simple_mem_ref (addr);
655 dta->changed = true;
656 return NULL_TREE;
659 if (TREE_CODE (t) == ADDR_EXPR)
661 /* ADDR_EXPR may appear in two contexts:
662 -- as a gimple operand, when the address taken is a function invariant
663 -- as gimple rhs, when the resulting address in not a function
664 invariant
665 We do not need to do anything special in the latter case (the base of
666 the memory reference whose address is taken may be replaced in the
667 DECL_P case). The former case is more complicated, as we need to
668 ensure that the new address is still a gimple operand. Thus, it
669 is not sufficient to replace just the base of the memory reference --
670 we need to move the whole computation of the address out of the
671 loop. */
672 if (!is_gimple_val (t))
673 return NULL_TREE;
675 *walk_subtrees = 0;
676 obj = TREE_OPERAND (t, 0);
677 var = get_base_address (obj);
678 if (!var || !SSA_VAR_P (var) || DECL_EXTERNAL (var))
679 return NULL_TREE;
681 addr_type = TREE_TYPE (t);
682 addr = take_address_of (obj, addr_type, dta->entry, dta->decl_address,
683 dta->gsi);
684 if (dta->gsi == NULL && addr == NULL_TREE)
686 dta->reset = true;
687 return NULL_TREE;
689 *tp = addr;
691 dta->changed = true;
692 return NULL_TREE;
695 if (!EXPR_P (t))
696 *walk_subtrees = 0;
698 return NULL_TREE;
701 /* Moves the references to local variables in STMT at *GSI out of the single
702 entry single exit region starting at ENTRY. DECL_ADDRESS contains
703 addresses of the references that had their address taken
704 already. */
706 static void
707 eliminate_local_variables_stmt (edge entry, gimple_stmt_iterator *gsi,
708 int_tree_htab_type *decl_address)
710 struct elv_data dta;
711 gimple stmt = gsi_stmt (*gsi);
713 memset (&dta.info, '\0', sizeof (dta.info));
714 dta.entry = entry;
715 dta.decl_address = decl_address;
716 dta.changed = false;
717 dta.reset = false;
719 if (gimple_debug_bind_p (stmt))
721 dta.gsi = NULL;
722 walk_tree (gimple_debug_bind_get_value_ptr (stmt),
723 eliminate_local_variables_1, &dta.info, NULL);
724 if (dta.reset)
726 gimple_debug_bind_reset_value (stmt);
727 dta.changed = true;
730 else if (gimple_clobber_p (stmt))
732 stmt = gimple_build_nop ();
733 gsi_replace (gsi, stmt, false);
734 dta.changed = true;
736 else
738 dta.gsi = gsi;
739 walk_gimple_op (stmt, eliminate_local_variables_1, &dta.info);
742 if (dta.changed)
743 update_stmt (stmt);
746 /* Eliminates the references to local variables from the single entry
747 single exit region between the ENTRY and EXIT edges.
749 This includes:
750 1) Taking address of a local variable -- these are moved out of the
751 region (and temporary variable is created to hold the address if
752 necessary).
754 2) Dereferencing a local variable -- these are replaced with indirect
755 references. */
757 static void
758 eliminate_local_variables (edge entry, edge exit)
760 basic_block bb;
761 auto_vec<basic_block, 3> body;
762 unsigned i;
763 gimple_stmt_iterator gsi;
764 bool has_debug_stmt = false;
765 int_tree_htab_type decl_address (10);
766 basic_block entry_bb = entry->src;
767 basic_block exit_bb = exit->dest;
769 gather_blocks_in_sese_region (entry_bb, exit_bb, &body);
771 FOR_EACH_VEC_ELT (body, i, bb)
772 if (bb != entry_bb && bb != exit_bb)
773 for (gsi = gsi_start_bb (bb); !gsi_end_p (gsi); gsi_next (&gsi))
774 if (is_gimple_debug (gsi_stmt (gsi)))
776 if (gimple_debug_bind_p (gsi_stmt (gsi)))
777 has_debug_stmt = true;
779 else
780 eliminate_local_variables_stmt (entry, &gsi, &decl_address);
782 if (has_debug_stmt)
783 FOR_EACH_VEC_ELT (body, i, bb)
784 if (bb != entry_bb && bb != exit_bb)
785 for (gsi = gsi_start_bb (bb); !gsi_end_p (gsi); gsi_next (&gsi))
786 if (gimple_debug_bind_p (gsi_stmt (gsi)))
787 eliminate_local_variables_stmt (entry, &gsi, &decl_address);
790 /* Returns true if expression EXPR is not defined between ENTRY and
791 EXIT, i.e. if all its operands are defined outside of the region. */
793 static bool
794 expr_invariant_in_region_p (edge entry, edge exit, tree expr)
796 basic_block entry_bb = entry->src;
797 basic_block exit_bb = exit->dest;
798 basic_block def_bb;
800 if (is_gimple_min_invariant (expr))
801 return true;
803 if (TREE_CODE (expr) == SSA_NAME)
805 def_bb = gimple_bb (SSA_NAME_DEF_STMT (expr));
806 if (def_bb
807 && dominated_by_p (CDI_DOMINATORS, def_bb, entry_bb)
808 && !dominated_by_p (CDI_DOMINATORS, def_bb, exit_bb))
809 return false;
811 return true;
814 return false;
817 /* If COPY_NAME_P is true, creates and returns a duplicate of NAME.
818 The copies are stored to NAME_COPIES, if NAME was already duplicated,
819 its duplicate stored in NAME_COPIES is returned.
821 Regardless of COPY_NAME_P, the decl used as a base of the ssa name is also
822 duplicated, storing the copies in DECL_COPIES. */
824 static tree
825 separate_decls_in_region_name (tree name, name_to_copy_table_type *name_copies,
826 int_tree_htab_type *decl_copies,
827 bool copy_name_p)
829 tree copy, var, var_copy;
830 unsigned idx, uid, nuid;
831 struct int_tree_map ielt;
832 struct name_to_copy_elt elt, *nelt;
833 name_to_copy_elt **slot;
834 int_tree_map *dslot;
836 if (TREE_CODE (name) != SSA_NAME)
837 return name;
839 idx = SSA_NAME_VERSION (name);
840 elt.version = idx;
841 slot = name_copies->find_slot_with_hash (&elt, idx,
842 copy_name_p ? INSERT : NO_INSERT);
843 if (slot && *slot)
844 return (*slot)->new_name;
846 if (copy_name_p)
848 copy = duplicate_ssa_name (name, NULL);
849 nelt = XNEW (struct name_to_copy_elt);
850 nelt->version = idx;
851 nelt->new_name = copy;
852 nelt->field = NULL_TREE;
853 *slot = nelt;
855 else
857 gcc_assert (!slot);
858 copy = name;
861 var = SSA_NAME_VAR (name);
862 if (!var)
863 return copy;
865 uid = DECL_UID (var);
866 ielt.uid = uid;
867 dslot = decl_copies->find_slot_with_hash (ielt, uid, INSERT);
868 if (!dslot->to)
870 var_copy = create_tmp_var (TREE_TYPE (var), get_name (var));
871 DECL_GIMPLE_REG_P (var_copy) = DECL_GIMPLE_REG_P (var);
872 dslot->uid = uid;
873 dslot->to = var_copy;
875 /* Ensure that when we meet this decl next time, we won't duplicate
876 it again. */
877 nuid = DECL_UID (var_copy);
878 ielt.uid = nuid;
879 dslot = decl_copies->find_slot_with_hash (ielt, nuid, INSERT);
880 gcc_assert (!dslot->to);
881 dslot->uid = nuid;
882 dslot->to = var_copy;
884 else
885 var_copy = dslot->to;
887 replace_ssa_name_symbol (copy, var_copy);
888 return copy;
891 /* Finds the ssa names used in STMT that are defined outside the
892 region between ENTRY and EXIT and replaces such ssa names with
893 their duplicates. The duplicates are stored to NAME_COPIES. Base
894 decls of all ssa names used in STMT (including those defined in
895 LOOP) are replaced with the new temporary variables; the
896 replacement decls are stored in DECL_COPIES. */
898 static void
899 separate_decls_in_region_stmt (edge entry, edge exit, gimple stmt,
900 name_to_copy_table_type *name_copies,
901 int_tree_htab_type *decl_copies)
903 use_operand_p use;
904 def_operand_p def;
905 ssa_op_iter oi;
906 tree name, copy;
907 bool copy_name_p;
909 FOR_EACH_PHI_OR_STMT_DEF (def, stmt, oi, SSA_OP_DEF)
911 name = DEF_FROM_PTR (def);
912 gcc_assert (TREE_CODE (name) == SSA_NAME);
913 copy = separate_decls_in_region_name (name, name_copies, decl_copies,
914 false);
915 gcc_assert (copy == name);
918 FOR_EACH_PHI_OR_STMT_USE (use, stmt, oi, SSA_OP_USE)
920 name = USE_FROM_PTR (use);
921 if (TREE_CODE (name) != SSA_NAME)
922 continue;
924 copy_name_p = expr_invariant_in_region_p (entry, exit, name);
925 copy = separate_decls_in_region_name (name, name_copies, decl_copies,
926 copy_name_p);
927 SET_USE (use, copy);
931 /* Finds the ssa names used in STMT that are defined outside the
932 region between ENTRY and EXIT and replaces such ssa names with
933 their duplicates. The duplicates are stored to NAME_COPIES. Base
934 decls of all ssa names used in STMT (including those defined in
935 LOOP) are replaced with the new temporary variables; the
936 replacement decls are stored in DECL_COPIES. */
938 static bool
939 separate_decls_in_region_debug (gimple stmt,
940 name_to_copy_table_type *name_copies,
941 int_tree_htab_type *decl_copies)
943 use_operand_p use;
944 ssa_op_iter oi;
945 tree var, name;
946 struct int_tree_map ielt;
947 struct name_to_copy_elt elt;
948 name_to_copy_elt **slot;
949 int_tree_map *dslot;
951 if (gimple_debug_bind_p (stmt))
952 var = gimple_debug_bind_get_var (stmt);
953 else if (gimple_debug_source_bind_p (stmt))
954 var = gimple_debug_source_bind_get_var (stmt);
955 else
956 return true;
957 if (TREE_CODE (var) == DEBUG_EXPR_DECL || TREE_CODE (var) == LABEL_DECL)
958 return true;
959 gcc_assert (DECL_P (var) && SSA_VAR_P (var));
960 ielt.uid = DECL_UID (var);
961 dslot = decl_copies->find_slot_with_hash (ielt, ielt.uid, NO_INSERT);
962 if (!dslot)
963 return true;
964 if (gimple_debug_bind_p (stmt))
965 gimple_debug_bind_set_var (stmt, dslot->to);
966 else if (gimple_debug_source_bind_p (stmt))
967 gimple_debug_source_bind_set_var (stmt, dslot->to);
969 FOR_EACH_PHI_OR_STMT_USE (use, stmt, oi, SSA_OP_USE)
971 name = USE_FROM_PTR (use);
972 if (TREE_CODE (name) != SSA_NAME)
973 continue;
975 elt.version = SSA_NAME_VERSION (name);
976 slot = name_copies->find_slot_with_hash (&elt, elt.version, NO_INSERT);
977 if (!slot)
979 gimple_debug_bind_reset_value (stmt);
980 update_stmt (stmt);
981 break;
984 SET_USE (use, (*slot)->new_name);
987 return false;
990 /* Callback for htab_traverse. Adds a field corresponding to the reduction
991 specified in SLOT. The type is passed in DATA. */
994 add_field_for_reduction (reduction_info **slot, tree type)
997 struct reduction_info *const red = *slot;
998 tree var = gimple_assign_lhs (red->reduc_stmt);
999 tree field = build_decl (gimple_location (red->reduc_stmt), FIELD_DECL,
1000 SSA_NAME_IDENTIFIER (var), TREE_TYPE (var));
1002 insert_field_into_struct (type, field);
1004 red->field = field;
1006 return 1;
1009 /* Callback for htab_traverse. Adds a field corresponding to a ssa name
1010 described in SLOT. The type is passed in DATA. */
1013 add_field_for_name (name_to_copy_elt **slot, tree type)
1015 struct name_to_copy_elt *const elt = *slot;
1016 tree name = ssa_name (elt->version);
1017 tree field = build_decl (UNKNOWN_LOCATION,
1018 FIELD_DECL, SSA_NAME_IDENTIFIER (name),
1019 TREE_TYPE (name));
1021 insert_field_into_struct (type, field);
1022 elt->field = field;
1024 return 1;
1027 /* Callback for htab_traverse. A local result is the intermediate result
1028 computed by a single
1029 thread, or the initial value in case no iteration was executed.
1030 This function creates a phi node reflecting these values.
1031 The phi's result will be stored in NEW_PHI field of the
1032 reduction's data structure. */
1035 create_phi_for_local_result (reduction_info **slot, struct loop *loop)
1037 struct reduction_info *const reduc = *slot;
1038 edge e;
1039 gphi *new_phi;
1040 basic_block store_bb;
1041 tree local_res;
1042 source_location locus;
1044 /* STORE_BB is the block where the phi
1045 should be stored. It is the destination of the loop exit.
1046 (Find the fallthru edge from GIMPLE_OMP_CONTINUE). */
1047 store_bb = FALLTHRU_EDGE (loop->latch)->dest;
1049 /* STORE_BB has two predecessors. One coming from the loop
1050 (the reduction's result is computed at the loop),
1051 and another coming from a block preceding the loop,
1052 when no iterations
1053 are executed (the initial value should be taken). */
1054 if (EDGE_PRED (store_bb, 0) == FALLTHRU_EDGE (loop->latch))
1055 e = EDGE_PRED (store_bb, 1);
1056 else
1057 e = EDGE_PRED (store_bb, 0);
1058 local_res = copy_ssa_name (gimple_assign_lhs (reduc->reduc_stmt));
1059 locus = gimple_location (reduc->reduc_stmt);
1060 new_phi = create_phi_node (local_res, store_bb);
1061 add_phi_arg (new_phi, reduc->init, e, locus);
1062 add_phi_arg (new_phi, gimple_assign_lhs (reduc->reduc_stmt),
1063 FALLTHRU_EDGE (loop->latch), locus);
1064 reduc->new_phi = new_phi;
1066 return 1;
1069 struct clsn_data
1071 tree store;
1072 tree load;
1074 basic_block store_bb;
1075 basic_block load_bb;
1078 /* Callback for htab_traverse. Create an atomic instruction for the
1079 reduction described in SLOT.
1080 DATA annotates the place in memory the atomic operation relates to,
1081 and the basic block it needs to be generated in. */
1084 create_call_for_reduction_1 (reduction_info **slot, struct clsn_data *clsn_data)
1086 struct reduction_info *const reduc = *slot;
1087 gimple_stmt_iterator gsi;
1088 tree type = TREE_TYPE (PHI_RESULT (reduc->reduc_phi));
1089 tree load_struct;
1090 basic_block bb;
1091 basic_block new_bb;
1092 edge e;
1093 tree t, addr, ref, x;
1094 tree tmp_load, name;
1095 gimple load;
1097 load_struct = build_simple_mem_ref (clsn_data->load);
1098 t = build3 (COMPONENT_REF, type, load_struct, reduc->field, NULL_TREE);
1100 addr = build_addr (t, current_function_decl);
1102 /* Create phi node. */
1103 bb = clsn_data->load_bb;
1105 gsi = gsi_last_bb (bb);
1106 e = split_block (bb, gsi_stmt (gsi));
1107 new_bb = e->dest;
1109 tmp_load = create_tmp_var (TREE_TYPE (TREE_TYPE (addr)));
1110 tmp_load = make_ssa_name (tmp_load);
1111 load = gimple_build_omp_atomic_load (tmp_load, addr);
1112 SSA_NAME_DEF_STMT (tmp_load) = load;
1113 gsi = gsi_start_bb (new_bb);
1114 gsi_insert_after (&gsi, load, GSI_NEW_STMT);
1116 e = split_block (new_bb, load);
1117 new_bb = e->dest;
1118 gsi = gsi_start_bb (new_bb);
1119 ref = tmp_load;
1120 x = fold_build2 (reduc->reduction_code,
1121 TREE_TYPE (PHI_RESULT (reduc->new_phi)), ref,
1122 PHI_RESULT (reduc->new_phi));
1124 name = force_gimple_operand_gsi (&gsi, x, true, NULL_TREE, true,
1125 GSI_CONTINUE_LINKING);
1127 gsi_insert_after (&gsi, gimple_build_omp_atomic_store (name), GSI_NEW_STMT);
1128 return 1;
1131 /* Create the atomic operation at the join point of the threads.
1132 REDUCTION_LIST describes the reductions in the LOOP.
1133 LD_ST_DATA describes the shared data structure where
1134 shared data is stored in and loaded from. */
1135 static void
1136 create_call_for_reduction (struct loop *loop,
1137 reduction_info_table_type *reduction_list,
1138 struct clsn_data *ld_st_data)
1140 reduction_list->traverse <struct loop *, create_phi_for_local_result> (loop);
1141 /* Find the fallthru edge from GIMPLE_OMP_CONTINUE. */
1142 ld_st_data->load_bb = FALLTHRU_EDGE (loop->latch)->dest;
1143 reduction_list
1144 ->traverse <struct clsn_data *, create_call_for_reduction_1> (ld_st_data);
1147 /* Callback for htab_traverse. Loads the final reduction value at the
1148 join point of all threads, and inserts it in the right place. */
1151 create_loads_for_reductions (reduction_info **slot, struct clsn_data *clsn_data)
1153 struct reduction_info *const red = *slot;
1154 gimple stmt;
1155 gimple_stmt_iterator gsi;
1156 tree type = TREE_TYPE (gimple_assign_lhs (red->reduc_stmt));
1157 tree load_struct;
1158 tree name;
1159 tree x;
1161 gsi = gsi_after_labels (clsn_data->load_bb);
1162 load_struct = build_simple_mem_ref (clsn_data->load);
1163 load_struct = build3 (COMPONENT_REF, type, load_struct, red->field,
1164 NULL_TREE);
1166 x = load_struct;
1167 name = PHI_RESULT (red->keep_res);
1168 stmt = gimple_build_assign (name, x);
1170 gsi_insert_after (&gsi, stmt, GSI_NEW_STMT);
1172 for (gsi = gsi_start_phis (gimple_bb (red->keep_res));
1173 !gsi_end_p (gsi); gsi_next (&gsi))
1174 if (gsi_stmt (gsi) == red->keep_res)
1176 remove_phi_node (&gsi, false);
1177 return 1;
1179 gcc_unreachable ();
1182 /* Load the reduction result that was stored in LD_ST_DATA.
1183 REDUCTION_LIST describes the list of reductions that the
1184 loads should be generated for. */
1185 static void
1186 create_final_loads_for_reduction (reduction_info_table_type *reduction_list,
1187 struct clsn_data *ld_st_data)
1189 gimple_stmt_iterator gsi;
1190 tree t;
1191 gimple stmt;
1193 gsi = gsi_after_labels (ld_st_data->load_bb);
1194 t = build_fold_addr_expr (ld_st_data->store);
1195 stmt = gimple_build_assign (ld_st_data->load, t);
1197 gsi_insert_before (&gsi, stmt, GSI_NEW_STMT);
1199 reduction_list
1200 ->traverse <struct clsn_data *, create_loads_for_reductions> (ld_st_data);
1204 /* Callback for htab_traverse. Store the neutral value for the
1205 particular reduction's operation, e.g. 0 for PLUS_EXPR,
1206 1 for MULT_EXPR, etc. into the reduction field.
1207 The reduction is specified in SLOT. The store information is
1208 passed in DATA. */
1211 create_stores_for_reduction (reduction_info **slot, struct clsn_data *clsn_data)
1213 struct reduction_info *const red = *slot;
1214 tree t;
1215 gimple stmt;
1216 gimple_stmt_iterator gsi;
1217 tree type = TREE_TYPE (gimple_assign_lhs (red->reduc_stmt));
1219 gsi = gsi_last_bb (clsn_data->store_bb);
1220 t = build3 (COMPONENT_REF, type, clsn_data->store, red->field, NULL_TREE);
1221 stmt = gimple_build_assign (t, red->initial_value);
1222 gsi_insert_after (&gsi, stmt, GSI_NEW_STMT);
1224 return 1;
1227 /* Callback for htab_traverse. Creates loads to a field of LOAD in LOAD_BB and
1228 store to a field of STORE in STORE_BB for the ssa name and its duplicate
1229 specified in SLOT. */
1232 create_loads_and_stores_for_name (name_to_copy_elt **slot,
1233 struct clsn_data *clsn_data)
1235 struct name_to_copy_elt *const elt = *slot;
1236 tree t;
1237 gimple stmt;
1238 gimple_stmt_iterator gsi;
1239 tree type = TREE_TYPE (elt->new_name);
1240 tree load_struct;
1242 gsi = gsi_last_bb (clsn_data->store_bb);
1243 t = build3 (COMPONENT_REF, type, clsn_data->store, elt->field, NULL_TREE);
1244 stmt = gimple_build_assign (t, ssa_name (elt->version));
1245 gsi_insert_after (&gsi, stmt, GSI_NEW_STMT);
1247 gsi = gsi_last_bb (clsn_data->load_bb);
1248 load_struct = build_simple_mem_ref (clsn_data->load);
1249 t = build3 (COMPONENT_REF, type, load_struct, elt->field, NULL_TREE);
1250 stmt = gimple_build_assign (elt->new_name, t);
1251 gsi_insert_after (&gsi, stmt, GSI_NEW_STMT);
1253 return 1;
1256 /* Moves all the variables used in LOOP and defined outside of it (including
1257 the initial values of loop phi nodes, and *PER_THREAD if it is a ssa
1258 name) to a structure created for this purpose. The code
1260 while (1)
1262 use (a);
1263 use (b);
1266 is transformed this way:
1268 bb0:
1269 old.a = a;
1270 old.b = b;
1272 bb1:
1273 a' = new->a;
1274 b' = new->b;
1275 while (1)
1277 use (a');
1278 use (b');
1281 `old' is stored to *ARG_STRUCT and `new' is stored to NEW_ARG_STRUCT. The
1282 pointer `new' is intentionally not initialized (the loop will be split to a
1283 separate function later, and `new' will be initialized from its arguments).
1284 LD_ST_DATA holds information about the shared data structure used to pass
1285 information among the threads. It is initialized here, and
1286 gen_parallel_loop will pass it to create_call_for_reduction that
1287 needs this information. REDUCTION_LIST describes the reductions
1288 in LOOP. */
1290 static void
1291 separate_decls_in_region (edge entry, edge exit,
1292 reduction_info_table_type *reduction_list,
1293 tree *arg_struct, tree *new_arg_struct,
1294 struct clsn_data *ld_st_data)
1297 basic_block bb1 = split_edge (entry);
1298 basic_block bb0 = single_pred (bb1);
1299 name_to_copy_table_type name_copies (10);
1300 int_tree_htab_type decl_copies (10);
1301 unsigned i;
1302 tree type, type_name, nvar;
1303 gimple_stmt_iterator gsi;
1304 struct clsn_data clsn_data;
1305 auto_vec<basic_block, 3> body;
1306 basic_block bb;
1307 basic_block entry_bb = bb1;
1308 basic_block exit_bb = exit->dest;
1309 bool has_debug_stmt = false;
1311 entry = single_succ_edge (entry_bb);
1312 gather_blocks_in_sese_region (entry_bb, exit_bb, &body);
1314 FOR_EACH_VEC_ELT (body, i, bb)
1316 if (bb != entry_bb && bb != exit_bb)
1318 for (gsi = gsi_start_phis (bb); !gsi_end_p (gsi); gsi_next (&gsi))
1319 separate_decls_in_region_stmt (entry, exit, gsi_stmt (gsi),
1320 &name_copies, &decl_copies);
1322 for (gsi = gsi_start_bb (bb); !gsi_end_p (gsi); gsi_next (&gsi))
1324 gimple stmt = gsi_stmt (gsi);
1326 if (is_gimple_debug (stmt))
1327 has_debug_stmt = true;
1328 else
1329 separate_decls_in_region_stmt (entry, exit, stmt,
1330 &name_copies, &decl_copies);
1335 /* Now process debug bind stmts. We must not create decls while
1336 processing debug stmts, so we defer their processing so as to
1337 make sure we will have debug info for as many variables as
1338 possible (all of those that were dealt with in the loop above),
1339 and discard those for which we know there's nothing we can
1340 do. */
1341 if (has_debug_stmt)
1342 FOR_EACH_VEC_ELT (body, i, bb)
1343 if (bb != entry_bb && bb != exit_bb)
1345 for (gsi = gsi_start_bb (bb); !gsi_end_p (gsi);)
1347 gimple stmt = gsi_stmt (gsi);
1349 if (is_gimple_debug (stmt))
1351 if (separate_decls_in_region_debug (stmt, &name_copies,
1352 &decl_copies))
1354 gsi_remove (&gsi, true);
1355 continue;
1359 gsi_next (&gsi);
1363 if (name_copies.elements () == 0 && reduction_list->elements () == 0)
1365 /* It may happen that there is nothing to copy (if there are only
1366 loop carried and external variables in the loop). */
1367 *arg_struct = NULL;
1368 *new_arg_struct = NULL;
1370 else
1372 /* Create the type for the structure to store the ssa names to. */
1373 type = lang_hooks.types.make_type (RECORD_TYPE);
1374 type_name = build_decl (UNKNOWN_LOCATION,
1375 TYPE_DECL, create_tmp_var_name (".paral_data"),
1376 type);
1377 TYPE_NAME (type) = type_name;
1379 name_copies.traverse <tree, add_field_for_name> (type);
1380 if (reduction_list && reduction_list->elements () > 0)
1382 /* Create the fields for reductions. */
1383 reduction_list->traverse <tree, add_field_for_reduction> (type);
1385 layout_type (type);
1387 /* Create the loads and stores. */
1388 *arg_struct = create_tmp_var (type, ".paral_data_store");
1389 nvar = create_tmp_var (build_pointer_type (type), ".paral_data_load");
1390 *new_arg_struct = make_ssa_name (nvar);
1392 ld_st_data->store = *arg_struct;
1393 ld_st_data->load = *new_arg_struct;
1394 ld_st_data->store_bb = bb0;
1395 ld_st_data->load_bb = bb1;
1397 name_copies
1398 .traverse <struct clsn_data *, create_loads_and_stores_for_name>
1399 (ld_st_data);
1401 /* Load the calculation from memory (after the join of the threads). */
1403 if (reduction_list && reduction_list->elements () > 0)
1405 reduction_list
1406 ->traverse <struct clsn_data *, create_stores_for_reduction>
1407 (ld_st_data);
1408 clsn_data.load = make_ssa_name (nvar);
1409 clsn_data.load_bb = exit->dest;
1410 clsn_data.store = ld_st_data->store;
1411 create_final_loads_for_reduction (reduction_list, &clsn_data);
1416 /* Returns true if FN was created to run in parallel. */
1418 bool
1419 parallelized_function_p (tree fndecl)
1421 cgraph_node *node = cgraph_node::get (fndecl);
1422 gcc_assert (node != NULL);
1423 return node->parallelized_function;
1426 /* Creates and returns an empty function that will receive the body of
1427 a parallelized loop. */
1429 static tree
1430 create_loop_fn (location_t loc)
1432 char buf[100];
1433 char *tname;
1434 tree decl, type, name, t;
1435 struct function *act_cfun = cfun;
1436 static unsigned loopfn_num;
1438 loc = LOCATION_LOCUS (loc);
1439 snprintf (buf, 100, "%s.$loopfn", current_function_name ());
1440 ASM_FORMAT_PRIVATE_NAME (tname, buf, loopfn_num++);
1441 clean_symbol_name (tname);
1442 name = get_identifier (tname);
1443 type = build_function_type_list (void_type_node, ptr_type_node, NULL_TREE);
1445 decl = build_decl (loc, FUNCTION_DECL, name, type);
1446 TREE_STATIC (decl) = 1;
1447 TREE_USED (decl) = 1;
1448 DECL_ARTIFICIAL (decl) = 1;
1449 DECL_IGNORED_P (decl) = 0;
1450 TREE_PUBLIC (decl) = 0;
1451 DECL_UNINLINABLE (decl) = 1;
1452 DECL_EXTERNAL (decl) = 0;
1453 DECL_CONTEXT (decl) = NULL_TREE;
1454 DECL_INITIAL (decl) = make_node (BLOCK);
1456 t = build_decl (loc, RESULT_DECL, NULL_TREE, void_type_node);
1457 DECL_ARTIFICIAL (t) = 1;
1458 DECL_IGNORED_P (t) = 1;
1459 DECL_RESULT (decl) = t;
1461 t = build_decl (loc, PARM_DECL, get_identifier (".paral_data_param"),
1462 ptr_type_node);
1463 DECL_ARTIFICIAL (t) = 1;
1464 DECL_ARG_TYPE (t) = ptr_type_node;
1465 DECL_CONTEXT (t) = decl;
1466 TREE_USED (t) = 1;
1467 DECL_ARGUMENTS (decl) = t;
1469 allocate_struct_function (decl, false);
1471 /* The call to allocate_struct_function clobbers CFUN, so we need to restore
1472 it. */
1473 set_cfun (act_cfun);
1475 return decl;
1478 /* Replace uses of NAME by VAL in block BB. */
1480 static void
1481 replace_uses_in_bb_by (tree name, tree val, basic_block bb)
1483 gimple use_stmt;
1484 imm_use_iterator imm_iter;
1486 FOR_EACH_IMM_USE_STMT (use_stmt, imm_iter, name)
1488 if (gimple_bb (use_stmt) != bb)
1489 continue;
1491 use_operand_p use_p;
1492 FOR_EACH_IMM_USE_ON_STMT (use_p, imm_iter)
1493 SET_USE (use_p, val);
1497 /* Replace uses of NAME by VAL in blocks BBS. */
1499 static void
1500 replace_uses_in_bbs_by (tree name, tree val, bitmap bbs)
1502 gimple use_stmt;
1503 imm_use_iterator imm_iter;
1505 FOR_EACH_IMM_USE_STMT (use_stmt, imm_iter, name)
1507 if (!bitmap_bit_p (bbs, gimple_bb (use_stmt)->index))
1508 continue;
1510 use_operand_p use_p;
1511 FOR_EACH_IMM_USE_ON_STMT (use_p, imm_iter)
1512 SET_USE (use_p, val);
1516 /* Do transformation from:
1518 <bb preheader>:
1520 goto <bb header>
1522 <bb header>:
1523 ivtmp_a = PHI <ivtmp_init (preheader), ivtmp_b (latch)>
1524 sum_a = PHI <sum_init (preheader), sum_b (latch)>
1526 use (ivtmp_a)
1528 sum_b = sum_a + sum_update
1530 if (ivtmp_a < n)
1531 goto <bb latch>;
1532 else
1533 goto <bb exit>;
1535 <bb latch>:
1536 ivtmp_b = ivtmp_a + 1;
1537 goto <bb header>
1539 <bb exit>:
1540 sum_z = PHI <sum_b (cond[1])>
1542 [1] Where <bb cond> is single_pred (bb latch); In the simplest case,
1543 that's <bb header>.
1547 <bb preheader>:
1549 goto <bb newheader>
1551 <bb header>:
1552 ivtmp_a = PHI <ivtmp_c (latch)>
1553 sum_a = PHI <sum_c (latch)>
1555 use (ivtmp_a)
1557 sum_b = sum_a + sum_update
1559 goto <bb latch>;
1561 <bb newheader>:
1562 ivtmp_c = PHI <ivtmp_init (preheader), ivtmp_b (latch)>
1563 sum_c = PHI <sum_init (preheader), sum_b (latch)>
1564 if (ivtmp_c < n + 1)
1565 goto <bb header>;
1566 else
1567 goto <bb exit>;
1569 <bb latch>:
1570 ivtmp_b = ivtmp_a + 1;
1571 goto <bb newheader>
1573 <bb exit>:
1574 sum_z = PHI <sum_c (newheader)>
1577 In unified diff format:
1579 <bb preheader>:
1581 - goto <bb header>
1582 + goto <bb newheader>
1584 <bb header>:
1585 - ivtmp_a = PHI <ivtmp_init (preheader), ivtmp_b (latch)>
1586 - sum_a = PHI <sum_init (preheader), sum_b (latch)>
1587 + ivtmp_a = PHI <ivtmp_c (latch)>
1588 + sum_a = PHI <sum_c (latch)>
1590 use (ivtmp_a)
1592 sum_b = sum_a + sum_update
1594 - if (ivtmp_a < n)
1595 - goto <bb latch>;
1596 + goto <bb latch>;
1598 + <bb newheader>:
1599 + ivtmp_c = PHI <ivtmp_init (preheader), ivtmp_b (latch)>
1600 + sum_c = PHI <sum_init (preheader), sum_b (latch)>
1601 + if (ivtmp_c < n + 1)
1602 + goto <bb header>;
1603 else
1604 goto <bb exit>;
1606 <bb latch>:
1607 ivtmp_b = ivtmp_a + 1;
1608 - goto <bb header>
1609 + goto <bb newheader>
1611 <bb exit>:
1612 - sum_z = PHI <sum_b (cond[1])>
1613 + sum_z = PHI <sum_c (newheader)>
1615 Note: the example does not show any virtual phis, but these are handled more
1616 or less as reductions.
1619 Moves the exit condition of LOOP to the beginning of its header.
1620 REDUCTION_LIST describes the reductions in LOOP. BOUND is the new loop
1621 bound. */
1623 static void
1624 transform_to_exit_first_loop_alt (struct loop *loop,
1625 reduction_info_table_type *reduction_list,
1626 tree bound)
1628 basic_block header = loop->header;
1629 basic_block latch = loop->latch;
1630 edge exit = single_dom_exit (loop);
1631 basic_block exit_block = exit->dest;
1632 gcond *cond_stmt = as_a <gcond *> (last_stmt (exit->src));
1633 tree control = gimple_cond_lhs (cond_stmt);
1634 edge e;
1636 /* Gather the bbs dominated by the exit block. */
1637 bitmap exit_dominated = BITMAP_ALLOC (NULL);
1638 bitmap_set_bit (exit_dominated, exit_block->index);
1639 vec<basic_block> exit_dominated_vec
1640 = get_dominated_by (CDI_DOMINATORS, exit_block);
1642 int i;
1643 basic_block dom_bb;
1644 FOR_EACH_VEC_ELT (exit_dominated_vec, i, dom_bb)
1645 bitmap_set_bit (exit_dominated, dom_bb->index);
1647 exit_dominated_vec.release ();
1649 /* Create the new_header block. */
1650 basic_block new_header = split_block_before_cond_jump (exit->src);
1651 edge split_edge = single_pred_edge (new_header);
1653 /* Redirect entry edge to new_header. */
1654 edge entry = loop_preheader_edge (loop);
1655 e = redirect_edge_and_branch (entry, new_header);
1656 gcc_assert (e == entry);
1658 /* Redirect post_inc_edge to new_header. */
1659 edge post_inc_edge = single_succ_edge (latch);
1660 e = redirect_edge_and_branch (post_inc_edge, new_header);
1661 gcc_assert (e == post_inc_edge);
1663 /* Redirect post_cond_edge to header. */
1664 edge post_cond_edge = single_pred_edge (latch);
1665 e = redirect_edge_and_branch (post_cond_edge, header);
1666 gcc_assert (e == post_cond_edge);
1668 /* Redirect split_edge to latch. */
1669 e = redirect_edge_and_branch (split_edge, latch);
1670 gcc_assert (e == split_edge);
1672 /* Set the new loop bound. */
1673 gimple_cond_set_rhs (cond_stmt, bound);
1674 update_stmt (cond_stmt);
1676 /* Repair the ssa. */
1677 vec<edge_var_map> *v = redirect_edge_var_map_vector (post_inc_edge);
1678 edge_var_map *vm;
1679 gphi_iterator gsi;
1680 for (gsi = gsi_start_phis (header), i = 0;
1681 !gsi_end_p (gsi) && v->iterate (i, &vm);
1682 gsi_next (&gsi), i++)
1684 gphi *phi = gsi.phi ();
1685 tree res_a = PHI_RESULT (phi);
1687 /* Create new phi. */
1688 tree res_c = copy_ssa_name (res_a, phi);
1689 gphi *nphi = create_phi_node (res_c, new_header);
1691 /* Replace ivtmp_a with ivtmp_c in condition 'if (ivtmp_a < n)'. */
1692 replace_uses_in_bb_by (res_a, res_c, new_header);
1694 /* Replace ivtmp/sum_b with ivtmp/sum_c in header phi. */
1695 add_phi_arg (phi, res_c, post_cond_edge, UNKNOWN_LOCATION);
1697 /* Replace sum_b with sum_c in exit phi. Loop-closed ssa does not hold
1698 for virtuals, so we cannot get away with exit_block only. */
1699 tree res_b = redirect_edge_var_map_def (vm);
1700 replace_uses_in_bbs_by (res_b, res_c, exit_dominated);
1702 struct reduction_info *red = reduction_phi (reduction_list, phi);
1703 gcc_assert (virtual_operand_p (res_a)
1704 || res_a == control
1705 || red != NULL);
1707 if (red)
1709 /* Register the new reduction phi. */
1710 red->reduc_phi = nphi;
1711 gimple_set_uid (red->reduc_phi, red->reduc_version);
1714 gcc_assert (gsi_end_p (gsi) && !v->iterate (i, &vm));
1715 BITMAP_FREE (exit_dominated);
1717 /* Set the preheader argument of the new phis to ivtmp/sum_init. */
1718 flush_pending_stmts (entry);
1720 /* Set the latch arguments of the new phis to ivtmp/sum_b. */
1721 flush_pending_stmts (post_inc_edge);
1723 /* Register the reduction exit phis. */
1724 for (gphi_iterator gsi = gsi_start_phis (exit_block);
1725 !gsi_end_p (gsi);
1726 gsi_next (&gsi))
1728 gphi *phi = gsi.phi ();
1729 tree res_z = PHI_RESULT (phi);
1730 if (virtual_operand_p (res_z))
1731 continue;
1733 tree res_c = PHI_ARG_DEF_FROM_EDGE (phi, exit);
1734 gimple reduc_phi = SSA_NAME_DEF_STMT (res_c);
1735 struct reduction_info *red = reduction_phi (reduction_list, reduc_phi);
1736 if (red != NULL)
1737 red->keep_res = phi;
1740 /* We're going to cancel the loop at the end of gen_parallel_loop, but until
1741 then we're still using some fields, so only bother about fields that are
1742 still used: header and latch.
1743 The loop has a new header bb, so we update it. The latch bb stays the
1744 same. */
1745 loop->header = new_header;
1747 /* Recalculate dominance info. */
1748 free_dominance_info (CDI_DOMINATORS);
1749 calculate_dominance_info (CDI_DOMINATORS);
1752 /* Tries to moves the exit condition of LOOP to the beginning of its header
1753 without duplication of the loop body. NIT is the number of iterations of the
1754 loop. REDUCTION_LIST describes the reductions in LOOP. Return true if
1755 transformation is successful. */
1757 static bool
1758 try_transform_to_exit_first_loop_alt (struct loop *loop,
1759 reduction_info_table_type *reduction_list,
1760 tree nit)
1762 /* Check whether the latch contains a single statement. */
1763 if (!gimple_seq_nondebug_singleton_p (bb_seq (loop->latch)))
1764 return false;
1766 /* Check whether the latch contains the loop iv increment. */
1767 edge back = single_succ_edge (loop->latch);
1768 edge exit = single_dom_exit (loop);
1769 gcond *cond_stmt = as_a <gcond *> (last_stmt (exit->src));
1770 tree control = gimple_cond_lhs (cond_stmt);
1771 gphi *phi = as_a <gphi *> (SSA_NAME_DEF_STMT (control));
1772 tree inc_res = gimple_phi_arg_def (phi, back->dest_idx);
1773 if (gimple_bb (SSA_NAME_DEF_STMT (inc_res)) != loop->latch)
1774 return false;
1776 /* Check whether there's no code between the loop condition and the latch. */
1777 if (!single_pred_p (loop->latch)
1778 || single_pred (loop->latch) != exit->src)
1779 return false;
1781 tree alt_bound = NULL_TREE;
1782 tree nit_type = TREE_TYPE (nit);
1784 /* Figure out whether nit + 1 overflows. */
1785 if (TREE_CODE (nit) == INTEGER_CST)
1787 if (!tree_int_cst_equal (nit, TYPE_MAXVAL (nit_type)))
1789 alt_bound = fold_build2_loc (UNKNOWN_LOCATION, PLUS_EXPR, nit_type,
1790 nit, build_one_cst (nit_type));
1792 gcc_assert (TREE_CODE (alt_bound) == INTEGER_CST);
1794 else
1796 /* Todo: Figure out if we can trigger this, if it's worth to handle
1797 optimally, and if we can handle it optimally. */
1800 else
1802 gcc_assert (TREE_CODE (nit) == SSA_NAME);
1804 gimple def = SSA_NAME_DEF_STMT (nit);
1806 if (def
1807 && is_gimple_assign (def)
1808 && gimple_assign_rhs_code (def) == PLUS_EXPR)
1810 tree op1 = gimple_assign_rhs1 (def);
1811 tree op2 = gimple_assign_rhs2 (def);
1812 if (integer_minus_onep (op1))
1813 alt_bound = op2;
1814 else if (integer_minus_onep (op2))
1815 alt_bound = op1;
1818 /* There is a number of test-cases for which we don't get an alt_bound
1819 here: they're listed here, with the lhs of the last stmt as the nit:
1821 libgomp.graphite/force-parallel-1.c:
1822 _21 = (signed long) N_6(D);
1823 _19 = _21 + -1;
1824 _7 = (unsigned long) _19;
1826 libgomp.graphite/force-parallel-2.c:
1827 _33 = (signed long) N_9(D);
1828 _16 = _33 + -1;
1829 _37 = (unsigned long) _16;
1831 libgomp.graphite/force-parallel-5.c:
1832 <bb 6>:
1833 # graphite_IV.5_46 = PHI <0(5), graphite_IV.5_47(11)>
1834 <bb 7>:
1835 _33 = (unsigned long) graphite_IV.5_46;
1837 g++.dg/tree-ssa/pr34355.C:
1838 _2 = (unsigned int) i_9;
1839 _3 = 4 - _2;
1841 gcc.dg/pr53849.c:
1842 _5 = d.0_11 + -2;
1843 _18 = (unsigned int) _5;
1845 We will be able to handle some of these cases, if we can determine when
1846 it's safe to look past casts. */
1849 if (alt_bound == NULL_TREE)
1850 return false;
1852 transform_to_exit_first_loop_alt (loop, reduction_list, alt_bound);
1853 return true;
1856 /* Moves the exit condition of LOOP to the beginning of its header. NIT is the
1857 number of iterations of the loop. REDUCTION_LIST describes the reductions in
1858 LOOP. */
1860 static void
1861 transform_to_exit_first_loop (struct loop *loop,
1862 reduction_info_table_type *reduction_list,
1863 tree nit)
1865 basic_block *bbs, *nbbs, ex_bb, orig_header;
1866 unsigned n;
1867 bool ok;
1868 edge exit = single_dom_exit (loop), hpred;
1869 tree control, control_name, res, t;
1870 gphi *phi, *nphi;
1871 gassign *stmt;
1872 gcond *cond_stmt, *cond_nit;
1873 tree nit_1;
1875 split_block_after_labels (loop->header);
1876 orig_header = single_succ (loop->header);
1877 hpred = single_succ_edge (loop->header);
1879 cond_stmt = as_a <gcond *> (last_stmt (exit->src));
1880 control = gimple_cond_lhs (cond_stmt);
1881 gcc_assert (gimple_cond_rhs (cond_stmt) == nit);
1883 /* Make sure that we have phi nodes on exit for all loop header phis
1884 (create_parallel_loop requires that). */
1885 for (gphi_iterator gsi = gsi_start_phis (loop->header);
1886 !gsi_end_p (gsi);
1887 gsi_next (&gsi))
1889 phi = gsi.phi ();
1890 res = PHI_RESULT (phi);
1891 t = copy_ssa_name (res, phi);
1892 SET_PHI_RESULT (phi, t);
1893 nphi = create_phi_node (res, orig_header);
1894 add_phi_arg (nphi, t, hpred, UNKNOWN_LOCATION);
1896 if (res == control)
1898 gimple_cond_set_lhs (cond_stmt, t);
1899 update_stmt (cond_stmt);
1900 control = t;
1904 bbs = get_loop_body_in_dom_order (loop);
1906 for (n = 0; bbs[n] != exit->src; n++)
1907 continue;
1908 nbbs = XNEWVEC (basic_block, n);
1909 ok = gimple_duplicate_sese_tail (single_succ_edge (loop->header), exit,
1910 bbs + 1, n, nbbs);
1911 gcc_assert (ok);
1912 free (bbs);
1913 ex_bb = nbbs[0];
1914 free (nbbs);
1916 /* Other than reductions, the only gimple reg that should be copied
1917 out of the loop is the control variable. */
1918 exit = single_dom_exit (loop);
1919 control_name = NULL_TREE;
1920 for (gphi_iterator gsi = gsi_start_phis (ex_bb);
1921 !gsi_end_p (gsi); )
1923 phi = gsi.phi ();
1924 res = PHI_RESULT (phi);
1925 if (virtual_operand_p (res))
1927 gsi_next (&gsi);
1928 continue;
1931 /* Check if it is a part of reduction. If it is,
1932 keep the phi at the reduction's keep_res field. The
1933 PHI_RESULT of this phi is the resulting value of the reduction
1934 variable when exiting the loop. */
1936 if (reduction_list->elements () > 0)
1938 struct reduction_info *red;
1940 tree val = PHI_ARG_DEF_FROM_EDGE (phi, exit);
1941 red = reduction_phi (reduction_list, SSA_NAME_DEF_STMT (val));
1942 if (red)
1944 red->keep_res = phi;
1945 gsi_next (&gsi);
1946 continue;
1949 gcc_assert (control_name == NULL_TREE
1950 && SSA_NAME_VAR (res) == SSA_NAME_VAR (control));
1951 control_name = res;
1952 remove_phi_node (&gsi, false);
1954 gcc_assert (control_name != NULL_TREE);
1956 /* Initialize the control variable to number of iterations
1957 according to the rhs of the exit condition. */
1958 gimple_stmt_iterator gsi = gsi_after_labels (ex_bb);
1959 cond_nit = as_a <gcond *> (last_stmt (exit->src));
1960 nit_1 = gimple_cond_rhs (cond_nit);
1961 nit_1 = force_gimple_operand_gsi (&gsi,
1962 fold_convert (TREE_TYPE (control_name), nit_1),
1963 false, NULL_TREE, false, GSI_SAME_STMT);
1964 stmt = gimple_build_assign (control_name, nit_1);
1965 gsi_insert_before (&gsi, stmt, GSI_NEW_STMT);
1968 /* Create the parallel constructs for LOOP as described in gen_parallel_loop.
1969 LOOP_FN and DATA are the arguments of GIMPLE_OMP_PARALLEL.
1970 NEW_DATA is the variable that should be initialized from the argument
1971 of LOOP_FN. N_THREADS is the requested number of threads. Returns the
1972 basic block containing GIMPLE_OMP_PARALLEL tree. */
1974 static basic_block
1975 create_parallel_loop (struct loop *loop, tree loop_fn, tree data,
1976 tree new_data, unsigned n_threads, location_t loc)
1978 gimple_stmt_iterator gsi;
1979 basic_block bb, paral_bb, for_bb, ex_bb;
1980 tree t, param;
1981 gomp_parallel *omp_par_stmt;
1982 gimple omp_return_stmt1, omp_return_stmt2;
1983 gimple phi;
1984 gcond *cond_stmt;
1985 gomp_for *for_stmt;
1986 gomp_continue *omp_cont_stmt;
1987 tree cvar, cvar_init, initvar, cvar_next, cvar_base, type;
1988 edge exit, nexit, guard, end, e;
1990 /* Prepare the GIMPLE_OMP_PARALLEL statement. */
1991 bb = loop_preheader_edge (loop)->src;
1992 paral_bb = single_pred (bb);
1993 gsi = gsi_last_bb (paral_bb);
1995 t = build_omp_clause (loc, OMP_CLAUSE_NUM_THREADS);
1996 OMP_CLAUSE_NUM_THREADS_EXPR (t)
1997 = build_int_cst (integer_type_node, n_threads);
1998 omp_par_stmt = gimple_build_omp_parallel (NULL, t, loop_fn, data);
1999 gimple_set_location (omp_par_stmt, loc);
2001 gsi_insert_after (&gsi, omp_par_stmt, GSI_NEW_STMT);
2003 /* Initialize NEW_DATA. */
2004 if (data)
2006 gassign *assign_stmt;
2008 gsi = gsi_after_labels (bb);
2010 param = make_ssa_name (DECL_ARGUMENTS (loop_fn));
2011 assign_stmt = gimple_build_assign (param, build_fold_addr_expr (data));
2012 gsi_insert_before (&gsi, assign_stmt, GSI_SAME_STMT);
2014 assign_stmt = gimple_build_assign (new_data,
2015 fold_convert (TREE_TYPE (new_data), param));
2016 gsi_insert_before (&gsi, assign_stmt, GSI_SAME_STMT);
2019 /* Emit GIMPLE_OMP_RETURN for GIMPLE_OMP_PARALLEL. */
2020 bb = split_loop_exit_edge (single_dom_exit (loop));
2021 gsi = gsi_last_bb (bb);
2022 omp_return_stmt1 = gimple_build_omp_return (false);
2023 gimple_set_location (omp_return_stmt1, loc);
2024 gsi_insert_after (&gsi, omp_return_stmt1, GSI_NEW_STMT);
2026 /* Extract data for GIMPLE_OMP_FOR. */
2027 gcc_assert (loop->header == single_dom_exit (loop)->src);
2028 cond_stmt = as_a <gcond *> (last_stmt (loop->header));
2030 cvar = gimple_cond_lhs (cond_stmt);
2031 cvar_base = SSA_NAME_VAR (cvar);
2032 phi = SSA_NAME_DEF_STMT (cvar);
2033 cvar_init = PHI_ARG_DEF_FROM_EDGE (phi, loop_preheader_edge (loop));
2034 initvar = copy_ssa_name (cvar);
2035 SET_USE (PHI_ARG_DEF_PTR_FROM_EDGE (phi, loop_preheader_edge (loop)),
2036 initvar);
2037 cvar_next = PHI_ARG_DEF_FROM_EDGE (phi, loop_latch_edge (loop));
2039 gsi = gsi_last_nondebug_bb (loop->latch);
2040 gcc_assert (gsi_stmt (gsi) == SSA_NAME_DEF_STMT (cvar_next));
2041 gsi_remove (&gsi, true);
2043 /* Prepare cfg. */
2044 for_bb = split_edge (loop_preheader_edge (loop));
2045 ex_bb = split_loop_exit_edge (single_dom_exit (loop));
2046 extract_true_false_edges_from_block (loop->header, &nexit, &exit);
2047 gcc_assert (exit == single_dom_exit (loop));
2049 guard = make_edge (for_bb, ex_bb, 0);
2050 single_succ_edge (loop->latch)->flags = 0;
2051 end = make_edge (loop->latch, ex_bb, EDGE_FALLTHRU);
2052 for (gphi_iterator gpi = gsi_start_phis (ex_bb);
2053 !gsi_end_p (gpi); gsi_next (&gpi))
2055 source_location locus;
2056 tree def;
2057 gphi *phi = gpi.phi ();
2058 gphi *stmt;
2060 stmt = as_a <gphi *> (
2061 SSA_NAME_DEF_STMT (PHI_ARG_DEF_FROM_EDGE (phi, exit)));
2063 def = PHI_ARG_DEF_FROM_EDGE (stmt, loop_preheader_edge (loop));
2064 locus = gimple_phi_arg_location_from_edge (stmt,
2065 loop_preheader_edge (loop));
2066 add_phi_arg (phi, def, guard, locus);
2068 def = PHI_ARG_DEF_FROM_EDGE (stmt, loop_latch_edge (loop));
2069 locus = gimple_phi_arg_location_from_edge (stmt, loop_latch_edge (loop));
2070 add_phi_arg (phi, def, end, locus);
2072 e = redirect_edge_and_branch (exit, nexit->dest);
2073 PENDING_STMT (e) = NULL;
2075 /* Emit GIMPLE_OMP_FOR. */
2076 gimple_cond_set_lhs (cond_stmt, cvar_base);
2077 type = TREE_TYPE (cvar);
2078 t = build_omp_clause (loc, OMP_CLAUSE_SCHEDULE);
2079 OMP_CLAUSE_SCHEDULE_KIND (t) = OMP_CLAUSE_SCHEDULE_STATIC;
2081 for_stmt = gimple_build_omp_for (NULL, GF_OMP_FOR_KIND_FOR, t, 1, NULL);
2082 gimple_set_location (for_stmt, loc);
2083 gimple_omp_for_set_index (for_stmt, 0, initvar);
2084 gimple_omp_for_set_initial (for_stmt, 0, cvar_init);
2085 gimple_omp_for_set_final (for_stmt, 0, gimple_cond_rhs (cond_stmt));
2086 gimple_omp_for_set_cond (for_stmt, 0, gimple_cond_code (cond_stmt));
2087 gimple_omp_for_set_incr (for_stmt, 0, build2 (PLUS_EXPR, type,
2088 cvar_base,
2089 build_int_cst (type, 1)));
2091 gsi = gsi_last_bb (for_bb);
2092 gsi_insert_after (&gsi, for_stmt, GSI_NEW_STMT);
2093 SSA_NAME_DEF_STMT (initvar) = for_stmt;
2095 /* Emit GIMPLE_OMP_CONTINUE. */
2096 gsi = gsi_last_bb (loop->latch);
2097 omp_cont_stmt = gimple_build_omp_continue (cvar_next, cvar);
2098 gimple_set_location (omp_cont_stmt, loc);
2099 gsi_insert_after (&gsi, omp_cont_stmt, GSI_NEW_STMT);
2100 SSA_NAME_DEF_STMT (cvar_next) = omp_cont_stmt;
2102 /* Emit GIMPLE_OMP_RETURN for GIMPLE_OMP_FOR. */
2103 gsi = gsi_last_bb (ex_bb);
2104 omp_return_stmt2 = gimple_build_omp_return (true);
2105 gimple_set_location (omp_return_stmt2, loc);
2106 gsi_insert_after (&gsi, omp_return_stmt2, GSI_NEW_STMT);
2108 /* After the above dom info is hosed. Re-compute it. */
2109 free_dominance_info (CDI_DOMINATORS);
2110 calculate_dominance_info (CDI_DOMINATORS);
2112 return paral_bb;
2115 /* Generates code to execute the iterations of LOOP in N_THREADS
2116 threads in parallel.
2118 NITER describes number of iterations of LOOP.
2119 REDUCTION_LIST describes the reductions existent in the LOOP. */
2121 static void
2122 gen_parallel_loop (struct loop *loop,
2123 reduction_info_table_type *reduction_list,
2124 unsigned n_threads, struct tree_niter_desc *niter)
2126 tree many_iterations_cond, type, nit;
2127 tree arg_struct, new_arg_struct;
2128 gimple_seq stmts;
2129 edge entry, exit;
2130 struct clsn_data clsn_data;
2131 unsigned prob;
2132 location_t loc;
2133 gimple cond_stmt;
2134 unsigned int m_p_thread=2;
2136 /* From
2138 ---------------------------------------------------------------------
2139 loop
2141 IV = phi (INIT, IV + STEP)
2142 BODY1;
2143 if (COND)
2144 break;
2145 BODY2;
2147 ---------------------------------------------------------------------
2149 with # of iterations NITER (possibly with MAY_BE_ZERO assumption),
2150 we generate the following code:
2152 ---------------------------------------------------------------------
2154 if (MAY_BE_ZERO
2155 || NITER < MIN_PER_THREAD * N_THREADS)
2156 goto original;
2158 BODY1;
2159 store all local loop-invariant variables used in body of the loop to DATA.
2160 GIMPLE_OMP_PARALLEL (OMP_CLAUSE_NUM_THREADS (N_THREADS), LOOPFN, DATA);
2161 load the variables from DATA.
2162 GIMPLE_OMP_FOR (IV = INIT; COND; IV += STEP) (OMP_CLAUSE_SCHEDULE (static))
2163 BODY2;
2164 BODY1;
2165 GIMPLE_OMP_CONTINUE;
2166 GIMPLE_OMP_RETURN -- GIMPLE_OMP_FOR
2167 GIMPLE_OMP_RETURN -- GIMPLE_OMP_PARALLEL
2168 goto end;
2170 original:
2171 loop
2173 IV = phi (INIT, IV + STEP)
2174 BODY1;
2175 if (COND)
2176 break;
2177 BODY2;
2180 end:
2184 /* Create two versions of the loop -- in the old one, we know that the
2185 number of iterations is large enough, and we will transform it into the
2186 loop that will be split to loop_fn, the new one will be used for the
2187 remaining iterations. */
2189 /* We should compute a better number-of-iterations value for outer loops.
2190 That is, if we have
2192 for (i = 0; i < n; ++i)
2193 for (j = 0; j < m; ++j)
2196 we should compute nit = n * m, not nit = n.
2197 Also may_be_zero handling would need to be adjusted. */
2199 type = TREE_TYPE (niter->niter);
2200 nit = force_gimple_operand (unshare_expr (niter->niter), &stmts, true,
2201 NULL_TREE);
2202 if (stmts)
2203 gsi_insert_seq_on_edge_immediate (loop_preheader_edge (loop), stmts);
2205 if (loop->inner)
2206 m_p_thread=2;
2207 else
2208 m_p_thread=MIN_PER_THREAD;
2210 many_iterations_cond =
2211 fold_build2 (GE_EXPR, boolean_type_node,
2212 nit, build_int_cst (type, m_p_thread * n_threads));
2214 many_iterations_cond
2215 = fold_build2 (TRUTH_AND_EXPR, boolean_type_node,
2216 invert_truthvalue (unshare_expr (niter->may_be_zero)),
2217 many_iterations_cond);
2218 many_iterations_cond
2219 = force_gimple_operand (many_iterations_cond, &stmts, false, NULL_TREE);
2220 if (stmts)
2221 gsi_insert_seq_on_edge_immediate (loop_preheader_edge (loop), stmts);
2222 if (!is_gimple_condexpr (many_iterations_cond))
2224 many_iterations_cond
2225 = force_gimple_operand (many_iterations_cond, &stmts,
2226 true, NULL_TREE);
2227 if (stmts)
2228 gsi_insert_seq_on_edge_immediate (loop_preheader_edge (loop), stmts);
2231 initialize_original_copy_tables ();
2233 /* We assume that the loop usually iterates a lot. */
2234 prob = 4 * REG_BR_PROB_BASE / 5;
2235 loop_version (loop, many_iterations_cond, NULL,
2236 prob, prob, REG_BR_PROB_BASE - prob, true);
2237 update_ssa (TODO_update_ssa);
2238 free_original_copy_tables ();
2240 /* Base all the induction variables in LOOP on a single control one. */
2241 canonicalize_loop_ivs (loop, &nit, true);
2243 /* Ensure that the exit condition is the first statement in the loop.
2244 The common case is that latch of the loop is empty (apart from the
2245 increment) and immediately follows the loop exit test. Attempt to move the
2246 entry of the loop directly before the exit check and increase the number of
2247 iterations of the loop by one. */
2248 if (!try_transform_to_exit_first_loop_alt (loop, reduction_list, nit))
2250 /* Fall back on the method that handles more cases, but duplicates the
2251 loop body: move the exit condition of LOOP to the beginning of its
2252 header, and duplicate the part of the last iteration that gets disabled
2253 to the exit of the loop. */
2254 transform_to_exit_first_loop (loop, reduction_list, nit);
2257 /* Generate initializations for reductions. */
2258 if (reduction_list->elements () > 0)
2259 reduction_list->traverse <struct loop *, initialize_reductions> (loop);
2261 /* Eliminate the references to local variables from the loop. */
2262 gcc_assert (single_exit (loop));
2263 entry = loop_preheader_edge (loop);
2264 exit = single_dom_exit (loop);
2266 eliminate_local_variables (entry, exit);
2267 /* In the old loop, move all variables non-local to the loop to a structure
2268 and back, and create separate decls for the variables used in loop. */
2269 separate_decls_in_region (entry, exit, reduction_list, &arg_struct,
2270 &new_arg_struct, &clsn_data);
2272 /* Create the parallel constructs. */
2273 loc = UNKNOWN_LOCATION;
2274 cond_stmt = last_stmt (loop->header);
2275 if (cond_stmt)
2276 loc = gimple_location (cond_stmt);
2277 create_parallel_loop (loop, create_loop_fn (loc), arg_struct,
2278 new_arg_struct, n_threads, loc);
2279 if (reduction_list->elements () > 0)
2280 create_call_for_reduction (loop, reduction_list, &clsn_data);
2282 scev_reset ();
2284 /* Cancel the loop (it is simpler to do it here rather than to teach the
2285 expander to do it). */
2286 cancel_loop_tree (loop);
2288 /* Free loop bound estimations that could contain references to
2289 removed statements. */
2290 FOR_EACH_LOOP (loop, 0)
2291 free_numbers_of_iterations_estimates_loop (loop);
2294 /* Returns true when LOOP contains vector phi nodes. */
2296 static bool
2297 loop_has_vector_phi_nodes (struct loop *loop ATTRIBUTE_UNUSED)
2299 unsigned i;
2300 basic_block *bbs = get_loop_body_in_dom_order (loop);
2301 gphi_iterator gsi;
2302 bool res = true;
2304 for (i = 0; i < loop->num_nodes; i++)
2305 for (gsi = gsi_start_phis (bbs[i]); !gsi_end_p (gsi); gsi_next (&gsi))
2306 if (TREE_CODE (TREE_TYPE (PHI_RESULT (gsi.phi ()))) == VECTOR_TYPE)
2307 goto end;
2309 res = false;
2310 end:
2311 free (bbs);
2312 return res;
2315 /* Create a reduction_info struct, initialize it with REDUC_STMT
2316 and PHI, insert it to the REDUCTION_LIST. */
2318 static void
2319 build_new_reduction (reduction_info_table_type *reduction_list,
2320 gimple reduc_stmt, gphi *phi)
2322 reduction_info **slot;
2323 struct reduction_info *new_reduction;
2325 gcc_assert (reduc_stmt);
2327 if (dump_file && (dump_flags & TDF_DETAILS))
2329 fprintf (dump_file,
2330 "Detected reduction. reduction stmt is: \n");
2331 print_gimple_stmt (dump_file, reduc_stmt, 0, 0);
2332 fprintf (dump_file, "\n");
2335 new_reduction = XCNEW (struct reduction_info);
2337 new_reduction->reduc_stmt = reduc_stmt;
2338 new_reduction->reduc_phi = phi;
2339 new_reduction->reduc_version = SSA_NAME_VERSION (gimple_phi_result (phi));
2340 new_reduction->reduction_code = gimple_assign_rhs_code (reduc_stmt);
2341 slot = reduction_list->find_slot (new_reduction, INSERT);
2342 *slot = new_reduction;
2345 /* Callback for htab_traverse. Sets gimple_uid of reduc_phi stmts. */
2348 set_reduc_phi_uids (reduction_info **slot, void *data ATTRIBUTE_UNUSED)
2350 struct reduction_info *const red = *slot;
2351 gimple_set_uid (red->reduc_phi, red->reduc_version);
2352 return 1;
2355 /* Detect all reductions in the LOOP, insert them into REDUCTION_LIST. */
2357 static void
2358 gather_scalar_reductions (loop_p loop, reduction_info_table_type *reduction_list)
2360 gphi_iterator gsi;
2361 loop_vec_info simple_loop_info;
2363 simple_loop_info = vect_analyze_loop_form (loop);
2365 for (gsi = gsi_start_phis (loop->header); !gsi_end_p (gsi); gsi_next (&gsi))
2367 gphi *phi = gsi.phi ();
2368 affine_iv iv;
2369 tree res = PHI_RESULT (phi);
2370 bool double_reduc;
2372 if (virtual_operand_p (res))
2373 continue;
2375 if (!simple_iv (loop, loop, res, &iv, true)
2376 && simple_loop_info)
2378 gimple reduc_stmt = vect_force_simple_reduction (simple_loop_info,
2379 phi, true,
2380 &double_reduc);
2381 if (reduc_stmt && !double_reduc)
2382 build_new_reduction (reduction_list, reduc_stmt, phi);
2385 destroy_loop_vec_info (simple_loop_info, true);
2387 /* As gimple_uid is used by the vectorizer in between vect_analyze_loop_form
2388 and destroy_loop_vec_info, we can set gimple_uid of reduc_phi stmts
2389 only now. */
2390 reduction_list->traverse <void *, set_reduc_phi_uids> (NULL);
2393 /* Try to initialize NITER for code generation part. */
2395 static bool
2396 try_get_loop_niter (loop_p loop, struct tree_niter_desc *niter)
2398 edge exit = single_dom_exit (loop);
2400 gcc_assert (exit);
2402 /* We need to know # of iterations, and there should be no uses of values
2403 defined inside loop outside of it, unless the values are invariants of
2404 the loop. */
2405 if (!number_of_iterations_exit (loop, exit, niter, false))
2407 if (dump_file && (dump_flags & TDF_DETAILS))
2408 fprintf (dump_file, " FAILED: number of iterations not known\n");
2409 return false;
2412 return true;
2415 /* Try to initialize REDUCTION_LIST for code generation part.
2416 REDUCTION_LIST describes the reductions. */
2418 static bool
2419 try_create_reduction_list (loop_p loop,
2420 reduction_info_table_type *reduction_list)
2422 edge exit = single_dom_exit (loop);
2423 gphi_iterator gsi;
2425 gcc_assert (exit);
2427 gather_scalar_reductions (loop, reduction_list);
2430 for (gsi = gsi_start_phis (exit->dest); !gsi_end_p (gsi); gsi_next (&gsi))
2432 gphi *phi = gsi.phi ();
2433 struct reduction_info *red;
2434 imm_use_iterator imm_iter;
2435 use_operand_p use_p;
2436 gimple reduc_phi;
2437 tree val = PHI_ARG_DEF_FROM_EDGE (phi, exit);
2439 if (!virtual_operand_p (val))
2441 if (dump_file && (dump_flags & TDF_DETAILS))
2443 fprintf (dump_file, "phi is ");
2444 print_gimple_stmt (dump_file, phi, 0, 0);
2445 fprintf (dump_file, "arg of phi to exit: value ");
2446 print_generic_expr (dump_file, val, 0);
2447 fprintf (dump_file, " used outside loop\n");
2448 fprintf (dump_file,
2449 " checking if it a part of reduction pattern: \n");
2451 if (reduction_list->elements () == 0)
2453 if (dump_file && (dump_flags & TDF_DETAILS))
2454 fprintf (dump_file,
2455 " FAILED: it is not a part of reduction.\n");
2456 return false;
2458 reduc_phi = NULL;
2459 FOR_EACH_IMM_USE_FAST (use_p, imm_iter, val)
2461 if (!gimple_debug_bind_p (USE_STMT (use_p))
2462 && flow_bb_inside_loop_p (loop, gimple_bb (USE_STMT (use_p))))
2464 reduc_phi = USE_STMT (use_p);
2465 break;
2468 red = reduction_phi (reduction_list, reduc_phi);
2469 if (red == NULL)
2471 if (dump_file && (dump_flags & TDF_DETAILS))
2472 fprintf (dump_file,
2473 " FAILED: it is not a part of reduction.\n");
2474 return false;
2476 if (dump_file && (dump_flags & TDF_DETAILS))
2478 fprintf (dump_file, "reduction phi is ");
2479 print_gimple_stmt (dump_file, red->reduc_phi, 0, 0);
2480 fprintf (dump_file, "reduction stmt is ");
2481 print_gimple_stmt (dump_file, red->reduc_stmt, 0, 0);
2486 /* The iterations of the loop may communicate only through bivs whose
2487 iteration space can be distributed efficiently. */
2488 for (gsi = gsi_start_phis (loop->header); !gsi_end_p (gsi); gsi_next (&gsi))
2490 gphi *phi = gsi.phi ();
2491 tree def = PHI_RESULT (phi);
2492 affine_iv iv;
2494 if (!virtual_operand_p (def) && !simple_iv (loop, loop, def, &iv, true))
2496 struct reduction_info *red;
2498 red = reduction_phi (reduction_list, phi);
2499 if (red == NULL)
2501 if (dump_file && (dump_flags & TDF_DETAILS))
2502 fprintf (dump_file,
2503 " FAILED: scalar dependency between iterations\n");
2504 return false;
2510 return true;
2513 /* Detect parallel loops and generate parallel code using libgomp
2514 primitives. Returns true if some loop was parallelized, false
2515 otherwise. */
2517 static bool
2518 parallelize_loops (void)
2520 unsigned n_threads = flag_tree_parallelize_loops;
2521 bool changed = false;
2522 struct loop *loop;
2523 struct tree_niter_desc niter_desc;
2524 struct obstack parloop_obstack;
2525 HOST_WIDE_INT estimated;
2526 source_location loop_loc;
2528 /* Do not parallelize loops in the functions created by parallelization. */
2529 if (parallelized_function_p (cfun->decl))
2530 return false;
2531 if (cfun->has_nonlocal_label)
2532 return false;
2534 gcc_obstack_init (&parloop_obstack);
2535 reduction_info_table_type reduction_list (10);
2536 init_stmt_vec_info_vec ();
2538 FOR_EACH_LOOP (loop, 0)
2540 reduction_list.empty ();
2541 if (dump_file && (dump_flags & TDF_DETAILS))
2543 fprintf (dump_file, "Trying loop %d as candidate\n",loop->num);
2544 if (loop->inner)
2545 fprintf (dump_file, "loop %d is not innermost\n",loop->num);
2546 else
2547 fprintf (dump_file, "loop %d is innermost\n",loop->num);
2550 /* If we use autopar in graphite pass, we use its marked dependency
2551 checking results. */
2552 if (flag_loop_parallelize_all && !loop->can_be_parallel)
2554 if (dump_file && (dump_flags & TDF_DETAILS))
2555 fprintf (dump_file, "loop is not parallel according to graphite\n");
2556 continue;
2559 if (!single_dom_exit (loop))
2562 if (dump_file && (dump_flags & TDF_DETAILS))
2563 fprintf (dump_file, "loop is !single_dom_exit\n");
2565 continue;
2568 if (/* And of course, the loop must be parallelizable. */
2569 !can_duplicate_loop_p (loop)
2570 || loop_has_blocks_with_irreducible_flag (loop)
2571 || (loop_preheader_edge (loop)->src->flags & BB_IRREDUCIBLE_LOOP)
2572 /* FIXME: the check for vector phi nodes could be removed. */
2573 || loop_has_vector_phi_nodes (loop))
2574 continue;
2576 estimated = estimated_stmt_executions_int (loop);
2577 if (estimated == -1)
2578 estimated = max_stmt_executions_int (loop);
2579 /* FIXME: Bypass this check as graphite doesn't update the
2580 count and frequency correctly now. */
2581 if (!flag_loop_parallelize_all
2582 && ((estimated != -1
2583 && estimated <= (HOST_WIDE_INT) n_threads * MIN_PER_THREAD)
2584 /* Do not bother with loops in cold areas. */
2585 || optimize_loop_nest_for_size_p (loop)))
2586 continue;
2588 if (!try_get_loop_niter (loop, &niter_desc))
2589 continue;
2591 if (!try_create_reduction_list (loop, &reduction_list))
2592 continue;
2594 if (!flag_loop_parallelize_all
2595 && !loop_parallel_p (loop, &parloop_obstack))
2596 continue;
2598 changed = true;
2599 if (dump_file && (dump_flags & TDF_DETAILS))
2601 if (loop->inner)
2602 fprintf (dump_file, "parallelizing outer loop %d\n",loop->header->index);
2603 else
2604 fprintf (dump_file, "parallelizing inner loop %d\n",loop->header->index);
2605 loop_loc = find_loop_location (loop);
2606 if (loop_loc != UNKNOWN_LOCATION)
2607 fprintf (dump_file, "\nloop at %s:%d: ",
2608 LOCATION_FILE (loop_loc), LOCATION_LINE (loop_loc));
2610 gen_parallel_loop (loop, &reduction_list,
2611 n_threads, &niter_desc);
2614 free_stmt_vec_info_vec ();
2615 obstack_free (&parloop_obstack, NULL);
2617 /* Parallelization will cause new function calls to be inserted through
2618 which local variables will escape. Reset the points-to solution
2619 for ESCAPED. */
2620 if (changed)
2621 pt_solution_reset (&cfun->gimple_df->escaped);
2623 return changed;
2626 /* Parallelization. */
2628 namespace {
2630 const pass_data pass_data_parallelize_loops =
2632 GIMPLE_PASS, /* type */
2633 "parloops", /* name */
2634 OPTGROUP_LOOP, /* optinfo_flags */
2635 TV_TREE_PARALLELIZE_LOOPS, /* tv_id */
2636 ( PROP_cfg | PROP_ssa ), /* properties_required */
2637 0, /* properties_provided */
2638 0, /* properties_destroyed */
2639 0, /* todo_flags_start */
2640 0, /* todo_flags_finish */
2643 class pass_parallelize_loops : public gimple_opt_pass
2645 public:
2646 pass_parallelize_loops (gcc::context *ctxt)
2647 : gimple_opt_pass (pass_data_parallelize_loops, ctxt)
2650 /* opt_pass methods: */
2651 virtual bool gate (function *) { return flag_tree_parallelize_loops > 1; }
2652 virtual unsigned int execute (function *);
2654 }; // class pass_parallelize_loops
2656 unsigned
2657 pass_parallelize_loops::execute (function *fun)
2659 if (number_of_loops (fun) <= 1)
2660 return 0;
2662 if (parallelize_loops ())
2664 fun->curr_properties &= ~(PROP_gimple_eomp);
2665 return TODO_update_ssa;
2668 return 0;
2671 } // anon namespace
2673 gimple_opt_pass *
2674 make_pass_parallelize_loops (gcc::context *ctxt)
2676 return new pass_parallelize_loops (ctxt);