Handle double reduction in parloops
[official-gcc.git] / gcc / tree-parloops.c
blobb06265c4bb85686a1632df15a05c30a96f95a2b2
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 "backend.h"
27 #include "cfghooks.h"
28 #include "tree.h"
29 #include "gimple.h"
30 #include "hard-reg-set.h"
31 #include "ssa.h"
32 #include "options.h"
33 #include "fold-const.h"
34 #include "internal-fn.h"
35 #include "gimplify.h"
36 #include "gimple-iterator.h"
37 #include "gimplify-me.h"
38 #include "gimple-walk.h"
39 #include "stor-layout.h"
40 #include "tree-nested.h"
41 #include "tree-cfg.h"
42 #include "tree-ssa-loop-ivopts.h"
43 #include "tree-ssa-loop-manip.h"
44 #include "tree-ssa-loop-niter.h"
45 #include "tree-ssa-loop.h"
46 #include "tree-into-ssa.h"
47 #include "cfgloop.h"
48 #include "tree-data-ref.h"
49 #include "tree-scalar-evolution.h"
50 #include "gimple-pretty-print.h"
51 #include "tree-pass.h"
52 #include "langhooks.h"
53 #include "tree-vectorizer.h"
54 #include "tree-hasher.h"
55 #include "tree-parloops.h"
56 #include "omp-low.h"
57 #include "tree-nested.h"
58 #include "cgraph.h"
59 #include "tree-ssa.h"
61 /* This pass tries to distribute iterations of loops into several threads.
62 The implementation is straightforward -- for each loop we test whether its
63 iterations are independent, and if it is the case (and some additional
64 conditions regarding profitability and correctness are satisfied), we
65 add GIMPLE_OMP_PARALLEL and GIMPLE_OMP_FOR codes and let omp expansion
66 machinery do its job.
68 The most of the complexity is in bringing the code into shape expected
69 by the omp expanders:
70 -- for GIMPLE_OMP_FOR, ensuring that the loop has only one induction
71 variable and that the exit test is at the start of the loop body
72 -- for GIMPLE_OMP_PARALLEL, replacing the references to local addressable
73 variables by accesses through pointers, and breaking up ssa chains
74 by storing the values incoming to the parallelized loop to a structure
75 passed to the new function as an argument (something similar is done
76 in omp gimplification, unfortunately only a small part of the code
77 can be shared).
79 TODO:
80 -- if there are several parallelizable loops in a function, it may be
81 possible to generate the threads just once (using synchronization to
82 ensure that cross-loop dependences are obeyed).
83 -- handling of common reduction patterns for outer loops.
85 More info can also be found at http://gcc.gnu.org/wiki/AutoParInGCC */
87 Reduction handling:
88 currently we use vect_force_simple_reduction() to detect reduction patterns.
89 The code transformation will be introduced by an example.
92 parloop
94 int sum=1;
96 for (i = 0; i < N; i++)
98 x[i] = i + 3;
99 sum+=x[i];
103 gimple-like code:
104 header_bb:
106 # sum_29 = PHI <sum_11(5), 1(3)>
107 # i_28 = PHI <i_12(5), 0(3)>
108 D.1795_8 = i_28 + 3;
109 x[i_28] = D.1795_8;
110 sum_11 = D.1795_8 + sum_29;
111 i_12 = i_28 + 1;
112 if (N_6(D) > i_12)
113 goto header_bb;
116 exit_bb:
118 # sum_21 = PHI <sum_11(4)>
119 printf (&"%d"[0], sum_21);
122 after reduction transformation (only relevant parts):
124 parloop
127 ....
130 # Storing the initial value given by the user. #
132 .paral_data_store.32.sum.27 = 1;
134 #pragma omp parallel num_threads(4)
136 #pragma omp for schedule(static)
138 # The neutral element corresponding to the particular
139 reduction's operation, e.g. 0 for PLUS_EXPR,
140 1 for MULT_EXPR, etc. replaces the user's initial value. #
142 # sum.27_29 = PHI <sum.27_11, 0>
144 sum.27_11 = D.1827_8 + sum.27_29;
146 GIMPLE_OMP_CONTINUE
148 # Adding this reduction phi is done at create_phi_for_local_result() #
149 # sum.27_56 = PHI <sum.27_11, 0>
150 GIMPLE_OMP_RETURN
152 # Creating the atomic operation is done at
153 create_call_for_reduction_1() #
155 #pragma omp atomic_load
156 D.1839_59 = *&.paral_data_load.33_51->reduction.23;
157 D.1840_60 = sum.27_56 + D.1839_59;
158 #pragma omp atomic_store (D.1840_60);
160 GIMPLE_OMP_RETURN
162 # collecting the result after the join of the threads is done at
163 create_loads_for_reductions().
164 The value computed by the threads is loaded from the
165 shared struct. #
168 .paral_data_load.33_52 = &.paral_data_store.32;
169 sum_37 = .paral_data_load.33_52->sum.27;
170 sum_43 = D.1795_41 + sum_37;
172 exit bb:
173 # sum_21 = PHI <sum_43, sum_26>
174 printf (&"%d"[0], sum_21);
182 /* Minimal number of iterations of a loop that should be executed in each
183 thread. */
184 #define MIN_PER_THREAD 100
186 /* Element of the hashtable, representing a
187 reduction in the current loop. */
188 struct reduction_info
190 gimple reduc_stmt; /* reduction statement. */
191 gimple reduc_phi; /* The phi node defining the reduction. */
192 enum tree_code reduction_code;/* code for the reduction operation. */
193 unsigned reduc_version; /* SSA_NAME_VERSION of original reduc_phi
194 result. */
195 gphi *keep_res; /* The PHI_RESULT of this phi is the resulting value
196 of the reduction variable when existing the loop. */
197 tree initial_value; /* The initial value of the reduction var before entering the loop. */
198 tree field; /* the name of the field in the parloop data structure intended for reduction. */
199 tree init; /* reduction initialization value. */
200 gphi *new_phi; /* (helper field) Newly created phi node whose result
201 will be passed to the atomic operation. Represents
202 the local result each thread computed for the reduction
203 operation. */
206 /* Reduction info hashtable helpers. */
208 struct reduction_hasher : free_ptr_hash <reduction_info>
210 static inline hashval_t hash (const reduction_info *);
211 static inline bool equal (const reduction_info *, const reduction_info *);
214 /* Equality and hash functions for hashtab code. */
216 inline bool
217 reduction_hasher::equal (const reduction_info *a, const reduction_info *b)
219 return (a->reduc_phi == b->reduc_phi);
222 inline hashval_t
223 reduction_hasher::hash (const reduction_info *a)
225 return a->reduc_version;
228 typedef hash_table<reduction_hasher> reduction_info_table_type;
231 static struct reduction_info *
232 reduction_phi (reduction_info_table_type *reduction_list, gimple phi)
234 struct reduction_info tmpred, *red;
236 if (reduction_list->elements () == 0 || phi == NULL)
237 return NULL;
239 tmpred.reduc_phi = phi;
240 tmpred.reduc_version = gimple_uid (phi);
241 red = reduction_list->find (&tmpred);
243 return red;
246 /* Element of hashtable of names to copy. */
248 struct name_to_copy_elt
250 unsigned version; /* The version of the name to copy. */
251 tree new_name; /* The new name used in the copy. */
252 tree field; /* The field of the structure used to pass the
253 value. */
256 /* Name copies hashtable helpers. */
258 struct name_to_copy_hasher : free_ptr_hash <name_to_copy_elt>
260 static inline hashval_t hash (const name_to_copy_elt *);
261 static inline bool equal (const name_to_copy_elt *, const name_to_copy_elt *);
264 /* Equality and hash functions for hashtab code. */
266 inline bool
267 name_to_copy_hasher::equal (const name_to_copy_elt *a, const name_to_copy_elt *b)
269 return a->version == b->version;
272 inline hashval_t
273 name_to_copy_hasher::hash (const name_to_copy_elt *a)
275 return (hashval_t) a->version;
278 typedef hash_table<name_to_copy_hasher> name_to_copy_table_type;
280 /* A transformation matrix, which is a self-contained ROWSIZE x COLSIZE
281 matrix. Rather than use floats, we simply keep a single DENOMINATOR that
282 represents the denominator for every element in the matrix. */
283 typedef struct lambda_trans_matrix_s
285 lambda_matrix matrix;
286 int rowsize;
287 int colsize;
288 int denominator;
289 } *lambda_trans_matrix;
290 #define LTM_MATRIX(T) ((T)->matrix)
291 #define LTM_ROWSIZE(T) ((T)->rowsize)
292 #define LTM_COLSIZE(T) ((T)->colsize)
293 #define LTM_DENOMINATOR(T) ((T)->denominator)
295 /* Allocate a new transformation matrix. */
297 static lambda_trans_matrix
298 lambda_trans_matrix_new (int colsize, int rowsize,
299 struct obstack * lambda_obstack)
301 lambda_trans_matrix ret;
303 ret = (lambda_trans_matrix)
304 obstack_alloc (lambda_obstack, sizeof (struct lambda_trans_matrix_s));
305 LTM_MATRIX (ret) = lambda_matrix_new (rowsize, colsize, lambda_obstack);
306 LTM_ROWSIZE (ret) = rowsize;
307 LTM_COLSIZE (ret) = colsize;
308 LTM_DENOMINATOR (ret) = 1;
309 return ret;
312 /* Multiply a vector VEC by a matrix MAT.
313 MAT is an M*N matrix, and VEC is a vector with length N. The result
314 is stored in DEST which must be a vector of length M. */
316 static void
317 lambda_matrix_vector_mult (lambda_matrix matrix, int m, int n,
318 lambda_vector vec, lambda_vector dest)
320 int i, j;
322 lambda_vector_clear (dest, m);
323 for (i = 0; i < m; i++)
324 for (j = 0; j < n; j++)
325 dest[i] += matrix[i][j] * vec[j];
328 /* Return true if TRANS is a legal transformation matrix that respects
329 the dependence vectors in DISTS and DIRS. The conservative answer
330 is false.
332 "Wolfe proves that a unimodular transformation represented by the
333 matrix T is legal when applied to a loop nest with a set of
334 lexicographically non-negative distance vectors RDG if and only if
335 for each vector d in RDG, (T.d >= 0) is lexicographically positive.
336 i.e.: if and only if it transforms the lexicographically positive
337 distance vectors to lexicographically positive vectors. Note that
338 a unimodular matrix must transform the zero vector (and only it) to
339 the zero vector." S.Muchnick. */
341 static bool
342 lambda_transform_legal_p (lambda_trans_matrix trans,
343 int nb_loops,
344 vec<ddr_p> dependence_relations)
346 unsigned int i, j;
347 lambda_vector distres;
348 struct data_dependence_relation *ddr;
350 gcc_assert (LTM_COLSIZE (trans) == nb_loops
351 && LTM_ROWSIZE (trans) == nb_loops);
353 /* When there are no dependences, the transformation is correct. */
354 if (dependence_relations.length () == 0)
355 return true;
357 ddr = dependence_relations[0];
358 if (ddr == NULL)
359 return true;
361 /* When there is an unknown relation in the dependence_relations, we
362 know that it is no worth looking at this loop nest: give up. */
363 if (DDR_ARE_DEPENDENT (ddr) == chrec_dont_know)
364 return false;
366 distres = lambda_vector_new (nb_loops);
368 /* For each distance vector in the dependence graph. */
369 FOR_EACH_VEC_ELT (dependence_relations, i, ddr)
371 /* Don't care about relations for which we know that there is no
372 dependence, nor about read-read (aka. output-dependences):
373 these data accesses can happen in any order. */
374 if (DDR_ARE_DEPENDENT (ddr) == chrec_known
375 || (DR_IS_READ (DDR_A (ddr)) && DR_IS_READ (DDR_B (ddr))))
376 continue;
378 /* Conservatively answer: "this transformation is not valid". */
379 if (DDR_ARE_DEPENDENT (ddr) == chrec_dont_know)
380 return false;
382 /* If the dependence could not be captured by a distance vector,
383 conservatively answer that the transform is not valid. */
384 if (DDR_NUM_DIST_VECTS (ddr) == 0)
385 return false;
387 /* Compute trans.dist_vect */
388 for (j = 0; j < DDR_NUM_DIST_VECTS (ddr); j++)
390 lambda_matrix_vector_mult (LTM_MATRIX (trans), nb_loops, nb_loops,
391 DDR_DIST_VECT (ddr, j), distres);
393 if (!lambda_vector_lexico_pos (distres, nb_loops))
394 return false;
397 return true;
400 /* Data dependency analysis. Returns true if the iterations of LOOP
401 are independent on each other (that is, if we can execute them
402 in parallel). */
404 static bool
405 loop_parallel_p (struct loop *loop, struct obstack * parloop_obstack)
407 vec<ddr_p> dependence_relations;
408 vec<data_reference_p> datarefs;
409 lambda_trans_matrix trans;
410 bool ret = false;
412 if (dump_file && (dump_flags & TDF_DETAILS))
414 fprintf (dump_file, "Considering loop %d\n", loop->num);
415 if (!loop->inner)
416 fprintf (dump_file, "loop is innermost\n");
417 else
418 fprintf (dump_file, "loop NOT innermost\n");
421 /* Check for problems with dependences. If the loop can be reversed,
422 the iterations are independent. */
423 auto_vec<loop_p, 3> loop_nest;
424 datarefs.create (10);
425 dependence_relations.create (100);
426 if (! compute_data_dependences_for_loop (loop, true, &loop_nest, &datarefs,
427 &dependence_relations))
429 if (dump_file && (dump_flags & TDF_DETAILS))
430 fprintf (dump_file, " FAILED: cannot analyze data dependencies\n");
431 ret = false;
432 goto end;
434 if (dump_file && (dump_flags & TDF_DETAILS))
435 dump_data_dependence_relations (dump_file, dependence_relations);
437 trans = lambda_trans_matrix_new (1, 1, parloop_obstack);
438 LTM_MATRIX (trans)[0][0] = -1;
440 if (lambda_transform_legal_p (trans, 1, dependence_relations))
442 ret = true;
443 if (dump_file && (dump_flags & TDF_DETAILS))
444 fprintf (dump_file, " SUCCESS: may be parallelized\n");
446 else if (dump_file && (dump_flags & TDF_DETAILS))
447 fprintf (dump_file,
448 " FAILED: data dependencies exist across iterations\n");
450 end:
451 free_dependence_relations (dependence_relations);
452 free_data_refs (datarefs);
454 return ret;
457 /* Return true when LOOP contains basic blocks marked with the
458 BB_IRREDUCIBLE_LOOP flag. */
460 static inline bool
461 loop_has_blocks_with_irreducible_flag (struct loop *loop)
463 unsigned i;
464 basic_block *bbs = get_loop_body_in_dom_order (loop);
465 bool res = true;
467 for (i = 0; i < loop->num_nodes; i++)
468 if (bbs[i]->flags & BB_IRREDUCIBLE_LOOP)
469 goto end;
471 res = false;
472 end:
473 free (bbs);
474 return res;
477 /* Assigns the address of OBJ in TYPE to an ssa name, and returns this name.
478 The assignment statement is placed on edge ENTRY. DECL_ADDRESS maps decls
479 to their addresses that can be reused. The address of OBJ is known to
480 be invariant in the whole function. Other needed statements are placed
481 right before GSI. */
483 static tree
484 take_address_of (tree obj, tree type, edge entry,
485 int_tree_htab_type *decl_address, gimple_stmt_iterator *gsi)
487 int uid;
488 tree *var_p, name, addr;
489 gassign *stmt;
490 gimple_seq stmts;
492 /* Since the address of OBJ is invariant, the trees may be shared.
493 Avoid rewriting unrelated parts of the code. */
494 obj = unshare_expr (obj);
495 for (var_p = &obj;
496 handled_component_p (*var_p);
497 var_p = &TREE_OPERAND (*var_p, 0))
498 continue;
500 /* Canonicalize the access to base on a MEM_REF. */
501 if (DECL_P (*var_p))
502 *var_p = build_simple_mem_ref (build_fold_addr_expr (*var_p));
504 /* Assign a canonical SSA name to the address of the base decl used
505 in the address and share it for all accesses and addresses based
506 on it. */
507 uid = DECL_UID (TREE_OPERAND (TREE_OPERAND (*var_p, 0), 0));
508 int_tree_map elt;
509 elt.uid = uid;
510 int_tree_map *slot = decl_address->find_slot (elt, INSERT);
511 if (!slot->to)
513 if (gsi == NULL)
514 return NULL;
515 addr = TREE_OPERAND (*var_p, 0);
516 const char *obj_name
517 = get_name (TREE_OPERAND (TREE_OPERAND (*var_p, 0), 0));
518 if (obj_name)
519 name = make_temp_ssa_name (TREE_TYPE (addr), NULL, obj_name);
520 else
521 name = make_ssa_name (TREE_TYPE (addr));
522 stmt = gimple_build_assign (name, addr);
523 gsi_insert_on_edge_immediate (entry, stmt);
525 slot->uid = uid;
526 slot->to = name;
528 else
529 name = slot->to;
531 /* Express the address in terms of the canonical SSA name. */
532 TREE_OPERAND (*var_p, 0) = name;
533 if (gsi == NULL)
534 return build_fold_addr_expr_with_type (obj, type);
536 name = force_gimple_operand (build_addr (obj, current_function_decl),
537 &stmts, true, NULL_TREE);
538 if (!gimple_seq_empty_p (stmts))
539 gsi_insert_seq_before (gsi, stmts, GSI_SAME_STMT);
541 if (!useless_type_conversion_p (type, TREE_TYPE (name)))
543 name = force_gimple_operand (fold_convert (type, name), &stmts, true,
544 NULL_TREE);
545 if (!gimple_seq_empty_p (stmts))
546 gsi_insert_seq_before (gsi, stmts, GSI_SAME_STMT);
549 return name;
552 static tree
553 reduc_stmt_res (gimple stmt)
555 return (gimple_code (stmt) == GIMPLE_PHI
556 ? gimple_phi_result (stmt)
557 : gimple_assign_lhs (stmt));
560 /* Callback for htab_traverse. Create the initialization statement
561 for reduction described in SLOT, and place it at the preheader of
562 the loop described in DATA. */
565 initialize_reductions (reduction_info **slot, struct loop *loop)
567 tree init, c;
568 tree bvar, type, arg;
569 edge e;
571 struct reduction_info *const reduc = *slot;
573 /* Create initialization in preheader:
574 reduction_variable = initialization value of reduction. */
576 /* In the phi node at the header, replace the argument coming
577 from the preheader with the reduction initialization value. */
579 /* Create a new variable to initialize the reduction. */
580 type = TREE_TYPE (PHI_RESULT (reduc->reduc_phi));
581 bvar = create_tmp_var (type, "reduction");
583 c = build_omp_clause (gimple_location (reduc->reduc_stmt),
584 OMP_CLAUSE_REDUCTION);
585 OMP_CLAUSE_REDUCTION_CODE (c) = reduc->reduction_code;
586 OMP_CLAUSE_DECL (c) = SSA_NAME_VAR (reduc_stmt_res (reduc->reduc_stmt));
588 init = omp_reduction_init (c, TREE_TYPE (bvar));
589 reduc->init = init;
591 /* Replace the argument representing the initialization value
592 with the initialization value for the reduction (neutral
593 element for the particular operation, e.g. 0 for PLUS_EXPR,
594 1 for MULT_EXPR, etc).
595 Keep the old value in a new variable "reduction_initial",
596 that will be taken in consideration after the parallel
597 computing is done. */
599 e = loop_preheader_edge (loop);
600 arg = PHI_ARG_DEF_FROM_EDGE (reduc->reduc_phi, e);
601 /* Create new variable to hold the initial value. */
603 SET_USE (PHI_ARG_DEF_PTR_FROM_EDGE
604 (reduc->reduc_phi, loop_preheader_edge (loop)), init);
605 reduc->initial_value = arg;
606 return 1;
609 struct elv_data
611 struct walk_stmt_info info;
612 edge entry;
613 int_tree_htab_type *decl_address;
614 gimple_stmt_iterator *gsi;
615 bool changed;
616 bool reset;
619 /* Eliminates references to local variables in *TP out of the single
620 entry single exit region starting at DTA->ENTRY.
621 DECL_ADDRESS contains addresses of the references that had their
622 address taken already. If the expression is changed, CHANGED is
623 set to true. Callback for walk_tree. */
625 static tree
626 eliminate_local_variables_1 (tree *tp, int *walk_subtrees, void *data)
628 struct elv_data *const dta = (struct elv_data *) data;
629 tree t = *tp, var, addr, addr_type, type, obj;
631 if (DECL_P (t))
633 *walk_subtrees = 0;
635 if (!SSA_VAR_P (t) || DECL_EXTERNAL (t))
636 return NULL_TREE;
638 type = TREE_TYPE (t);
639 addr_type = build_pointer_type (type);
640 addr = take_address_of (t, addr_type, dta->entry, dta->decl_address,
641 dta->gsi);
642 if (dta->gsi == NULL && addr == NULL_TREE)
644 dta->reset = true;
645 return NULL_TREE;
648 *tp = build_simple_mem_ref (addr);
650 dta->changed = true;
651 return NULL_TREE;
654 if (TREE_CODE (t) == ADDR_EXPR)
656 /* ADDR_EXPR may appear in two contexts:
657 -- as a gimple operand, when the address taken is a function invariant
658 -- as gimple rhs, when the resulting address in not a function
659 invariant
660 We do not need to do anything special in the latter case (the base of
661 the memory reference whose address is taken may be replaced in the
662 DECL_P case). The former case is more complicated, as we need to
663 ensure that the new address is still a gimple operand. Thus, it
664 is not sufficient to replace just the base of the memory reference --
665 we need to move the whole computation of the address out of the
666 loop. */
667 if (!is_gimple_val (t))
668 return NULL_TREE;
670 *walk_subtrees = 0;
671 obj = TREE_OPERAND (t, 0);
672 var = get_base_address (obj);
673 if (!var || !SSA_VAR_P (var) || DECL_EXTERNAL (var))
674 return NULL_TREE;
676 addr_type = TREE_TYPE (t);
677 addr = take_address_of (obj, addr_type, dta->entry, dta->decl_address,
678 dta->gsi);
679 if (dta->gsi == NULL && addr == NULL_TREE)
681 dta->reset = true;
682 return NULL_TREE;
684 *tp = addr;
686 dta->changed = true;
687 return NULL_TREE;
690 if (!EXPR_P (t))
691 *walk_subtrees = 0;
693 return NULL_TREE;
696 /* Moves the references to local variables in STMT at *GSI out of the single
697 entry single exit region starting at ENTRY. DECL_ADDRESS contains
698 addresses of the references that had their address taken
699 already. */
701 static void
702 eliminate_local_variables_stmt (edge entry, gimple_stmt_iterator *gsi,
703 int_tree_htab_type *decl_address)
705 struct elv_data dta;
706 gimple stmt = gsi_stmt (*gsi);
708 memset (&dta.info, '\0', sizeof (dta.info));
709 dta.entry = entry;
710 dta.decl_address = decl_address;
711 dta.changed = false;
712 dta.reset = false;
714 if (gimple_debug_bind_p (stmt))
716 dta.gsi = NULL;
717 walk_tree (gimple_debug_bind_get_value_ptr (stmt),
718 eliminate_local_variables_1, &dta.info, NULL);
719 if (dta.reset)
721 gimple_debug_bind_reset_value (stmt);
722 dta.changed = true;
725 else if (gimple_clobber_p (stmt))
727 stmt = gimple_build_nop ();
728 gsi_replace (gsi, stmt, false);
729 dta.changed = true;
731 else
733 dta.gsi = gsi;
734 walk_gimple_op (stmt, eliminate_local_variables_1, &dta.info);
737 if (dta.changed)
738 update_stmt (stmt);
741 /* Eliminates the references to local variables from the single entry
742 single exit region between the ENTRY and EXIT edges.
744 This includes:
745 1) Taking address of a local variable -- these are moved out of the
746 region (and temporary variable is created to hold the address if
747 necessary).
749 2) Dereferencing a local variable -- these are replaced with indirect
750 references. */
752 static void
753 eliminate_local_variables (edge entry, edge exit)
755 basic_block bb;
756 auto_vec<basic_block, 3> body;
757 unsigned i;
758 gimple_stmt_iterator gsi;
759 bool has_debug_stmt = false;
760 int_tree_htab_type decl_address (10);
761 basic_block entry_bb = entry->src;
762 basic_block exit_bb = exit->dest;
764 gather_blocks_in_sese_region (entry_bb, exit_bb, &body);
766 FOR_EACH_VEC_ELT (body, i, bb)
767 if (bb != entry_bb && bb != exit_bb)
768 for (gsi = gsi_start_bb (bb); !gsi_end_p (gsi); gsi_next (&gsi))
769 if (is_gimple_debug (gsi_stmt (gsi)))
771 if (gimple_debug_bind_p (gsi_stmt (gsi)))
772 has_debug_stmt = true;
774 else
775 eliminate_local_variables_stmt (entry, &gsi, &decl_address);
777 if (has_debug_stmt)
778 FOR_EACH_VEC_ELT (body, i, bb)
779 if (bb != entry_bb && bb != exit_bb)
780 for (gsi = gsi_start_bb (bb); !gsi_end_p (gsi); gsi_next (&gsi))
781 if (gimple_debug_bind_p (gsi_stmt (gsi)))
782 eliminate_local_variables_stmt (entry, &gsi, &decl_address);
785 /* Returns true if expression EXPR is not defined between ENTRY and
786 EXIT, i.e. if all its operands are defined outside of the region. */
788 static bool
789 expr_invariant_in_region_p (edge entry, edge exit, tree expr)
791 basic_block entry_bb = entry->src;
792 basic_block exit_bb = exit->dest;
793 basic_block def_bb;
795 if (is_gimple_min_invariant (expr))
796 return true;
798 if (TREE_CODE (expr) == SSA_NAME)
800 def_bb = gimple_bb (SSA_NAME_DEF_STMT (expr));
801 if (def_bb
802 && dominated_by_p (CDI_DOMINATORS, def_bb, entry_bb)
803 && !dominated_by_p (CDI_DOMINATORS, def_bb, exit_bb))
804 return false;
806 return true;
809 return false;
812 /* If COPY_NAME_P is true, creates and returns a duplicate of NAME.
813 The copies are stored to NAME_COPIES, if NAME was already duplicated,
814 its duplicate stored in NAME_COPIES is returned.
816 Regardless of COPY_NAME_P, the decl used as a base of the ssa name is also
817 duplicated, storing the copies in DECL_COPIES. */
819 static tree
820 separate_decls_in_region_name (tree name, name_to_copy_table_type *name_copies,
821 int_tree_htab_type *decl_copies,
822 bool copy_name_p)
824 tree copy, var, var_copy;
825 unsigned idx, uid, nuid;
826 struct int_tree_map ielt;
827 struct name_to_copy_elt elt, *nelt;
828 name_to_copy_elt **slot;
829 int_tree_map *dslot;
831 if (TREE_CODE (name) != SSA_NAME)
832 return name;
834 idx = SSA_NAME_VERSION (name);
835 elt.version = idx;
836 slot = name_copies->find_slot_with_hash (&elt, idx,
837 copy_name_p ? INSERT : NO_INSERT);
838 if (slot && *slot)
839 return (*slot)->new_name;
841 if (copy_name_p)
843 copy = duplicate_ssa_name (name, NULL);
844 nelt = XNEW (struct name_to_copy_elt);
845 nelt->version = idx;
846 nelt->new_name = copy;
847 nelt->field = NULL_TREE;
848 *slot = nelt;
850 else
852 gcc_assert (!slot);
853 copy = name;
856 var = SSA_NAME_VAR (name);
857 if (!var)
858 return copy;
860 uid = DECL_UID (var);
861 ielt.uid = uid;
862 dslot = decl_copies->find_slot_with_hash (ielt, uid, INSERT);
863 if (!dslot->to)
865 var_copy = create_tmp_var (TREE_TYPE (var), get_name (var));
866 DECL_GIMPLE_REG_P (var_copy) = DECL_GIMPLE_REG_P (var);
867 dslot->uid = uid;
868 dslot->to = var_copy;
870 /* Ensure that when we meet this decl next time, we won't duplicate
871 it again. */
872 nuid = DECL_UID (var_copy);
873 ielt.uid = nuid;
874 dslot = decl_copies->find_slot_with_hash (ielt, nuid, INSERT);
875 gcc_assert (!dslot->to);
876 dslot->uid = nuid;
877 dslot->to = var_copy;
879 else
880 var_copy = dslot->to;
882 replace_ssa_name_symbol (copy, var_copy);
883 return copy;
886 /* Finds the ssa names used in STMT that are defined outside the
887 region between ENTRY and EXIT and replaces such ssa names with
888 their duplicates. The duplicates are stored to NAME_COPIES. Base
889 decls of all ssa names used in STMT (including those defined in
890 LOOP) are replaced with the new temporary variables; the
891 replacement decls are stored in DECL_COPIES. */
893 static void
894 separate_decls_in_region_stmt (edge entry, edge exit, gimple stmt,
895 name_to_copy_table_type *name_copies,
896 int_tree_htab_type *decl_copies)
898 use_operand_p use;
899 def_operand_p def;
900 ssa_op_iter oi;
901 tree name, copy;
902 bool copy_name_p;
904 FOR_EACH_PHI_OR_STMT_DEF (def, stmt, oi, SSA_OP_DEF)
906 name = DEF_FROM_PTR (def);
907 gcc_assert (TREE_CODE (name) == SSA_NAME);
908 copy = separate_decls_in_region_name (name, name_copies, decl_copies,
909 false);
910 gcc_assert (copy == name);
913 FOR_EACH_PHI_OR_STMT_USE (use, stmt, oi, SSA_OP_USE)
915 name = USE_FROM_PTR (use);
916 if (TREE_CODE (name) != SSA_NAME)
917 continue;
919 copy_name_p = expr_invariant_in_region_p (entry, exit, name);
920 copy = separate_decls_in_region_name (name, name_copies, decl_copies,
921 copy_name_p);
922 SET_USE (use, copy);
926 /* Finds the ssa names used in STMT that are defined outside the
927 region between ENTRY and EXIT and replaces such ssa names with
928 their duplicates. The duplicates are stored to NAME_COPIES. Base
929 decls of all ssa names used in STMT (including those defined in
930 LOOP) are replaced with the new temporary variables; the
931 replacement decls are stored in DECL_COPIES. */
933 static bool
934 separate_decls_in_region_debug (gimple stmt,
935 name_to_copy_table_type *name_copies,
936 int_tree_htab_type *decl_copies)
938 use_operand_p use;
939 ssa_op_iter oi;
940 tree var, name;
941 struct int_tree_map ielt;
942 struct name_to_copy_elt elt;
943 name_to_copy_elt **slot;
944 int_tree_map *dslot;
946 if (gimple_debug_bind_p (stmt))
947 var = gimple_debug_bind_get_var (stmt);
948 else if (gimple_debug_source_bind_p (stmt))
949 var = gimple_debug_source_bind_get_var (stmt);
950 else
951 return true;
952 if (TREE_CODE (var) == DEBUG_EXPR_DECL || TREE_CODE (var) == LABEL_DECL)
953 return true;
954 gcc_assert (DECL_P (var) && SSA_VAR_P (var));
955 ielt.uid = DECL_UID (var);
956 dslot = decl_copies->find_slot_with_hash (ielt, ielt.uid, NO_INSERT);
957 if (!dslot)
958 return true;
959 if (gimple_debug_bind_p (stmt))
960 gimple_debug_bind_set_var (stmt, dslot->to);
961 else if (gimple_debug_source_bind_p (stmt))
962 gimple_debug_source_bind_set_var (stmt, dslot->to);
964 FOR_EACH_PHI_OR_STMT_USE (use, stmt, oi, SSA_OP_USE)
966 name = USE_FROM_PTR (use);
967 if (TREE_CODE (name) != SSA_NAME)
968 continue;
970 elt.version = SSA_NAME_VERSION (name);
971 slot = name_copies->find_slot_with_hash (&elt, elt.version, NO_INSERT);
972 if (!slot)
974 gimple_debug_bind_reset_value (stmt);
975 update_stmt (stmt);
976 break;
979 SET_USE (use, (*slot)->new_name);
982 return false;
985 /* Callback for htab_traverse. Adds a field corresponding to the reduction
986 specified in SLOT. The type is passed in DATA. */
989 add_field_for_reduction (reduction_info **slot, tree type)
992 struct reduction_info *const red = *slot;
993 tree var = reduc_stmt_res (red->reduc_stmt);
994 tree field = build_decl (gimple_location (red->reduc_stmt), FIELD_DECL,
995 SSA_NAME_IDENTIFIER (var), TREE_TYPE (var));
997 insert_field_into_struct (type, field);
999 red->field = field;
1001 return 1;
1004 /* Callback for htab_traverse. Adds a field corresponding to a ssa name
1005 described in SLOT. The type is passed in DATA. */
1008 add_field_for_name (name_to_copy_elt **slot, tree type)
1010 struct name_to_copy_elt *const elt = *slot;
1011 tree name = ssa_name (elt->version);
1012 tree field = build_decl (UNKNOWN_LOCATION,
1013 FIELD_DECL, SSA_NAME_IDENTIFIER (name),
1014 TREE_TYPE (name));
1016 insert_field_into_struct (type, field);
1017 elt->field = field;
1019 return 1;
1022 /* Callback for htab_traverse. A local result is the intermediate result
1023 computed by a single
1024 thread, or the initial value in case no iteration was executed.
1025 This function creates a phi node reflecting these values.
1026 The phi's result will be stored in NEW_PHI field of the
1027 reduction's data structure. */
1030 create_phi_for_local_result (reduction_info **slot, struct loop *loop)
1032 struct reduction_info *const reduc = *slot;
1033 edge e;
1034 gphi *new_phi;
1035 basic_block store_bb;
1036 tree local_res;
1037 source_location locus;
1039 /* STORE_BB is the block where the phi
1040 should be stored. It is the destination of the loop exit.
1041 (Find the fallthru edge from GIMPLE_OMP_CONTINUE). */
1042 store_bb = FALLTHRU_EDGE (loop->latch)->dest;
1044 /* STORE_BB has two predecessors. One coming from the loop
1045 (the reduction's result is computed at the loop),
1046 and another coming from a block preceding the loop,
1047 when no iterations
1048 are executed (the initial value should be taken). */
1049 if (EDGE_PRED (store_bb, 0) == FALLTHRU_EDGE (loop->latch))
1050 e = EDGE_PRED (store_bb, 1);
1051 else
1052 e = EDGE_PRED (store_bb, 0);
1053 tree lhs = reduc_stmt_res (reduc->reduc_stmt);
1054 local_res = copy_ssa_name (lhs);
1055 locus = gimple_location (reduc->reduc_stmt);
1056 new_phi = create_phi_node (local_res, store_bb);
1057 add_phi_arg (new_phi, reduc->init, e, locus);
1058 add_phi_arg (new_phi, lhs, FALLTHRU_EDGE (loop->latch), locus);
1059 reduc->new_phi = new_phi;
1061 return 1;
1064 struct clsn_data
1066 tree store;
1067 tree load;
1069 basic_block store_bb;
1070 basic_block load_bb;
1073 /* Callback for htab_traverse. Create an atomic instruction for the
1074 reduction described in SLOT.
1075 DATA annotates the place in memory the atomic operation relates to,
1076 and the basic block it needs to be generated in. */
1079 create_call_for_reduction_1 (reduction_info **slot, struct clsn_data *clsn_data)
1081 struct reduction_info *const reduc = *slot;
1082 gimple_stmt_iterator gsi;
1083 tree type = TREE_TYPE (PHI_RESULT (reduc->reduc_phi));
1084 tree load_struct;
1085 basic_block bb;
1086 basic_block new_bb;
1087 edge e;
1088 tree t, addr, ref, x;
1089 tree tmp_load, name;
1090 gimple load;
1092 load_struct = build_simple_mem_ref (clsn_data->load);
1093 t = build3 (COMPONENT_REF, type, load_struct, reduc->field, NULL_TREE);
1095 addr = build_addr (t, current_function_decl);
1097 /* Create phi node. */
1098 bb = clsn_data->load_bb;
1100 gsi = gsi_last_bb (bb);
1101 e = split_block (bb, gsi_stmt (gsi));
1102 new_bb = e->dest;
1104 tmp_load = create_tmp_var (TREE_TYPE (TREE_TYPE (addr)));
1105 tmp_load = make_ssa_name (tmp_load);
1106 load = gimple_build_omp_atomic_load (tmp_load, addr);
1107 SSA_NAME_DEF_STMT (tmp_load) = load;
1108 gsi = gsi_start_bb (new_bb);
1109 gsi_insert_after (&gsi, load, GSI_NEW_STMT);
1111 e = split_block (new_bb, load);
1112 new_bb = e->dest;
1113 gsi = gsi_start_bb (new_bb);
1114 ref = tmp_load;
1115 x = fold_build2 (reduc->reduction_code,
1116 TREE_TYPE (PHI_RESULT (reduc->new_phi)), ref,
1117 PHI_RESULT (reduc->new_phi));
1119 name = force_gimple_operand_gsi (&gsi, x, true, NULL_TREE, true,
1120 GSI_CONTINUE_LINKING);
1122 gsi_insert_after (&gsi, gimple_build_omp_atomic_store (name), GSI_NEW_STMT);
1123 return 1;
1126 /* Create the atomic operation at the join point of the threads.
1127 REDUCTION_LIST describes the reductions in the LOOP.
1128 LD_ST_DATA describes the shared data structure where
1129 shared data is stored in and loaded from. */
1130 static void
1131 create_call_for_reduction (struct loop *loop,
1132 reduction_info_table_type *reduction_list,
1133 struct clsn_data *ld_st_data)
1135 reduction_list->traverse <struct loop *, create_phi_for_local_result> (loop);
1136 /* Find the fallthru edge from GIMPLE_OMP_CONTINUE. */
1137 ld_st_data->load_bb = FALLTHRU_EDGE (loop->latch)->dest;
1138 reduction_list
1139 ->traverse <struct clsn_data *, create_call_for_reduction_1> (ld_st_data);
1142 /* Callback for htab_traverse. Loads the final reduction value at the
1143 join point of all threads, and inserts it in the right place. */
1146 create_loads_for_reductions (reduction_info **slot, struct clsn_data *clsn_data)
1148 struct reduction_info *const red = *slot;
1149 gimple stmt;
1150 gimple_stmt_iterator gsi;
1151 tree type = TREE_TYPE (reduc_stmt_res (red->reduc_stmt));
1152 tree load_struct;
1153 tree name;
1154 tree x;
1156 /* If there's no exit phi, the result of the reduction is unused. */
1157 if (red->keep_res == NULL)
1158 return 1;
1160 gsi = gsi_after_labels (clsn_data->load_bb);
1161 load_struct = build_simple_mem_ref (clsn_data->load);
1162 load_struct = build3 (COMPONENT_REF, type, load_struct, red->field,
1163 NULL_TREE);
1165 x = load_struct;
1166 name = PHI_RESULT (red->keep_res);
1167 stmt = gimple_build_assign (name, x);
1169 gsi_insert_after (&gsi, stmt, GSI_NEW_STMT);
1171 for (gsi = gsi_start_phis (gimple_bb (red->keep_res));
1172 !gsi_end_p (gsi); gsi_next (&gsi))
1173 if (gsi_stmt (gsi) == red->keep_res)
1175 remove_phi_node (&gsi, false);
1176 return 1;
1178 gcc_unreachable ();
1181 /* Load the reduction result that was stored in LD_ST_DATA.
1182 REDUCTION_LIST describes the list of reductions that the
1183 loads should be generated for. */
1184 static void
1185 create_final_loads_for_reduction (reduction_info_table_type *reduction_list,
1186 struct clsn_data *ld_st_data)
1188 gimple_stmt_iterator gsi;
1189 tree t;
1190 gimple stmt;
1192 gsi = gsi_after_labels (ld_st_data->load_bb);
1193 t = build_fold_addr_expr (ld_st_data->store);
1194 stmt = gimple_build_assign (ld_st_data->load, t);
1196 gsi_insert_before (&gsi, stmt, GSI_NEW_STMT);
1198 reduction_list
1199 ->traverse <struct clsn_data *, create_loads_for_reductions> (ld_st_data);
1203 /* Callback for htab_traverse. Store the neutral value for the
1204 particular reduction's operation, e.g. 0 for PLUS_EXPR,
1205 1 for MULT_EXPR, etc. into the reduction field.
1206 The reduction is specified in SLOT. The store information is
1207 passed in DATA. */
1210 create_stores_for_reduction (reduction_info **slot, struct clsn_data *clsn_data)
1212 struct reduction_info *const red = *slot;
1213 tree t;
1214 gimple stmt;
1215 gimple_stmt_iterator gsi;
1216 tree type = TREE_TYPE (reduc_stmt_res (red->reduc_stmt));
1218 gsi = gsi_last_bb (clsn_data->store_bb);
1219 t = build3 (COMPONENT_REF, type, clsn_data->store, red->field, NULL_TREE);
1220 stmt = gimple_build_assign (t, red->initial_value);
1221 gsi_insert_after (&gsi, stmt, GSI_NEW_STMT);
1223 return 1;
1226 /* Callback for htab_traverse. Creates loads to a field of LOAD in LOAD_BB and
1227 store to a field of STORE in STORE_BB for the ssa name and its duplicate
1228 specified in SLOT. */
1231 create_loads_and_stores_for_name (name_to_copy_elt **slot,
1232 struct clsn_data *clsn_data)
1234 struct name_to_copy_elt *const elt = *slot;
1235 tree t;
1236 gimple stmt;
1237 gimple_stmt_iterator gsi;
1238 tree type = TREE_TYPE (elt->new_name);
1239 tree load_struct;
1241 gsi = gsi_last_bb (clsn_data->store_bb);
1242 t = build3 (COMPONENT_REF, type, clsn_data->store, elt->field, NULL_TREE);
1243 stmt = gimple_build_assign (t, ssa_name (elt->version));
1244 gsi_insert_after (&gsi, stmt, GSI_NEW_STMT);
1246 gsi = gsi_last_bb (clsn_data->load_bb);
1247 load_struct = build_simple_mem_ref (clsn_data->load);
1248 t = build3 (COMPONENT_REF, type, load_struct, elt->field, NULL_TREE);
1249 stmt = gimple_build_assign (elt->new_name, t);
1250 gsi_insert_after (&gsi, stmt, GSI_NEW_STMT);
1252 return 1;
1255 /* Moves all the variables used in LOOP and defined outside of it (including
1256 the initial values of loop phi nodes, and *PER_THREAD if it is a ssa
1257 name) to a structure created for this purpose. The code
1259 while (1)
1261 use (a);
1262 use (b);
1265 is transformed this way:
1267 bb0:
1268 old.a = a;
1269 old.b = b;
1271 bb1:
1272 a' = new->a;
1273 b' = new->b;
1274 while (1)
1276 use (a');
1277 use (b');
1280 `old' is stored to *ARG_STRUCT and `new' is stored to NEW_ARG_STRUCT. The
1281 pointer `new' is intentionally not initialized (the loop will be split to a
1282 separate function later, and `new' will be initialized from its arguments).
1283 LD_ST_DATA holds information about the shared data structure used to pass
1284 information among the threads. It is initialized here, and
1285 gen_parallel_loop will pass it to create_call_for_reduction that
1286 needs this information. REDUCTION_LIST describes the reductions
1287 in LOOP. */
1289 static void
1290 separate_decls_in_region (edge entry, edge exit,
1291 reduction_info_table_type *reduction_list,
1292 tree *arg_struct, tree *new_arg_struct,
1293 struct clsn_data *ld_st_data)
1296 basic_block bb1 = split_edge (entry);
1297 basic_block bb0 = single_pred (bb1);
1298 name_to_copy_table_type name_copies (10);
1299 int_tree_htab_type decl_copies (10);
1300 unsigned i;
1301 tree type, type_name, nvar;
1302 gimple_stmt_iterator gsi;
1303 struct clsn_data clsn_data;
1304 auto_vec<basic_block, 3> body;
1305 basic_block bb;
1306 basic_block entry_bb = bb1;
1307 basic_block exit_bb = exit->dest;
1308 bool has_debug_stmt = false;
1310 entry = single_succ_edge (entry_bb);
1311 gather_blocks_in_sese_region (entry_bb, exit_bb, &body);
1313 FOR_EACH_VEC_ELT (body, i, bb)
1315 if (bb != entry_bb && bb != exit_bb)
1317 for (gsi = gsi_start_phis (bb); !gsi_end_p (gsi); gsi_next (&gsi))
1318 separate_decls_in_region_stmt (entry, exit, gsi_stmt (gsi),
1319 &name_copies, &decl_copies);
1321 for (gsi = gsi_start_bb (bb); !gsi_end_p (gsi); gsi_next (&gsi))
1323 gimple stmt = gsi_stmt (gsi);
1325 if (is_gimple_debug (stmt))
1326 has_debug_stmt = true;
1327 else
1328 separate_decls_in_region_stmt (entry, exit, stmt,
1329 &name_copies, &decl_copies);
1334 /* Now process debug bind stmts. We must not create decls while
1335 processing debug stmts, so we defer their processing so as to
1336 make sure we will have debug info for as many variables as
1337 possible (all of those that were dealt with in the loop above),
1338 and discard those for which we know there's nothing we can
1339 do. */
1340 if (has_debug_stmt)
1341 FOR_EACH_VEC_ELT (body, i, bb)
1342 if (bb != entry_bb && bb != exit_bb)
1344 for (gsi = gsi_start_bb (bb); !gsi_end_p (gsi);)
1346 gimple stmt = gsi_stmt (gsi);
1348 if (is_gimple_debug (stmt))
1350 if (separate_decls_in_region_debug (stmt, &name_copies,
1351 &decl_copies))
1353 gsi_remove (&gsi, true);
1354 continue;
1358 gsi_next (&gsi);
1362 if (name_copies.elements () == 0 && reduction_list->elements () == 0)
1364 /* It may happen that there is nothing to copy (if there are only
1365 loop carried and external variables in the loop). */
1366 *arg_struct = NULL;
1367 *new_arg_struct = NULL;
1369 else
1371 /* Create the type for the structure to store the ssa names to. */
1372 type = lang_hooks.types.make_type (RECORD_TYPE);
1373 type_name = build_decl (UNKNOWN_LOCATION,
1374 TYPE_DECL, create_tmp_var_name (".paral_data"),
1375 type);
1376 TYPE_NAME (type) = type_name;
1378 name_copies.traverse <tree, add_field_for_name> (type);
1379 if (reduction_list && reduction_list->elements () > 0)
1381 /* Create the fields for reductions. */
1382 reduction_list->traverse <tree, add_field_for_reduction> (type);
1384 layout_type (type);
1386 /* Create the loads and stores. */
1387 *arg_struct = create_tmp_var (type, ".paral_data_store");
1388 nvar = create_tmp_var (build_pointer_type (type), ".paral_data_load");
1389 *new_arg_struct = make_ssa_name (nvar);
1391 ld_st_data->store = *arg_struct;
1392 ld_st_data->load = *new_arg_struct;
1393 ld_st_data->store_bb = bb0;
1394 ld_st_data->load_bb = bb1;
1396 name_copies
1397 .traverse <struct clsn_data *, create_loads_and_stores_for_name>
1398 (ld_st_data);
1400 /* Load the calculation from memory (after the join of the threads). */
1402 if (reduction_list && reduction_list->elements () > 0)
1404 reduction_list
1405 ->traverse <struct clsn_data *, create_stores_for_reduction>
1406 (ld_st_data);
1407 clsn_data.load = make_ssa_name (nvar);
1408 clsn_data.load_bb = exit->dest;
1409 clsn_data.store = ld_st_data->store;
1410 create_final_loads_for_reduction (reduction_list, &clsn_data);
1415 /* Returns true if FN was created to run in parallel. */
1417 bool
1418 parallelized_function_p (tree fndecl)
1420 cgraph_node *node = cgraph_node::get (fndecl);
1421 gcc_assert (node != NULL);
1422 return node->parallelized_function;
1425 /* Creates and returns an empty function that will receive the body of
1426 a parallelized loop. */
1428 static tree
1429 create_loop_fn (location_t loc)
1431 char buf[100];
1432 char *tname;
1433 tree decl, type, name, t;
1434 struct function *act_cfun = cfun;
1435 static unsigned loopfn_num;
1437 loc = LOCATION_LOCUS (loc);
1438 snprintf (buf, 100, "%s.$loopfn", current_function_name ());
1439 ASM_FORMAT_PRIVATE_NAME (tname, buf, loopfn_num++);
1440 clean_symbol_name (tname);
1441 name = get_identifier (tname);
1442 type = build_function_type_list (void_type_node, ptr_type_node, NULL_TREE);
1444 decl = build_decl (loc, FUNCTION_DECL, name, type);
1445 TREE_STATIC (decl) = 1;
1446 TREE_USED (decl) = 1;
1447 DECL_ARTIFICIAL (decl) = 1;
1448 DECL_IGNORED_P (decl) = 0;
1449 TREE_PUBLIC (decl) = 0;
1450 DECL_UNINLINABLE (decl) = 1;
1451 DECL_EXTERNAL (decl) = 0;
1452 DECL_CONTEXT (decl) = NULL_TREE;
1453 DECL_INITIAL (decl) = make_node (BLOCK);
1455 t = build_decl (loc, RESULT_DECL, NULL_TREE, void_type_node);
1456 DECL_ARTIFICIAL (t) = 1;
1457 DECL_IGNORED_P (t) = 1;
1458 DECL_RESULT (decl) = t;
1460 t = build_decl (loc, PARM_DECL, get_identifier (".paral_data_param"),
1461 ptr_type_node);
1462 DECL_ARTIFICIAL (t) = 1;
1463 DECL_ARG_TYPE (t) = ptr_type_node;
1464 DECL_CONTEXT (t) = decl;
1465 TREE_USED (t) = 1;
1466 DECL_ARGUMENTS (decl) = t;
1468 allocate_struct_function (decl, false);
1470 /* The call to allocate_struct_function clobbers CFUN, so we need to restore
1471 it. */
1472 set_cfun (act_cfun);
1474 return decl;
1477 /* Replace uses of NAME by VAL in block BB. */
1479 static void
1480 replace_uses_in_bb_by (tree name, tree val, basic_block bb)
1482 gimple use_stmt;
1483 imm_use_iterator imm_iter;
1485 FOR_EACH_IMM_USE_STMT (use_stmt, imm_iter, name)
1487 if (gimple_bb (use_stmt) != bb)
1488 continue;
1490 use_operand_p use_p;
1491 FOR_EACH_IMM_USE_ON_STMT (use_p, imm_iter)
1492 SET_USE (use_p, val);
1496 /* Do transformation from:
1498 <bb preheader>:
1500 goto <bb header>
1502 <bb header>:
1503 ivtmp_a = PHI <ivtmp_init (preheader), ivtmp_b (latch)>
1504 sum_a = PHI <sum_init (preheader), sum_b (latch)>
1506 use (ivtmp_a)
1508 sum_b = sum_a + sum_update
1510 if (ivtmp_a < n)
1511 goto <bb latch>;
1512 else
1513 goto <bb exit>;
1515 <bb latch>:
1516 ivtmp_b = ivtmp_a + 1;
1517 goto <bb header>
1519 <bb exit>:
1520 sum_z = PHI <sum_b (cond[1]), ...>
1522 [1] Where <bb cond> is single_pred (bb latch); In the simplest case,
1523 that's <bb header>.
1527 <bb preheader>:
1529 goto <bb newheader>
1531 <bb header>:
1532 ivtmp_a = PHI <ivtmp_c (latch)>
1533 sum_a = PHI <sum_c (latch)>
1535 use (ivtmp_a)
1537 sum_b = sum_a + sum_update
1539 goto <bb latch>;
1541 <bb newheader>:
1542 ivtmp_c = PHI <ivtmp_init (preheader), ivtmp_b (latch)>
1543 sum_c = PHI <sum_init (preheader), sum_b (latch)>
1544 if (ivtmp_c < n + 1)
1545 goto <bb header>;
1546 else
1547 goto <bb newexit>;
1549 <bb latch>:
1550 ivtmp_b = ivtmp_a + 1;
1551 goto <bb newheader>
1553 <bb newexit>:
1554 sum_y = PHI <sum_c (newheader)>
1556 <bb exit>:
1557 sum_z = PHI <sum_y (newexit), ...>
1560 In unified diff format:
1562 <bb preheader>:
1564 - goto <bb header>
1565 + goto <bb newheader>
1567 <bb header>:
1568 - ivtmp_a = PHI <ivtmp_init (preheader), ivtmp_b (latch)>
1569 - sum_a = PHI <sum_init (preheader), sum_b (latch)>
1570 + ivtmp_a = PHI <ivtmp_c (latch)>
1571 + sum_a = PHI <sum_c (latch)>
1573 use (ivtmp_a)
1575 sum_b = sum_a + sum_update
1577 - if (ivtmp_a < n)
1578 - goto <bb latch>;
1579 + goto <bb latch>;
1581 + <bb newheader>:
1582 + ivtmp_c = PHI <ivtmp_init (preheader), ivtmp_b (latch)>
1583 + sum_c = PHI <sum_init (preheader), sum_b (latch)>
1584 + if (ivtmp_c < n + 1)
1585 + goto <bb header>;
1586 else
1587 goto <bb exit>;
1589 <bb latch>:
1590 ivtmp_b = ivtmp_a + 1;
1591 - goto <bb header>
1592 + goto <bb newheader>
1594 + <bb newexit>:
1595 + sum_y = PHI <sum_c (newheader)>
1597 <bb exit>:
1598 - sum_z = PHI <sum_b (cond[1]), ...>
1599 + sum_z = PHI <sum_y (newexit), ...>
1601 Note: the example does not show any virtual phis, but these are handled more
1602 or less as reductions.
1605 Moves the exit condition of LOOP to the beginning of its header.
1606 REDUCTION_LIST describes the reductions in LOOP. BOUND is the new loop
1607 bound. */
1609 static void
1610 transform_to_exit_first_loop_alt (struct loop *loop,
1611 reduction_info_table_type *reduction_list,
1612 tree bound)
1614 basic_block header = loop->header;
1615 basic_block latch = loop->latch;
1616 edge exit = single_dom_exit (loop);
1617 basic_block exit_block = exit->dest;
1618 gcond *cond_stmt = as_a <gcond *> (last_stmt (exit->src));
1619 tree control = gimple_cond_lhs (cond_stmt);
1620 edge e;
1622 /* Rewriting virtuals into loop-closed ssa normal form makes this
1623 transformation simpler. It also ensures that the virtuals are in
1624 loop-closed ssa normal from after the transformation, which is required by
1625 create_parallel_loop. */
1626 rewrite_virtuals_into_loop_closed_ssa (loop);
1628 /* Create the new_header block. */
1629 basic_block new_header = split_block_before_cond_jump (exit->src);
1630 edge edge_at_split = single_pred_edge (new_header);
1632 /* Redirect entry edge to new_header. */
1633 edge entry = loop_preheader_edge (loop);
1634 e = redirect_edge_and_branch (entry, new_header);
1635 gcc_assert (e == entry);
1637 /* Redirect post_inc_edge to new_header. */
1638 edge post_inc_edge = single_succ_edge (latch);
1639 e = redirect_edge_and_branch (post_inc_edge, new_header);
1640 gcc_assert (e == post_inc_edge);
1642 /* Redirect post_cond_edge to header. */
1643 edge post_cond_edge = single_pred_edge (latch);
1644 e = redirect_edge_and_branch (post_cond_edge, header);
1645 gcc_assert (e == post_cond_edge);
1647 /* Redirect edge_at_split to latch. */
1648 e = redirect_edge_and_branch (edge_at_split, latch);
1649 gcc_assert (e == edge_at_split);
1651 /* Set the new loop bound. */
1652 gimple_cond_set_rhs (cond_stmt, bound);
1653 update_stmt (cond_stmt);
1655 /* Repair the ssa. */
1656 vec<edge_var_map> *v = redirect_edge_var_map_vector (post_inc_edge);
1657 edge_var_map *vm;
1658 gphi_iterator gsi;
1659 int i;
1660 for (gsi = gsi_start_phis (header), i = 0;
1661 !gsi_end_p (gsi) && v->iterate (i, &vm);
1662 gsi_next (&gsi), i++)
1664 gphi *phi = gsi.phi ();
1665 tree res_a = PHI_RESULT (phi);
1667 /* Create new phi. */
1668 tree res_c = copy_ssa_name (res_a, phi);
1669 gphi *nphi = create_phi_node (res_c, new_header);
1671 /* Replace ivtmp_a with ivtmp_c in condition 'if (ivtmp_a < n)'. */
1672 replace_uses_in_bb_by (res_a, res_c, new_header);
1674 /* Replace ivtmp/sum_b with ivtmp/sum_c in header phi. */
1675 add_phi_arg (phi, res_c, post_cond_edge, UNKNOWN_LOCATION);
1677 /* Replace sum_b with sum_c in exit phi. */
1678 tree res_b = redirect_edge_var_map_def (vm);
1679 replace_uses_in_bb_by (res_b, res_c, exit_block);
1681 struct reduction_info *red = reduction_phi (reduction_list, phi);
1682 gcc_assert (virtual_operand_p (res_a)
1683 || res_a == control
1684 || red != NULL);
1686 if (red)
1688 /* Register the new reduction phi. */
1689 red->reduc_phi = nphi;
1690 gimple_set_uid (red->reduc_phi, red->reduc_version);
1693 gcc_assert (gsi_end_p (gsi) && !v->iterate (i, &vm));
1695 /* Set the preheader argument of the new phis to ivtmp/sum_init. */
1696 flush_pending_stmts (entry);
1698 /* Set the latch arguments of the new phis to ivtmp/sum_b. */
1699 flush_pending_stmts (post_inc_edge);
1701 /* Create a new empty exit block, inbetween the new loop header and the old
1702 exit block. The function separate_decls_in_region needs this block to
1703 insert code that is active on loop exit, but not any other path. */
1704 basic_block new_exit_block = split_edge (exit);
1706 /* Insert and register the reduction exit phis. */
1707 for (gphi_iterator gsi = gsi_start_phis (exit_block);
1708 !gsi_end_p (gsi);
1709 gsi_next (&gsi))
1711 gphi *phi = gsi.phi ();
1712 tree res_z = PHI_RESULT (phi);
1714 /* Now that we have a new exit block, duplicate the phi of the old exit
1715 block in the new exit block to preserve loop-closed ssa. */
1716 edge succ_new_exit_block = single_succ_edge (new_exit_block);
1717 edge pred_new_exit_block = single_pred_edge (new_exit_block);
1718 tree res_y = copy_ssa_name (res_z, phi);
1719 gphi *nphi = create_phi_node (res_y, new_exit_block);
1720 tree res_c = PHI_ARG_DEF_FROM_EDGE (phi, succ_new_exit_block);
1721 add_phi_arg (nphi, res_c, pred_new_exit_block, UNKNOWN_LOCATION);
1722 add_phi_arg (phi, res_y, succ_new_exit_block, UNKNOWN_LOCATION);
1724 if (virtual_operand_p (res_z))
1725 continue;
1727 gimple reduc_phi = SSA_NAME_DEF_STMT (res_c);
1728 struct reduction_info *red = reduction_phi (reduction_list, reduc_phi);
1729 if (red != NULL)
1730 red->keep_res = nphi;
1733 /* We're going to cancel the loop at the end of gen_parallel_loop, but until
1734 then we're still using some fields, so only bother about fields that are
1735 still used: header and latch.
1736 The loop has a new header bb, so we update it. The latch bb stays the
1737 same. */
1738 loop->header = new_header;
1740 /* Recalculate dominance info. */
1741 free_dominance_info (CDI_DOMINATORS);
1742 calculate_dominance_info (CDI_DOMINATORS);
1745 /* Tries to moves the exit condition of LOOP to the beginning of its header
1746 without duplication of the loop body. NIT is the number of iterations of the
1747 loop. REDUCTION_LIST describes the reductions in LOOP. Return true if
1748 transformation is successful. */
1750 static bool
1751 try_transform_to_exit_first_loop_alt (struct loop *loop,
1752 reduction_info_table_type *reduction_list,
1753 tree nit)
1755 /* Check whether the latch contains a single statement. */
1756 if (!gimple_seq_nondebug_singleton_p (bb_seq (loop->latch)))
1757 return false;
1759 /* Check whether the latch contains the loop iv increment. */
1760 edge back = single_succ_edge (loop->latch);
1761 edge exit = single_dom_exit (loop);
1762 gcond *cond_stmt = as_a <gcond *> (last_stmt (exit->src));
1763 tree control = gimple_cond_lhs (cond_stmt);
1764 gphi *phi = as_a <gphi *> (SSA_NAME_DEF_STMT (control));
1765 tree inc_res = gimple_phi_arg_def (phi, back->dest_idx);
1766 if (gimple_bb (SSA_NAME_DEF_STMT (inc_res)) != loop->latch)
1767 return false;
1769 /* Check whether there's no code between the loop condition and the latch. */
1770 if (!single_pred_p (loop->latch)
1771 || single_pred (loop->latch) != exit->src)
1772 return false;
1774 tree alt_bound = NULL_TREE;
1775 tree nit_type = TREE_TYPE (nit);
1777 /* Figure out whether nit + 1 overflows. */
1778 if (TREE_CODE (nit) == INTEGER_CST)
1780 if (!tree_int_cst_equal (nit, TYPE_MAXVAL (nit_type)))
1782 alt_bound = fold_build2_loc (UNKNOWN_LOCATION, PLUS_EXPR, nit_type,
1783 nit, build_one_cst (nit_type));
1785 gcc_assert (TREE_CODE (alt_bound) == INTEGER_CST);
1786 transform_to_exit_first_loop_alt (loop, reduction_list, alt_bound);
1787 return true;
1789 else
1791 /* Todo: Figure out if we can trigger this, if it's worth to handle
1792 optimally, and if we can handle it optimally. */
1793 return false;
1797 gcc_assert (TREE_CODE (nit) == SSA_NAME);
1799 /* Variable nit is the loop bound as returned by canonicalize_loop_ivs, for an
1800 iv with base 0 and step 1 that is incremented in the latch, like this:
1802 <bb header>:
1803 # iv_1 = PHI <0 (preheader), iv_2 (latch)>
1805 if (iv_1 < nit)
1806 goto <bb latch>;
1807 else
1808 goto <bb exit>;
1810 <bb latch>:
1811 iv_2 = iv_1 + 1;
1812 goto <bb header>;
1814 The range of iv_1 is [0, nit]. The latch edge is taken for
1815 iv_1 == [0, nit - 1] and the exit edge is taken for iv_1 == nit. So the
1816 number of latch executions is equal to nit.
1818 The function max_loop_iterations gives us the maximum number of latch
1819 executions, so it gives us the maximum value of nit. */
1820 widest_int nit_max;
1821 if (!max_loop_iterations (loop, &nit_max))
1822 return false;
1824 /* Check if nit + 1 overflows. */
1825 widest_int type_max = wi::to_widest (TYPE_MAXVAL (nit_type));
1826 if (!wi::lts_p (nit_max, type_max))
1827 return false;
1829 gimple def = SSA_NAME_DEF_STMT (nit);
1831 /* Try to find nit + 1, in the form of n in an assignment nit = n - 1. */
1832 if (def
1833 && is_gimple_assign (def)
1834 && gimple_assign_rhs_code (def) == PLUS_EXPR)
1836 tree op1 = gimple_assign_rhs1 (def);
1837 tree op2 = gimple_assign_rhs2 (def);
1838 if (integer_minus_onep (op1))
1839 alt_bound = op2;
1840 else if (integer_minus_onep (op2))
1841 alt_bound = op1;
1844 /* If not found, insert nit + 1. */
1845 if (alt_bound == NULL_TREE)
1847 alt_bound = fold_build2 (PLUS_EXPR, nit_type, nit,
1848 build_int_cst_type (nit_type, 1));
1850 gimple_stmt_iterator gsi = gsi_last_bb (loop_preheader_edge (loop)->src);
1852 alt_bound
1853 = force_gimple_operand_gsi (&gsi, alt_bound, true, NULL_TREE, false,
1854 GSI_CONTINUE_LINKING);
1857 transform_to_exit_first_loop_alt (loop, reduction_list, alt_bound);
1858 return true;
1861 /* Moves the exit condition of LOOP to the beginning of its header. NIT is the
1862 number of iterations of the loop. REDUCTION_LIST describes the reductions in
1863 LOOP. */
1865 static void
1866 transform_to_exit_first_loop (struct loop *loop,
1867 reduction_info_table_type *reduction_list,
1868 tree nit)
1870 basic_block *bbs, *nbbs, ex_bb, orig_header;
1871 unsigned n;
1872 bool ok;
1873 edge exit = single_dom_exit (loop), hpred;
1874 tree control, control_name, res, t;
1875 gphi *phi, *nphi;
1876 gassign *stmt;
1877 gcond *cond_stmt, *cond_nit;
1878 tree nit_1;
1880 split_block_after_labels (loop->header);
1881 orig_header = single_succ (loop->header);
1882 hpred = single_succ_edge (loop->header);
1884 cond_stmt = as_a <gcond *> (last_stmt (exit->src));
1885 control = gimple_cond_lhs (cond_stmt);
1886 gcc_assert (gimple_cond_rhs (cond_stmt) == nit);
1888 /* Make sure that we have phi nodes on exit for all loop header phis
1889 (create_parallel_loop requires that). */
1890 for (gphi_iterator gsi = gsi_start_phis (loop->header);
1891 !gsi_end_p (gsi);
1892 gsi_next (&gsi))
1894 phi = gsi.phi ();
1895 res = PHI_RESULT (phi);
1896 t = copy_ssa_name (res, phi);
1897 SET_PHI_RESULT (phi, t);
1898 nphi = create_phi_node (res, orig_header);
1899 add_phi_arg (nphi, t, hpred, UNKNOWN_LOCATION);
1901 if (res == control)
1903 gimple_cond_set_lhs (cond_stmt, t);
1904 update_stmt (cond_stmt);
1905 control = t;
1909 bbs = get_loop_body_in_dom_order (loop);
1911 for (n = 0; bbs[n] != exit->src; n++)
1912 continue;
1913 nbbs = XNEWVEC (basic_block, n);
1914 ok = gimple_duplicate_sese_tail (single_succ_edge (loop->header), exit,
1915 bbs + 1, n, nbbs);
1916 gcc_assert (ok);
1917 free (bbs);
1918 ex_bb = nbbs[0];
1919 free (nbbs);
1921 /* Other than reductions, the only gimple reg that should be copied
1922 out of the loop is the control variable. */
1923 exit = single_dom_exit (loop);
1924 control_name = NULL_TREE;
1925 for (gphi_iterator gsi = gsi_start_phis (ex_bb);
1926 !gsi_end_p (gsi); )
1928 phi = gsi.phi ();
1929 res = PHI_RESULT (phi);
1930 if (virtual_operand_p (res))
1932 gsi_next (&gsi);
1933 continue;
1936 /* Check if it is a part of reduction. If it is,
1937 keep the phi at the reduction's keep_res field. The
1938 PHI_RESULT of this phi is the resulting value of the reduction
1939 variable when exiting the loop. */
1941 if (reduction_list->elements () > 0)
1943 struct reduction_info *red;
1945 tree val = PHI_ARG_DEF_FROM_EDGE (phi, exit);
1946 red = reduction_phi (reduction_list, SSA_NAME_DEF_STMT (val));
1947 if (red)
1949 red->keep_res = phi;
1950 gsi_next (&gsi);
1951 continue;
1954 gcc_assert (control_name == NULL_TREE
1955 && SSA_NAME_VAR (res) == SSA_NAME_VAR (control));
1956 control_name = res;
1957 remove_phi_node (&gsi, false);
1959 gcc_assert (control_name != NULL_TREE);
1961 /* Initialize the control variable to number of iterations
1962 according to the rhs of the exit condition. */
1963 gimple_stmt_iterator gsi = gsi_after_labels (ex_bb);
1964 cond_nit = as_a <gcond *> (last_stmt (exit->src));
1965 nit_1 = gimple_cond_rhs (cond_nit);
1966 nit_1 = force_gimple_operand_gsi (&gsi,
1967 fold_convert (TREE_TYPE (control_name), nit_1),
1968 false, NULL_TREE, false, GSI_SAME_STMT);
1969 stmt = gimple_build_assign (control_name, nit_1);
1970 gsi_insert_before (&gsi, stmt, GSI_NEW_STMT);
1973 /* Create the parallel constructs for LOOP as described in gen_parallel_loop.
1974 LOOP_FN and DATA are the arguments of GIMPLE_OMP_PARALLEL.
1975 NEW_DATA is the variable that should be initialized from the argument
1976 of LOOP_FN. N_THREADS is the requested number of threads. Returns the
1977 basic block containing GIMPLE_OMP_PARALLEL tree. */
1979 static basic_block
1980 create_parallel_loop (struct loop *loop, tree loop_fn, tree data,
1981 tree new_data, unsigned n_threads, location_t loc)
1983 gimple_stmt_iterator gsi;
1984 basic_block bb, paral_bb, for_bb, ex_bb;
1985 tree t, param;
1986 gomp_parallel *omp_par_stmt;
1987 gimple omp_return_stmt1, omp_return_stmt2;
1988 gimple phi;
1989 gcond *cond_stmt;
1990 gomp_for *for_stmt;
1991 gomp_continue *omp_cont_stmt;
1992 tree cvar, cvar_init, initvar, cvar_next, cvar_base, type;
1993 edge exit, nexit, guard, end, e;
1995 /* Prepare the GIMPLE_OMP_PARALLEL statement. */
1996 bb = loop_preheader_edge (loop)->src;
1997 paral_bb = single_pred (bb);
1998 gsi = gsi_last_bb (paral_bb);
2000 t = build_omp_clause (loc, OMP_CLAUSE_NUM_THREADS);
2001 OMP_CLAUSE_NUM_THREADS_EXPR (t)
2002 = build_int_cst (integer_type_node, n_threads);
2003 omp_par_stmt = gimple_build_omp_parallel (NULL, t, loop_fn, data);
2004 gimple_set_location (omp_par_stmt, loc);
2006 gsi_insert_after (&gsi, omp_par_stmt, GSI_NEW_STMT);
2008 /* Initialize NEW_DATA. */
2009 if (data)
2011 gassign *assign_stmt;
2013 gsi = gsi_after_labels (bb);
2015 param = make_ssa_name (DECL_ARGUMENTS (loop_fn));
2016 assign_stmt = gimple_build_assign (param, build_fold_addr_expr (data));
2017 gsi_insert_before (&gsi, assign_stmt, GSI_SAME_STMT);
2019 assign_stmt = gimple_build_assign (new_data,
2020 fold_convert (TREE_TYPE (new_data), param));
2021 gsi_insert_before (&gsi, assign_stmt, GSI_SAME_STMT);
2024 /* Emit GIMPLE_OMP_RETURN for GIMPLE_OMP_PARALLEL. */
2025 bb = split_loop_exit_edge (single_dom_exit (loop));
2026 gsi = gsi_last_bb (bb);
2027 omp_return_stmt1 = gimple_build_omp_return (false);
2028 gimple_set_location (omp_return_stmt1, loc);
2029 gsi_insert_after (&gsi, omp_return_stmt1, GSI_NEW_STMT);
2031 /* Extract data for GIMPLE_OMP_FOR. */
2032 gcc_assert (loop->header == single_dom_exit (loop)->src);
2033 cond_stmt = as_a <gcond *> (last_stmt (loop->header));
2035 cvar = gimple_cond_lhs (cond_stmt);
2036 cvar_base = SSA_NAME_VAR (cvar);
2037 phi = SSA_NAME_DEF_STMT (cvar);
2038 cvar_init = PHI_ARG_DEF_FROM_EDGE (phi, loop_preheader_edge (loop));
2039 initvar = copy_ssa_name (cvar);
2040 SET_USE (PHI_ARG_DEF_PTR_FROM_EDGE (phi, loop_preheader_edge (loop)),
2041 initvar);
2042 cvar_next = PHI_ARG_DEF_FROM_EDGE (phi, loop_latch_edge (loop));
2044 gsi = gsi_last_nondebug_bb (loop->latch);
2045 gcc_assert (gsi_stmt (gsi) == SSA_NAME_DEF_STMT (cvar_next));
2046 gsi_remove (&gsi, true);
2048 /* Prepare cfg. */
2049 for_bb = split_edge (loop_preheader_edge (loop));
2050 ex_bb = split_loop_exit_edge (single_dom_exit (loop));
2051 extract_true_false_edges_from_block (loop->header, &nexit, &exit);
2052 gcc_assert (exit == single_dom_exit (loop));
2054 guard = make_edge (for_bb, ex_bb, 0);
2055 single_succ_edge (loop->latch)->flags = 0;
2056 end = make_edge (loop->latch, ex_bb, EDGE_FALLTHRU);
2057 for (gphi_iterator gpi = gsi_start_phis (ex_bb);
2058 !gsi_end_p (gpi); gsi_next (&gpi))
2060 source_location locus;
2061 gphi *phi = gpi.phi ();
2062 tree def = PHI_ARG_DEF_FROM_EDGE (phi, exit);
2063 gimple def_stmt = SSA_NAME_DEF_STMT (def);
2065 /* If the exit phi is not connected to a header phi in the same loop, this
2066 value is not modified in the loop, and we're done with this phi. */
2067 if (!(gimple_code (def_stmt) == GIMPLE_PHI
2068 && gimple_bb (def_stmt) == loop->header))
2069 continue;
2071 gphi *stmt = as_a <gphi *> (def_stmt);
2072 def = PHI_ARG_DEF_FROM_EDGE (stmt, loop_preheader_edge (loop));
2073 locus = gimple_phi_arg_location_from_edge (stmt,
2074 loop_preheader_edge (loop));
2075 add_phi_arg (phi, def, guard, locus);
2077 def = PHI_ARG_DEF_FROM_EDGE (stmt, loop_latch_edge (loop));
2078 locus = gimple_phi_arg_location_from_edge (stmt, loop_latch_edge (loop));
2079 add_phi_arg (phi, def, end, locus);
2081 e = redirect_edge_and_branch (exit, nexit->dest);
2082 PENDING_STMT (e) = NULL;
2084 /* Emit GIMPLE_OMP_FOR. */
2085 gimple_cond_set_lhs (cond_stmt, cvar_base);
2086 type = TREE_TYPE (cvar);
2087 t = build_omp_clause (loc, OMP_CLAUSE_SCHEDULE);
2088 OMP_CLAUSE_SCHEDULE_KIND (t) = OMP_CLAUSE_SCHEDULE_STATIC;
2090 for_stmt = gimple_build_omp_for (NULL, GF_OMP_FOR_KIND_FOR, t, 1, NULL);
2091 gimple_set_location (for_stmt, loc);
2092 gimple_omp_for_set_index (for_stmt, 0, initvar);
2093 gimple_omp_for_set_initial (for_stmt, 0, cvar_init);
2094 gimple_omp_for_set_final (for_stmt, 0, gimple_cond_rhs (cond_stmt));
2095 gimple_omp_for_set_cond (for_stmt, 0, gimple_cond_code (cond_stmt));
2096 gimple_omp_for_set_incr (for_stmt, 0, build2 (PLUS_EXPR, type,
2097 cvar_base,
2098 build_int_cst (type, 1)));
2100 gsi = gsi_last_bb (for_bb);
2101 gsi_insert_after (&gsi, for_stmt, GSI_NEW_STMT);
2102 SSA_NAME_DEF_STMT (initvar) = for_stmt;
2104 /* Emit GIMPLE_OMP_CONTINUE. */
2105 gsi = gsi_last_bb (loop->latch);
2106 omp_cont_stmt = gimple_build_omp_continue (cvar_next, cvar);
2107 gimple_set_location (omp_cont_stmt, loc);
2108 gsi_insert_after (&gsi, omp_cont_stmt, GSI_NEW_STMT);
2109 SSA_NAME_DEF_STMT (cvar_next) = omp_cont_stmt;
2111 /* Emit GIMPLE_OMP_RETURN for GIMPLE_OMP_FOR. */
2112 gsi = gsi_last_bb (ex_bb);
2113 omp_return_stmt2 = gimple_build_omp_return (true);
2114 gimple_set_location (omp_return_stmt2, loc);
2115 gsi_insert_after (&gsi, omp_return_stmt2, GSI_NEW_STMT);
2117 /* After the above dom info is hosed. Re-compute it. */
2118 free_dominance_info (CDI_DOMINATORS);
2119 calculate_dominance_info (CDI_DOMINATORS);
2121 return paral_bb;
2124 /* Generates code to execute the iterations of LOOP in N_THREADS
2125 threads in parallel.
2127 NITER describes number of iterations of LOOP.
2128 REDUCTION_LIST describes the reductions existent in the LOOP. */
2130 static void
2131 gen_parallel_loop (struct loop *loop,
2132 reduction_info_table_type *reduction_list,
2133 unsigned n_threads, struct tree_niter_desc *niter)
2135 tree many_iterations_cond, type, nit;
2136 tree arg_struct, new_arg_struct;
2137 gimple_seq stmts;
2138 edge entry, exit;
2139 struct clsn_data clsn_data;
2140 unsigned prob;
2141 location_t loc;
2142 gimple cond_stmt;
2143 unsigned int m_p_thread=2;
2145 /* From
2147 ---------------------------------------------------------------------
2148 loop
2150 IV = phi (INIT, IV + STEP)
2151 BODY1;
2152 if (COND)
2153 break;
2154 BODY2;
2156 ---------------------------------------------------------------------
2158 with # of iterations NITER (possibly with MAY_BE_ZERO assumption),
2159 we generate the following code:
2161 ---------------------------------------------------------------------
2163 if (MAY_BE_ZERO
2164 || NITER < MIN_PER_THREAD * N_THREADS)
2165 goto original;
2167 BODY1;
2168 store all local loop-invariant variables used in body of the loop to DATA.
2169 GIMPLE_OMP_PARALLEL (OMP_CLAUSE_NUM_THREADS (N_THREADS), LOOPFN, DATA);
2170 load the variables from DATA.
2171 GIMPLE_OMP_FOR (IV = INIT; COND; IV += STEP) (OMP_CLAUSE_SCHEDULE (static))
2172 BODY2;
2173 BODY1;
2174 GIMPLE_OMP_CONTINUE;
2175 GIMPLE_OMP_RETURN -- GIMPLE_OMP_FOR
2176 GIMPLE_OMP_RETURN -- GIMPLE_OMP_PARALLEL
2177 goto end;
2179 original:
2180 loop
2182 IV = phi (INIT, IV + STEP)
2183 BODY1;
2184 if (COND)
2185 break;
2186 BODY2;
2189 end:
2193 /* Create two versions of the loop -- in the old one, we know that the
2194 number of iterations is large enough, and we will transform it into the
2195 loop that will be split to loop_fn, the new one will be used for the
2196 remaining iterations. */
2198 /* We should compute a better number-of-iterations value for outer loops.
2199 That is, if we have
2201 for (i = 0; i < n; ++i)
2202 for (j = 0; j < m; ++j)
2205 we should compute nit = n * m, not nit = n.
2206 Also may_be_zero handling would need to be adjusted. */
2208 type = TREE_TYPE (niter->niter);
2209 nit = force_gimple_operand (unshare_expr (niter->niter), &stmts, true,
2210 NULL_TREE);
2211 if (stmts)
2212 gsi_insert_seq_on_edge_immediate (loop_preheader_edge (loop), stmts);
2214 if (loop->inner)
2215 m_p_thread=2;
2216 else
2217 m_p_thread=MIN_PER_THREAD;
2219 many_iterations_cond =
2220 fold_build2 (GE_EXPR, boolean_type_node,
2221 nit, build_int_cst (type, m_p_thread * n_threads));
2223 many_iterations_cond
2224 = fold_build2 (TRUTH_AND_EXPR, boolean_type_node,
2225 invert_truthvalue (unshare_expr (niter->may_be_zero)),
2226 many_iterations_cond);
2227 many_iterations_cond
2228 = force_gimple_operand (many_iterations_cond, &stmts, false, NULL_TREE);
2229 if (stmts)
2230 gsi_insert_seq_on_edge_immediate (loop_preheader_edge (loop), stmts);
2231 if (!is_gimple_condexpr (many_iterations_cond))
2233 many_iterations_cond
2234 = force_gimple_operand (many_iterations_cond, &stmts,
2235 true, NULL_TREE);
2236 if (stmts)
2237 gsi_insert_seq_on_edge_immediate (loop_preheader_edge (loop), stmts);
2240 initialize_original_copy_tables ();
2242 /* We assume that the loop usually iterates a lot. */
2243 prob = 4 * REG_BR_PROB_BASE / 5;
2244 loop_version (loop, many_iterations_cond, NULL,
2245 prob, prob, REG_BR_PROB_BASE - prob, true);
2246 update_ssa (TODO_update_ssa);
2247 free_original_copy_tables ();
2249 /* Base all the induction variables in LOOP on a single control one. */
2250 canonicalize_loop_ivs (loop, &nit, true);
2252 /* Ensure that the exit condition is the first statement in the loop.
2253 The common case is that latch of the loop is empty (apart from the
2254 increment) and immediately follows the loop exit test. Attempt to move the
2255 entry of the loop directly before the exit check and increase the number of
2256 iterations of the loop by one. */
2257 if (try_transform_to_exit_first_loop_alt (loop, reduction_list, nit))
2259 if (dump_file
2260 && (dump_flags & TDF_DETAILS))
2261 fprintf (dump_file,
2262 "alternative exit-first loop transform succeeded"
2263 " for loop %d\n", loop->num);
2265 else
2267 /* Fall back on the method that handles more cases, but duplicates the
2268 loop body: move the exit condition of LOOP to the beginning of its
2269 header, and duplicate the part of the last iteration that gets disabled
2270 to the exit of the loop. */
2271 transform_to_exit_first_loop (loop, reduction_list, nit);
2274 /* Generate initializations for reductions. */
2275 if (reduction_list->elements () > 0)
2276 reduction_list->traverse <struct loop *, initialize_reductions> (loop);
2278 /* Eliminate the references to local variables from the loop. */
2279 gcc_assert (single_exit (loop));
2280 entry = loop_preheader_edge (loop);
2281 exit = single_dom_exit (loop);
2283 eliminate_local_variables (entry, exit);
2284 /* In the old loop, move all variables non-local to the loop to a structure
2285 and back, and create separate decls for the variables used in loop. */
2286 separate_decls_in_region (entry, exit, reduction_list, &arg_struct,
2287 &new_arg_struct, &clsn_data);
2289 /* Create the parallel constructs. */
2290 loc = UNKNOWN_LOCATION;
2291 cond_stmt = last_stmt (loop->header);
2292 if (cond_stmt)
2293 loc = gimple_location (cond_stmt);
2294 create_parallel_loop (loop, create_loop_fn (loc), arg_struct,
2295 new_arg_struct, n_threads, loc);
2296 if (reduction_list->elements () > 0)
2297 create_call_for_reduction (loop, reduction_list, &clsn_data);
2299 scev_reset ();
2301 /* Cancel the loop (it is simpler to do it here rather than to teach the
2302 expander to do it). */
2303 cancel_loop_tree (loop);
2305 /* Free loop bound estimations that could contain references to
2306 removed statements. */
2307 FOR_EACH_LOOP (loop, 0)
2308 free_numbers_of_iterations_estimates_loop (loop);
2311 /* Returns true when LOOP contains vector phi nodes. */
2313 static bool
2314 loop_has_vector_phi_nodes (struct loop *loop ATTRIBUTE_UNUSED)
2316 unsigned i;
2317 basic_block *bbs = get_loop_body_in_dom_order (loop);
2318 gphi_iterator gsi;
2319 bool res = true;
2321 for (i = 0; i < loop->num_nodes; i++)
2322 for (gsi = gsi_start_phis (bbs[i]); !gsi_end_p (gsi); gsi_next (&gsi))
2323 if (TREE_CODE (TREE_TYPE (PHI_RESULT (gsi.phi ()))) == VECTOR_TYPE)
2324 goto end;
2326 res = false;
2327 end:
2328 free (bbs);
2329 return res;
2332 /* Create a reduction_info struct, initialize it with REDUC_STMT
2333 and PHI, insert it to the REDUCTION_LIST. */
2335 static void
2336 build_new_reduction (reduction_info_table_type *reduction_list,
2337 gimple reduc_stmt, gphi *phi)
2339 reduction_info **slot;
2340 struct reduction_info *new_reduction;
2341 enum tree_code reduction_code;
2343 gcc_assert (reduc_stmt);
2345 if (dump_file && (dump_flags & TDF_DETAILS))
2347 fprintf (dump_file,
2348 "Detected reduction. reduction stmt is: \n");
2349 print_gimple_stmt (dump_file, reduc_stmt, 0, 0);
2350 fprintf (dump_file, "\n");
2353 if (gimple_code (reduc_stmt) == GIMPLE_PHI)
2355 tree op1 = PHI_ARG_DEF (reduc_stmt, 0);
2356 gimple def1 = SSA_NAME_DEF_STMT (op1);
2357 reduction_code = gimple_assign_rhs_code (def1);
2360 else
2361 reduction_code = gimple_assign_rhs_code (reduc_stmt);
2363 new_reduction = XCNEW (struct reduction_info);
2365 new_reduction->reduc_stmt = reduc_stmt;
2366 new_reduction->reduc_phi = phi;
2367 new_reduction->reduc_version = SSA_NAME_VERSION (gimple_phi_result (phi));
2368 new_reduction->reduction_code = reduction_code;
2369 slot = reduction_list->find_slot (new_reduction, INSERT);
2370 *slot = new_reduction;
2373 /* Callback for htab_traverse. Sets gimple_uid of reduc_phi stmts. */
2376 set_reduc_phi_uids (reduction_info **slot, void *data ATTRIBUTE_UNUSED)
2378 struct reduction_info *const red = *slot;
2379 gimple_set_uid (red->reduc_phi, red->reduc_version);
2380 return 1;
2383 /* Detect all reductions in the LOOP, insert them into REDUCTION_LIST. */
2385 static void
2386 gather_scalar_reductions (loop_p loop, reduction_info_table_type *reduction_list)
2388 gphi_iterator gsi;
2389 loop_vec_info simple_loop_info;
2390 loop_vec_info simple_inner_loop_info = NULL;
2391 bool allow_double_reduc = true;
2393 simple_loop_info = vect_analyze_loop_form (loop);
2394 if (simple_loop_info == NULL)
2395 return;
2397 for (gsi = gsi_start_phis (loop->header); !gsi_end_p (gsi); gsi_next (&gsi))
2399 gphi *phi = gsi.phi ();
2400 affine_iv iv;
2401 tree res = PHI_RESULT (phi);
2402 bool double_reduc;
2404 if (virtual_operand_p (res))
2405 continue;
2407 if (simple_iv (loop, loop, res, &iv, true))
2408 continue;
2410 gimple reduc_stmt
2411 = vect_force_simple_reduction (simple_loop_info, phi, true,
2412 &double_reduc, true);
2413 if (!reduc_stmt)
2414 continue;
2416 if (double_reduc)
2418 if (!allow_double_reduc
2419 || loop->inner->inner != NULL)
2420 continue;
2422 if (!simple_inner_loop_info)
2424 simple_inner_loop_info = vect_analyze_loop_form (loop->inner);
2425 if (!simple_inner_loop_info)
2427 allow_double_reduc = false;
2428 continue;
2432 use_operand_p use_p;
2433 gimple inner_stmt;
2434 bool single_use_p = single_imm_use (res, &use_p, &inner_stmt);
2435 gcc_assert (single_use_p);
2436 gphi *inner_phi = as_a <gphi *> (inner_stmt);
2437 if (simple_iv (loop->inner, loop->inner, PHI_RESULT (inner_phi),
2438 &iv, true))
2439 continue;
2441 gimple inner_reduc_stmt
2442 = vect_force_simple_reduction (simple_inner_loop_info, inner_phi,
2443 true, &double_reduc, true);
2444 gcc_assert (!double_reduc);
2445 if (inner_reduc_stmt == NULL)
2446 continue;
2449 build_new_reduction (reduction_list, reduc_stmt, phi);
2451 destroy_loop_vec_info (simple_loop_info, true);
2452 destroy_loop_vec_info (simple_inner_loop_info, true);
2454 /* As gimple_uid is used by the vectorizer in between vect_analyze_loop_form
2455 and destroy_loop_vec_info, we can set gimple_uid of reduc_phi stmts
2456 only now. */
2457 reduction_list->traverse <void *, set_reduc_phi_uids> (NULL);
2460 /* Try to initialize NITER for code generation part. */
2462 static bool
2463 try_get_loop_niter (loop_p loop, struct tree_niter_desc *niter)
2465 edge exit = single_dom_exit (loop);
2467 gcc_assert (exit);
2469 /* We need to know # of iterations, and there should be no uses of values
2470 defined inside loop outside of it, unless the values are invariants of
2471 the loop. */
2472 if (!number_of_iterations_exit (loop, exit, niter, false))
2474 if (dump_file && (dump_flags & TDF_DETAILS))
2475 fprintf (dump_file, " FAILED: number of iterations not known\n");
2476 return false;
2479 return true;
2482 /* Try to initialize REDUCTION_LIST for code generation part.
2483 REDUCTION_LIST describes the reductions. */
2485 static bool
2486 try_create_reduction_list (loop_p loop,
2487 reduction_info_table_type *reduction_list)
2489 edge exit = single_dom_exit (loop);
2490 gphi_iterator gsi;
2492 gcc_assert (exit);
2494 gather_scalar_reductions (loop, reduction_list);
2497 for (gsi = gsi_start_phis (exit->dest); !gsi_end_p (gsi); gsi_next (&gsi))
2499 gphi *phi = gsi.phi ();
2500 struct reduction_info *red;
2501 imm_use_iterator imm_iter;
2502 use_operand_p use_p;
2503 gimple reduc_phi;
2504 tree val = PHI_ARG_DEF_FROM_EDGE (phi, exit);
2506 if (!virtual_operand_p (val))
2508 if (dump_file && (dump_flags & TDF_DETAILS))
2510 fprintf (dump_file, "phi is ");
2511 print_gimple_stmt (dump_file, phi, 0, 0);
2512 fprintf (dump_file, "arg of phi to exit: value ");
2513 print_generic_expr (dump_file, val, 0);
2514 fprintf (dump_file, " used outside loop\n");
2515 fprintf (dump_file,
2516 " checking if it a part of reduction pattern: \n");
2518 if (reduction_list->elements () == 0)
2520 if (dump_file && (dump_flags & TDF_DETAILS))
2521 fprintf (dump_file,
2522 " FAILED: it is not a part of reduction.\n");
2523 return false;
2525 reduc_phi = NULL;
2526 FOR_EACH_IMM_USE_FAST (use_p, imm_iter, val)
2528 if (!gimple_debug_bind_p (USE_STMT (use_p))
2529 && flow_bb_inside_loop_p (loop, gimple_bb (USE_STMT (use_p))))
2531 reduc_phi = USE_STMT (use_p);
2532 break;
2535 red = reduction_phi (reduction_list, reduc_phi);
2536 if (red == NULL)
2538 if (dump_file && (dump_flags & TDF_DETAILS))
2539 fprintf (dump_file,
2540 " FAILED: it is not a part of reduction.\n");
2541 return false;
2543 if (dump_file && (dump_flags & TDF_DETAILS))
2545 fprintf (dump_file, "reduction phi is ");
2546 print_gimple_stmt (dump_file, red->reduc_phi, 0, 0);
2547 fprintf (dump_file, "reduction stmt is ");
2548 print_gimple_stmt (dump_file, red->reduc_stmt, 0, 0);
2553 /* The iterations of the loop may communicate only through bivs whose
2554 iteration space can be distributed efficiently. */
2555 for (gsi = gsi_start_phis (loop->header); !gsi_end_p (gsi); gsi_next (&gsi))
2557 gphi *phi = gsi.phi ();
2558 tree def = PHI_RESULT (phi);
2559 affine_iv iv;
2561 if (!virtual_operand_p (def) && !simple_iv (loop, loop, def, &iv, true))
2563 struct reduction_info *red;
2565 red = reduction_phi (reduction_list, phi);
2566 if (red == NULL)
2568 if (dump_file && (dump_flags & TDF_DETAILS))
2569 fprintf (dump_file,
2570 " FAILED: scalar dependency between iterations\n");
2571 return false;
2577 return true;
2580 /* Detect parallel loops and generate parallel code using libgomp
2581 primitives. Returns true if some loop was parallelized, false
2582 otherwise. */
2584 static bool
2585 parallelize_loops (void)
2587 unsigned n_threads = flag_tree_parallelize_loops;
2588 bool changed = false;
2589 struct loop *loop;
2590 struct tree_niter_desc niter_desc;
2591 struct obstack parloop_obstack;
2592 HOST_WIDE_INT estimated;
2593 source_location loop_loc;
2595 /* Do not parallelize loops in the functions created by parallelization. */
2596 if (parallelized_function_p (cfun->decl))
2597 return false;
2598 if (cfun->has_nonlocal_label)
2599 return false;
2601 gcc_obstack_init (&parloop_obstack);
2602 reduction_info_table_type reduction_list (10);
2603 init_stmt_vec_info_vec ();
2605 FOR_EACH_LOOP (loop, 0)
2607 reduction_list.empty ();
2608 if (dump_file && (dump_flags & TDF_DETAILS))
2610 fprintf (dump_file, "Trying loop %d as candidate\n",loop->num);
2611 if (loop->inner)
2612 fprintf (dump_file, "loop %d is not innermost\n",loop->num);
2613 else
2614 fprintf (dump_file, "loop %d is innermost\n",loop->num);
2617 /* If we use autopar in graphite pass, we use its marked dependency
2618 checking results. */
2619 if (flag_loop_parallelize_all && !loop->can_be_parallel)
2621 if (dump_file && (dump_flags & TDF_DETAILS))
2622 fprintf (dump_file, "loop is not parallel according to graphite\n");
2623 continue;
2626 if (!single_dom_exit (loop))
2629 if (dump_file && (dump_flags & TDF_DETAILS))
2630 fprintf (dump_file, "loop is !single_dom_exit\n");
2632 continue;
2635 if (/* And of course, the loop must be parallelizable. */
2636 !can_duplicate_loop_p (loop)
2637 || loop_has_blocks_with_irreducible_flag (loop)
2638 || (loop_preheader_edge (loop)->src->flags & BB_IRREDUCIBLE_LOOP)
2639 /* FIXME: the check for vector phi nodes could be removed. */
2640 || loop_has_vector_phi_nodes (loop))
2641 continue;
2643 estimated = estimated_stmt_executions_int (loop);
2644 if (estimated == -1)
2645 estimated = max_stmt_executions_int (loop);
2646 /* FIXME: Bypass this check as graphite doesn't update the
2647 count and frequency correctly now. */
2648 if (!flag_loop_parallelize_all
2649 && ((estimated != -1
2650 && estimated <= (HOST_WIDE_INT) n_threads * MIN_PER_THREAD)
2651 /* Do not bother with loops in cold areas. */
2652 || optimize_loop_nest_for_size_p (loop)))
2653 continue;
2655 if (!try_get_loop_niter (loop, &niter_desc))
2656 continue;
2658 if (!try_create_reduction_list (loop, &reduction_list))
2659 continue;
2661 if (!flag_loop_parallelize_all
2662 && !loop_parallel_p (loop, &parloop_obstack))
2663 continue;
2665 changed = true;
2666 if (dump_file && (dump_flags & TDF_DETAILS))
2668 if (loop->inner)
2669 fprintf (dump_file, "parallelizing outer loop %d\n",loop->header->index);
2670 else
2671 fprintf (dump_file, "parallelizing inner loop %d\n",loop->header->index);
2672 loop_loc = find_loop_location (loop);
2673 if (loop_loc != UNKNOWN_LOCATION)
2674 fprintf (dump_file, "\nloop at %s:%d: ",
2675 LOCATION_FILE (loop_loc), LOCATION_LINE (loop_loc));
2677 gen_parallel_loop (loop, &reduction_list,
2678 n_threads, &niter_desc);
2681 free_stmt_vec_info_vec ();
2682 obstack_free (&parloop_obstack, NULL);
2684 /* Parallelization will cause new function calls to be inserted through
2685 which local variables will escape. Reset the points-to solution
2686 for ESCAPED. */
2687 if (changed)
2688 pt_solution_reset (&cfun->gimple_df->escaped);
2690 return changed;
2693 /* Parallelization. */
2695 namespace {
2697 const pass_data pass_data_parallelize_loops =
2699 GIMPLE_PASS, /* type */
2700 "parloops", /* name */
2701 OPTGROUP_LOOP, /* optinfo_flags */
2702 TV_TREE_PARALLELIZE_LOOPS, /* tv_id */
2703 ( PROP_cfg | PROP_ssa ), /* properties_required */
2704 0, /* properties_provided */
2705 0, /* properties_destroyed */
2706 0, /* todo_flags_start */
2707 0, /* todo_flags_finish */
2710 class pass_parallelize_loops : public gimple_opt_pass
2712 public:
2713 pass_parallelize_loops (gcc::context *ctxt)
2714 : gimple_opt_pass (pass_data_parallelize_loops, ctxt)
2717 /* opt_pass methods: */
2718 virtual bool gate (function *) { return flag_tree_parallelize_loops > 1; }
2719 virtual unsigned int execute (function *);
2721 }; // class pass_parallelize_loops
2723 unsigned
2724 pass_parallelize_loops::execute (function *fun)
2726 if (number_of_loops (fun) <= 1)
2727 return 0;
2729 if (parallelize_loops ())
2731 fun->curr_properties &= ~(PROP_gimple_eomp);
2732 return TODO_update_ssa;
2735 return 0;
2738 } // anon namespace
2740 gimple_opt_pass *
2741 make_pass_parallelize_loops (gcc::context *ctxt)
2743 return new pass_parallelize_loops (ctxt);