tree-optimization/112767 - spurious diagnostic after sccp/loop-split swap
[official-gcc.git] / gcc / gimplify.cc
blob02f85e7109b30ba6ff84fa814f95eaae7495362c
1 /* Tree lowering pass. This pass converts the GENERIC functions-as-trees
2 tree representation into the GIMPLE form.
3 Copyright (C) 2002-2023 Free Software Foundation, Inc.
4 Major work done by Sebastian Pop <s.pop@laposte.net>,
5 Diego Novillo <dnovillo@redhat.com> and Jason Merrill <jason@redhat.com>.
7 This file is part of GCC.
9 GCC is free software; you can redistribute it and/or modify it under
10 the terms of the GNU General Public License as published by the Free
11 Software Foundation; either version 3, or (at your option) any later
12 version.
14 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
15 WARRANTY; without even the implied warranty of MERCHANTABILITY or
16 FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
17 for more details.
19 You should have received a copy of the GNU General Public License
20 along with GCC; see the file COPYING3. If not see
21 <http://www.gnu.org/licenses/>. */
23 #include "config.h"
24 #include "system.h"
25 #include "coretypes.h"
26 #include "backend.h"
27 #include "target.h"
28 #include "rtl.h"
29 #include "tree.h"
30 #include "memmodel.h"
31 #include "tm_p.h"
32 #include "gimple.h"
33 #include "gimple-predict.h"
34 #include "tree-pass.h" /* FIXME: only for PROP_gimple_any */
35 #include "ssa.h"
36 #include "cgraph.h"
37 #include "tree-pretty-print.h"
38 #include "diagnostic-core.h"
39 #include "diagnostic.h" /* For errorcount. */
40 #include "alias.h"
41 #include "fold-const.h"
42 #include "calls.h"
43 #include "varasm.h"
44 #include "stmt.h"
45 #include "expr.h"
46 #include "gimple-iterator.h"
47 #include "gimple-fold.h"
48 #include "tree-eh.h"
49 #include "gimplify.h"
50 #include "stor-layout.h"
51 #include "print-tree.h"
52 #include "tree-iterator.h"
53 #include "tree-inline.h"
54 #include "langhooks.h"
55 #include "tree-cfg.h"
56 #include "tree-ssa.h"
57 #include "tree-hash-traits.h"
58 #include "omp-general.h"
59 #include "omp-low.h"
60 #include "gimple-low.h"
61 #include "gomp-constants.h"
62 #include "splay-tree.h"
63 #include "gimple-walk.h"
64 #include "langhooks-def.h" /* FIXME: for lhd_set_decl_assembler_name */
65 #include "builtins.h"
66 #include "stringpool.h"
67 #include "attribs.h"
68 #include "asan.h"
69 #include "dbgcnt.h"
70 #include "omp-offload.h"
71 #include "context.h"
72 #include "tree-nested.h"
74 /* Hash set of poisoned variables in a bind expr. */
75 static hash_set<tree> *asan_poisoned_variables = NULL;
77 enum gimplify_omp_var_data
79 GOVD_SEEN = 0x000001,
80 GOVD_EXPLICIT = 0x000002,
81 GOVD_SHARED = 0x000004,
82 GOVD_PRIVATE = 0x000008,
83 GOVD_FIRSTPRIVATE = 0x000010,
84 GOVD_LASTPRIVATE = 0x000020,
85 GOVD_REDUCTION = 0x000040,
86 GOVD_LOCAL = 0x00080,
87 GOVD_MAP = 0x000100,
88 GOVD_DEBUG_PRIVATE = 0x000200,
89 GOVD_PRIVATE_OUTER_REF = 0x000400,
90 GOVD_LINEAR = 0x000800,
91 GOVD_ALIGNED = 0x001000,
93 /* Flag for GOVD_MAP: don't copy back. */
94 GOVD_MAP_TO_ONLY = 0x002000,
96 /* Flag for GOVD_LINEAR or GOVD_LASTPRIVATE: no outer reference. */
97 GOVD_LINEAR_LASTPRIVATE_NO_OUTER = 0x004000,
99 GOVD_MAP_0LEN_ARRAY = 0x008000,
101 /* Flag for GOVD_MAP, if it is always, to or always, tofrom mapping. */
102 GOVD_MAP_ALWAYS_TO = 0x010000,
104 /* Flag for shared vars that are or might be stored to in the region. */
105 GOVD_WRITTEN = 0x020000,
107 /* Flag for GOVD_MAP, if it is a forced mapping. */
108 GOVD_MAP_FORCE = 0x040000,
110 /* Flag for GOVD_MAP: must be present already. */
111 GOVD_MAP_FORCE_PRESENT = 0x080000,
113 /* Flag for GOVD_MAP: only allocate. */
114 GOVD_MAP_ALLOC_ONLY = 0x100000,
116 /* Flag for GOVD_MAP: only copy back. */
117 GOVD_MAP_FROM_ONLY = 0x200000,
119 GOVD_NONTEMPORAL = 0x400000,
121 /* Flag for GOVD_LASTPRIVATE: conditional modifier. */
122 GOVD_LASTPRIVATE_CONDITIONAL = 0x800000,
124 GOVD_CONDTEMP = 0x1000000,
126 /* Flag for GOVD_REDUCTION: inscan seen in {in,ex}clusive clause. */
127 GOVD_REDUCTION_INSCAN = 0x2000000,
129 /* Flag for GOVD_FIRSTPRIVATE: OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT. */
130 GOVD_FIRSTPRIVATE_IMPLICIT = 0x4000000,
132 GOVD_DATA_SHARE_CLASS = (GOVD_SHARED | GOVD_PRIVATE | GOVD_FIRSTPRIVATE
133 | GOVD_LASTPRIVATE | GOVD_REDUCTION | GOVD_LINEAR
134 | GOVD_LOCAL)
138 enum omp_region_type
140 ORT_WORKSHARE = 0x00,
141 ORT_TASKGROUP = 0x01,
142 ORT_SIMD = 0x04,
144 ORT_PARALLEL = 0x08,
145 ORT_COMBINED_PARALLEL = ORT_PARALLEL | 1,
147 ORT_TASK = 0x10,
148 ORT_UNTIED_TASK = ORT_TASK | 1,
149 ORT_TASKLOOP = ORT_TASK | 2,
150 ORT_UNTIED_TASKLOOP = ORT_UNTIED_TASK | 2,
152 ORT_TEAMS = 0x20,
153 ORT_COMBINED_TEAMS = ORT_TEAMS | 1,
154 ORT_HOST_TEAMS = ORT_TEAMS | 2,
155 ORT_COMBINED_HOST_TEAMS = ORT_COMBINED_TEAMS | 2,
157 /* Data region. */
158 ORT_TARGET_DATA = 0x40,
160 /* Data region with offloading. */
161 ORT_TARGET = 0x80,
162 ORT_COMBINED_TARGET = ORT_TARGET | 1,
163 ORT_IMPLICIT_TARGET = ORT_TARGET | 2,
165 /* OpenACC variants. */
166 ORT_ACC = 0x100, /* A generic OpenACC region. */
167 ORT_ACC_DATA = ORT_ACC | ORT_TARGET_DATA, /* Data construct. */
168 ORT_ACC_PARALLEL = ORT_ACC | ORT_TARGET, /* Parallel construct */
169 ORT_ACC_KERNELS = ORT_ACC | ORT_TARGET | 2, /* Kernels construct. */
170 ORT_ACC_SERIAL = ORT_ACC | ORT_TARGET | 4, /* Serial construct. */
171 ORT_ACC_HOST_DATA = ORT_ACC | ORT_TARGET_DATA | 2, /* Host data. */
173 /* Dummy OpenMP region, used to disable expansion of
174 DECL_VALUE_EXPRs in taskloop pre body. */
175 ORT_NONE = 0x200
178 /* Gimplify hashtable helper. */
180 struct gimplify_hasher : free_ptr_hash <elt_t>
182 static inline hashval_t hash (const elt_t *);
183 static inline bool equal (const elt_t *, const elt_t *);
186 struct gimplify_ctx
188 struct gimplify_ctx *prev_context;
190 vec<gbind *> bind_expr_stack;
191 tree temps;
192 gimple_seq conditional_cleanups;
193 tree exit_label;
194 tree return_temp;
196 vec<tree> case_labels;
197 hash_set<tree> *live_switch_vars;
198 /* The formal temporary table. Should this be persistent? */
199 hash_table<gimplify_hasher> *temp_htab;
201 int conditions;
202 unsigned into_ssa : 1;
203 unsigned allow_rhs_cond_expr : 1;
204 unsigned in_cleanup_point_expr : 1;
205 unsigned keep_stack : 1;
206 unsigned save_stack : 1;
207 unsigned in_switch_expr : 1;
210 enum gimplify_defaultmap_kind
212 GDMK_SCALAR,
213 GDMK_SCALAR_TARGET, /* w/ Fortran's target attr, implicit mapping, only. */
214 GDMK_AGGREGATE,
215 GDMK_ALLOCATABLE,
216 GDMK_POINTER
219 struct gimplify_omp_ctx
221 struct gimplify_omp_ctx *outer_context;
222 splay_tree variables;
223 hash_set<tree> *privatized_types;
224 tree clauses;
225 /* Iteration variables in an OMP_FOR. */
226 vec<tree> loop_iter_var;
227 location_t location;
228 enum omp_clause_default_kind default_kind;
229 enum omp_region_type region_type;
230 enum tree_code code;
231 bool combined_loop;
232 bool distribute;
233 bool target_firstprivatize_array_bases;
234 bool add_safelen1;
235 bool order_concurrent;
236 bool has_depend;
237 bool in_for_exprs;
238 int defaultmap[5];
241 static struct gimplify_ctx *gimplify_ctxp;
242 static struct gimplify_omp_ctx *gimplify_omp_ctxp;
243 static bool in_omp_construct;
245 /* Forward declaration. */
246 static enum gimplify_status gimplify_compound_expr (tree *, gimple_seq *, bool);
247 static hash_map<tree, tree> *oacc_declare_returns;
248 static enum gimplify_status gimplify_expr (tree *, gimple_seq *, gimple_seq *,
249 bool (*) (tree), fallback_t, bool);
250 static void prepare_gimple_addressable (tree *, gimple_seq *);
252 /* Shorter alias name for the above function for use in gimplify.cc
253 only. */
255 static inline void
256 gimplify_seq_add_stmt (gimple_seq *seq_p, gimple *gs)
258 gimple_seq_add_stmt_without_update (seq_p, gs);
261 /* Append sequence SRC to the end of sequence *DST_P. If *DST_P is
262 NULL, a new sequence is allocated. This function is
263 similar to gimple_seq_add_seq, but does not scan the operands.
264 During gimplification, we need to manipulate statement sequences
265 before the def/use vectors have been constructed. */
267 static void
268 gimplify_seq_add_seq (gimple_seq *dst_p, gimple_seq src)
270 gimple_stmt_iterator si;
272 if (src == NULL)
273 return;
275 si = gsi_last (*dst_p);
276 gsi_insert_seq_after_without_update (&si, src, GSI_NEW_STMT);
280 /* Pointer to a list of allocated gimplify_ctx structs to be used for pushing
281 and popping gimplify contexts. */
283 static struct gimplify_ctx *ctx_pool = NULL;
285 /* Return a gimplify context struct from the pool. */
287 static inline struct gimplify_ctx *
288 ctx_alloc (void)
290 struct gimplify_ctx * c = ctx_pool;
292 if (c)
293 ctx_pool = c->prev_context;
294 else
295 c = XNEW (struct gimplify_ctx);
297 memset (c, '\0', sizeof (*c));
298 return c;
301 /* Put gimplify context C back into the pool. */
303 static inline void
304 ctx_free (struct gimplify_ctx *c)
306 c->prev_context = ctx_pool;
307 ctx_pool = c;
310 /* Free allocated ctx stack memory. */
312 void
313 free_gimplify_stack (void)
315 struct gimplify_ctx *c;
317 while ((c = ctx_pool))
319 ctx_pool = c->prev_context;
320 free (c);
325 /* Set up a context for the gimplifier. */
327 void
328 push_gimplify_context (bool in_ssa, bool rhs_cond_ok)
330 struct gimplify_ctx *c = ctx_alloc ();
332 c->prev_context = gimplify_ctxp;
333 gimplify_ctxp = c;
334 gimplify_ctxp->into_ssa = in_ssa;
335 gimplify_ctxp->allow_rhs_cond_expr = rhs_cond_ok;
338 /* Tear down a context for the gimplifier. If BODY is non-null, then
339 put the temporaries into the outer BIND_EXPR. Otherwise, put them
340 in the local_decls.
342 BODY is not a sequence, but the first tuple in a sequence. */
344 void
345 pop_gimplify_context (gimple *body)
347 struct gimplify_ctx *c = gimplify_ctxp;
349 gcc_assert (c
350 && (!c->bind_expr_stack.exists ()
351 || c->bind_expr_stack.is_empty ()));
352 c->bind_expr_stack.release ();
353 gimplify_ctxp = c->prev_context;
355 if (body)
356 declare_vars (c->temps, body, false);
357 else
358 record_vars (c->temps);
360 delete c->temp_htab;
361 c->temp_htab = NULL;
362 ctx_free (c);
365 /* Push a GIMPLE_BIND tuple onto the stack of bindings. */
367 static void
368 gimple_push_bind_expr (gbind *bind_stmt)
370 gimplify_ctxp->bind_expr_stack.reserve (8);
371 gimplify_ctxp->bind_expr_stack.safe_push (bind_stmt);
374 /* Pop the first element off the stack of bindings. */
376 static void
377 gimple_pop_bind_expr (void)
379 gimplify_ctxp->bind_expr_stack.pop ();
382 /* Return the first element of the stack of bindings. */
384 gbind *
385 gimple_current_bind_expr (void)
387 return gimplify_ctxp->bind_expr_stack.last ();
390 /* Return the stack of bindings created during gimplification. */
392 vec<gbind *>
393 gimple_bind_expr_stack (void)
395 return gimplify_ctxp->bind_expr_stack;
398 /* Return true iff there is a COND_EXPR between us and the innermost
399 CLEANUP_POINT_EXPR. This info is used by gimple_push_cleanup. */
401 static bool
402 gimple_conditional_context (void)
404 return gimplify_ctxp->conditions > 0;
407 /* Note that we've entered a COND_EXPR. */
409 static void
410 gimple_push_condition (void)
412 #ifdef ENABLE_GIMPLE_CHECKING
413 if (gimplify_ctxp->conditions == 0)
414 gcc_assert (gimple_seq_empty_p (gimplify_ctxp->conditional_cleanups));
415 #endif
416 ++(gimplify_ctxp->conditions);
419 /* Note that we've left a COND_EXPR. If we're back at unconditional scope
420 now, add any conditional cleanups we've seen to the prequeue. */
422 static void
423 gimple_pop_condition (gimple_seq *pre_p)
425 int conds = --(gimplify_ctxp->conditions);
427 gcc_assert (conds >= 0);
428 if (conds == 0)
430 gimplify_seq_add_seq (pre_p, gimplify_ctxp->conditional_cleanups);
431 gimplify_ctxp->conditional_cleanups = NULL;
435 /* A stable comparison routine for use with splay trees and DECLs. */
437 static int
438 splay_tree_compare_decl_uid (splay_tree_key xa, splay_tree_key xb)
440 tree a = (tree) xa;
441 tree b = (tree) xb;
443 return DECL_UID (a) - DECL_UID (b);
446 /* Create a new omp construct that deals with variable remapping. */
448 static struct gimplify_omp_ctx *
449 new_omp_context (enum omp_region_type region_type)
451 struct gimplify_omp_ctx *c;
453 c = XCNEW (struct gimplify_omp_ctx);
454 c->outer_context = gimplify_omp_ctxp;
455 c->variables = splay_tree_new (splay_tree_compare_decl_uid, 0, 0);
456 c->privatized_types = new hash_set<tree>;
457 c->location = input_location;
458 c->region_type = region_type;
459 if ((region_type & ORT_TASK) == 0)
460 c->default_kind = OMP_CLAUSE_DEFAULT_SHARED;
461 else
462 c->default_kind = OMP_CLAUSE_DEFAULT_UNSPECIFIED;
463 c->defaultmap[GDMK_SCALAR] = GOVD_MAP;
464 c->defaultmap[GDMK_SCALAR_TARGET] = GOVD_MAP;
465 c->defaultmap[GDMK_AGGREGATE] = GOVD_MAP;
466 c->defaultmap[GDMK_ALLOCATABLE] = GOVD_MAP;
467 c->defaultmap[GDMK_POINTER] = GOVD_MAP;
469 return c;
472 /* Destroy an omp construct that deals with variable remapping. */
474 static void
475 delete_omp_context (struct gimplify_omp_ctx *c)
477 splay_tree_delete (c->variables);
478 delete c->privatized_types;
479 c->loop_iter_var.release ();
480 XDELETE (c);
483 static void omp_add_variable (struct gimplify_omp_ctx *, tree, unsigned int);
484 static bool omp_notice_variable (struct gimplify_omp_ctx *, tree, bool);
486 /* Both gimplify the statement T and append it to *SEQ_P. This function
487 behaves exactly as gimplify_stmt, but you don't have to pass T as a
488 reference. */
490 void
491 gimplify_and_add (tree t, gimple_seq *seq_p)
493 gimplify_stmt (&t, seq_p);
496 /* Gimplify statement T into sequence *SEQ_P, and return the first
497 tuple in the sequence of generated tuples for this statement.
498 Return NULL if gimplifying T produced no tuples. */
500 static gimple *
501 gimplify_and_return_first (tree t, gimple_seq *seq_p)
503 gimple_stmt_iterator last = gsi_last (*seq_p);
505 gimplify_and_add (t, seq_p);
507 if (!gsi_end_p (last))
509 gsi_next (&last);
510 return gsi_stmt (last);
512 else
513 return gimple_seq_first_stmt (*seq_p);
516 /* Returns true iff T is a valid RHS for an assignment to an un-renamed
517 LHS, or for a call argument. */
519 static bool
520 is_gimple_mem_rhs (tree t)
522 /* If we're dealing with a renamable type, either source or dest must be
523 a renamed variable. */
524 if (is_gimple_reg_type (TREE_TYPE (t)))
525 return is_gimple_val (t);
526 else
527 return is_gimple_val (t) || is_gimple_lvalue (t);
530 /* Return true if T is a CALL_EXPR or an expression that can be
531 assigned to a temporary. Note that this predicate should only be
532 used during gimplification. See the rationale for this in
533 gimplify_modify_expr. */
535 static bool
536 is_gimple_reg_rhs_or_call (tree t)
538 return (get_gimple_rhs_class (TREE_CODE (t)) != GIMPLE_INVALID_RHS
539 || TREE_CODE (t) == CALL_EXPR);
542 /* Return true if T is a valid memory RHS or a CALL_EXPR. Note that
543 this predicate should only be used during gimplification. See the
544 rationale for this in gimplify_modify_expr. */
546 static bool
547 is_gimple_mem_rhs_or_call (tree t)
549 /* If we're dealing with a renamable type, either source or dest must be
550 a renamed variable. */
551 if (is_gimple_reg_type (TREE_TYPE (t)))
552 return is_gimple_val (t);
553 else
554 return (is_gimple_val (t)
555 || is_gimple_lvalue (t)
556 || TREE_CLOBBER_P (t)
557 || TREE_CODE (t) == CALL_EXPR);
560 /* Create a temporary with a name derived from VAL. Subroutine of
561 lookup_tmp_var; nobody else should call this function. */
563 static inline tree
564 create_tmp_from_val (tree val)
566 /* Drop all qualifiers and address-space information from the value type. */
567 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (val));
568 tree var = create_tmp_var (type, get_name (val));
569 return var;
572 /* Create a temporary to hold the value of VAL. If IS_FORMAL, try to reuse
573 an existing expression temporary. If NOT_GIMPLE_REG, mark it as such. */
575 static tree
576 lookup_tmp_var (tree val, bool is_formal, bool not_gimple_reg)
578 tree ret;
580 /* We cannot mark a formal temporary with DECL_NOT_GIMPLE_REG_P. */
581 gcc_assert (!is_formal || !not_gimple_reg);
583 /* If not optimizing, never really reuse a temporary. local-alloc
584 won't allocate any variable that is used in more than one basic
585 block, which means it will go into memory, causing much extra
586 work in reload and final and poorer code generation, outweighing
587 the extra memory allocation here. */
588 if (!optimize || !is_formal || TREE_SIDE_EFFECTS (val))
590 ret = create_tmp_from_val (val);
591 DECL_NOT_GIMPLE_REG_P (ret) = not_gimple_reg;
593 else
595 elt_t elt, *elt_p;
596 elt_t **slot;
598 elt.val = val;
599 if (!gimplify_ctxp->temp_htab)
600 gimplify_ctxp->temp_htab = new hash_table<gimplify_hasher> (1000);
601 slot = gimplify_ctxp->temp_htab->find_slot (&elt, INSERT);
602 if (*slot == NULL)
604 elt_p = XNEW (elt_t);
605 elt_p->val = val;
606 elt_p->temp = ret = create_tmp_from_val (val);
607 *slot = elt_p;
609 else
611 elt_p = *slot;
612 ret = elt_p->temp;
616 return ret;
619 /* Helper for get_formal_tmp_var and get_initialized_tmp_var. */
621 static tree
622 internal_get_tmp_var (tree val, gimple_seq *pre_p, gimple_seq *post_p,
623 bool is_formal, bool allow_ssa, bool not_gimple_reg)
625 tree t, mod;
627 /* Notice that we explicitly allow VAL to be a CALL_EXPR so that we
628 can create an INIT_EXPR and convert it into a GIMPLE_CALL below. */
629 gimplify_expr (&val, pre_p, post_p, is_gimple_reg_rhs_or_call,
630 fb_rvalue);
632 if (allow_ssa
633 && gimplify_ctxp->into_ssa
634 && is_gimple_reg_type (TREE_TYPE (val)))
636 t = make_ssa_name (TYPE_MAIN_VARIANT (TREE_TYPE (val)));
637 if (! gimple_in_ssa_p (cfun))
639 const char *name = get_name (val);
640 if (name)
641 SET_SSA_NAME_VAR_OR_IDENTIFIER (t, create_tmp_var_name (name));
644 else
645 t = lookup_tmp_var (val, is_formal, not_gimple_reg);
647 mod = build2 (INIT_EXPR, TREE_TYPE (t), t, unshare_expr (val));
649 SET_EXPR_LOCATION (mod, EXPR_LOC_OR_LOC (val, input_location));
651 /* gimplify_modify_expr might want to reduce this further. */
652 gimplify_and_add (mod, pre_p);
653 ggc_free (mod);
655 return t;
658 /* Return a formal temporary variable initialized with VAL. PRE_P is as
659 in gimplify_expr. Only use this function if:
661 1) The value of the unfactored expression represented by VAL will not
662 change between the initialization and use of the temporary, and
663 2) The temporary will not be otherwise modified.
665 For instance, #1 means that this is inappropriate for SAVE_EXPR temps,
666 and #2 means it is inappropriate for && temps.
668 For other cases, use get_initialized_tmp_var instead. */
670 tree
671 get_formal_tmp_var (tree val, gimple_seq *pre_p)
673 return internal_get_tmp_var (val, pre_p, NULL, true, true, false);
676 /* Return a temporary variable initialized with VAL. PRE_P and POST_P
677 are as in gimplify_expr. */
679 tree
680 get_initialized_tmp_var (tree val, gimple_seq *pre_p,
681 gimple_seq *post_p /* = NULL */,
682 bool allow_ssa /* = true */)
684 return internal_get_tmp_var (val, pre_p, post_p, false, allow_ssa, false);
687 /* Declare all the variables in VARS in SCOPE. If DEBUG_INFO is true,
688 generate debug info for them; otherwise don't. */
690 void
691 declare_vars (tree vars, gimple *gs, bool debug_info)
693 tree last = vars;
694 if (last)
696 tree temps, block;
698 gbind *scope = as_a <gbind *> (gs);
700 temps = nreverse (last);
702 block = gimple_bind_block (scope);
703 gcc_assert (!block || TREE_CODE (block) == BLOCK);
704 if (!block || !debug_info)
706 DECL_CHAIN (last) = gimple_bind_vars (scope);
707 gimple_bind_set_vars (scope, temps);
709 else
711 /* We need to attach the nodes both to the BIND_EXPR and to its
712 associated BLOCK for debugging purposes. The key point here
713 is that the BLOCK_VARS of the BIND_EXPR_BLOCK of a BIND_EXPR
714 is a subchain of the BIND_EXPR_VARS of the BIND_EXPR. */
715 if (BLOCK_VARS (block))
716 BLOCK_VARS (block) = chainon (BLOCK_VARS (block), temps);
717 else
719 gimple_bind_set_vars (scope,
720 chainon (gimple_bind_vars (scope), temps));
721 BLOCK_VARS (block) = temps;
727 /* For VAR a VAR_DECL of variable size, try to find a constant upper bound
728 for the size and adjust DECL_SIZE/DECL_SIZE_UNIT accordingly. Abort if
729 no such upper bound can be obtained. */
731 static void
732 force_constant_size (tree var)
734 /* The only attempt we make is by querying the maximum size of objects
735 of the variable's type. */
737 HOST_WIDE_INT max_size;
739 gcc_assert (VAR_P (var));
741 max_size = max_int_size_in_bytes (TREE_TYPE (var));
743 gcc_assert (max_size >= 0);
745 DECL_SIZE_UNIT (var)
746 = build_int_cst (TREE_TYPE (DECL_SIZE_UNIT (var)), max_size);
747 DECL_SIZE (var)
748 = build_int_cst (TREE_TYPE (DECL_SIZE (var)), max_size * BITS_PER_UNIT);
751 /* Push the temporary variable TMP into the current binding. */
753 void
754 gimple_add_tmp_var_fn (struct function *fn, tree tmp)
756 gcc_assert (!DECL_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
758 /* Later processing assumes that the object size is constant, which might
759 not be true at this point. Force the use of a constant upper bound in
760 this case. */
761 if (!tree_fits_poly_uint64_p (DECL_SIZE_UNIT (tmp)))
762 force_constant_size (tmp);
764 DECL_CONTEXT (tmp) = fn->decl;
765 DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
767 record_vars_into (tmp, fn->decl);
770 /* Push the temporary variable TMP into the current binding. */
772 void
773 gimple_add_tmp_var (tree tmp)
775 gcc_assert (!DECL_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
777 /* Later processing assumes that the object size is constant, which might
778 not be true at this point. Force the use of a constant upper bound in
779 this case. */
780 if (!tree_fits_poly_uint64_p (DECL_SIZE_UNIT (tmp)))
781 force_constant_size (tmp);
783 DECL_CONTEXT (tmp) = current_function_decl;
784 DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
786 if (gimplify_ctxp)
788 DECL_CHAIN (tmp) = gimplify_ctxp->temps;
789 gimplify_ctxp->temps = tmp;
791 /* Mark temporaries local within the nearest enclosing parallel. */
792 if (gimplify_omp_ctxp)
794 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
795 int flag = GOVD_LOCAL | GOVD_SEEN;
796 while (ctx
797 && (ctx->region_type == ORT_WORKSHARE
798 || ctx->region_type == ORT_TASKGROUP
799 || ctx->region_type == ORT_SIMD
800 || ctx->region_type == ORT_ACC))
802 if (ctx->region_type == ORT_SIMD
803 && TREE_ADDRESSABLE (tmp)
804 && !TREE_STATIC (tmp))
806 if (TREE_CODE (DECL_SIZE_UNIT (tmp)) != INTEGER_CST)
807 ctx->add_safelen1 = true;
808 else if (ctx->in_for_exprs)
809 flag = GOVD_PRIVATE;
810 else
811 flag = GOVD_PRIVATE | GOVD_SEEN;
812 break;
814 ctx = ctx->outer_context;
816 if (ctx)
817 omp_add_variable (ctx, tmp, flag);
820 else if (cfun)
821 record_vars (tmp);
822 else
824 gimple_seq body_seq;
826 /* This case is for nested functions. We need to expose the locals
827 they create. */
828 body_seq = gimple_body (current_function_decl);
829 declare_vars (tmp, gimple_seq_first_stmt (body_seq), false);
835 /* This page contains routines to unshare tree nodes, i.e. to duplicate tree
836 nodes that are referenced more than once in GENERIC functions. This is
837 necessary because gimplification (translation into GIMPLE) is performed
838 by modifying tree nodes in-place, so gimplication of a shared node in a
839 first context could generate an invalid GIMPLE form in a second context.
841 This is achieved with a simple mark/copy/unmark algorithm that walks the
842 GENERIC representation top-down, marks nodes with TREE_VISITED the first
843 time it encounters them, duplicates them if they already have TREE_VISITED
844 set, and finally removes the TREE_VISITED marks it has set.
846 The algorithm works only at the function level, i.e. it generates a GENERIC
847 representation of a function with no nodes shared within the function when
848 passed a GENERIC function (except for nodes that are allowed to be shared).
850 At the global level, it is also necessary to unshare tree nodes that are
851 referenced in more than one function, for the same aforementioned reason.
852 This requires some cooperation from the front-end. There are 2 strategies:
854 1. Manual unsharing. The front-end needs to call unshare_expr on every
855 expression that might end up being shared across functions.
857 2. Deep unsharing. This is an extension of regular unsharing. Instead
858 of calling unshare_expr on expressions that might be shared across
859 functions, the front-end pre-marks them with TREE_VISITED. This will
860 ensure that they are unshared on the first reference within functions
861 when the regular unsharing algorithm runs. The counterpart is that
862 this algorithm must look deeper than for manual unsharing, which is
863 specified by LANG_HOOKS_DEEP_UNSHARING.
865 If there are only few specific cases of node sharing across functions, it is
866 probably easier for a front-end to unshare the expressions manually. On the
867 contrary, if the expressions generated at the global level are as widespread
868 as expressions generated within functions, deep unsharing is very likely the
869 way to go. */
871 /* Similar to copy_tree_r but do not copy SAVE_EXPR or TARGET_EXPR nodes.
872 These nodes model computations that must be done once. If we were to
873 unshare something like SAVE_EXPR(i++), the gimplification process would
874 create wrong code. However, if DATA is non-null, it must hold a pointer
875 set that is used to unshare the subtrees of these nodes. */
877 static tree
878 mostly_copy_tree_r (tree *tp, int *walk_subtrees, void *data)
880 tree t = *tp;
881 enum tree_code code = TREE_CODE (t);
883 /* Do not copy SAVE_EXPR, TARGET_EXPR or BIND_EXPR nodes themselves, but
884 copy their subtrees if we can make sure to do it only once. */
885 if (code == SAVE_EXPR || code == TARGET_EXPR || code == BIND_EXPR)
887 if (data && !((hash_set<tree> *)data)->add (t))
889 else
890 *walk_subtrees = 0;
893 /* Stop at types, decls, constants like copy_tree_r. */
894 else if (TREE_CODE_CLASS (code) == tcc_type
895 || TREE_CODE_CLASS (code) == tcc_declaration
896 || TREE_CODE_CLASS (code) == tcc_constant)
897 *walk_subtrees = 0;
899 /* Cope with the statement expression extension. */
900 else if (code == STATEMENT_LIST)
903 /* Leave the bulk of the work to copy_tree_r itself. */
904 else
905 copy_tree_r (tp, walk_subtrees, NULL);
907 return NULL_TREE;
910 /* Callback for walk_tree to unshare most of the shared trees rooted at *TP.
911 If *TP has been visited already, then *TP is deeply copied by calling
912 mostly_copy_tree_r. DATA is passed to mostly_copy_tree_r unmodified. */
914 static tree
915 copy_if_shared_r (tree *tp, int *walk_subtrees, void *data)
917 tree t = *tp;
918 enum tree_code code = TREE_CODE (t);
920 /* Skip types, decls, and constants. But we do want to look at their
921 types and the bounds of types. Mark them as visited so we properly
922 unmark their subtrees on the unmark pass. If we've already seen them,
923 don't look down further. */
924 if (TREE_CODE_CLASS (code) == tcc_type
925 || TREE_CODE_CLASS (code) == tcc_declaration
926 || TREE_CODE_CLASS (code) == tcc_constant)
928 if (TREE_VISITED (t))
929 *walk_subtrees = 0;
930 else
931 TREE_VISITED (t) = 1;
934 /* If this node has been visited already, unshare it and don't look
935 any deeper. */
936 else if (TREE_VISITED (t))
938 walk_tree (tp, mostly_copy_tree_r, data, NULL);
939 *walk_subtrees = 0;
942 /* Otherwise, mark the node as visited and keep looking. */
943 else
944 TREE_VISITED (t) = 1;
946 return NULL_TREE;
949 /* Unshare most of the shared trees rooted at *TP. DATA is passed to the
950 copy_if_shared_r callback unmodified. */
952 void
953 copy_if_shared (tree *tp, void *data)
955 walk_tree (tp, copy_if_shared_r, data, NULL);
958 /* Unshare all the trees in the body of FNDECL, as well as in the bodies of
959 any nested functions. */
961 static void
962 unshare_body (tree fndecl)
964 struct cgraph_node *cgn = cgraph_node::get (fndecl);
965 /* If the language requires deep unsharing, we need a pointer set to make
966 sure we don't repeatedly unshare subtrees of unshareable nodes. */
967 hash_set<tree> *visited
968 = lang_hooks.deep_unsharing ? new hash_set<tree> : NULL;
970 copy_if_shared (&DECL_SAVED_TREE (fndecl), visited);
971 copy_if_shared (&DECL_SIZE (DECL_RESULT (fndecl)), visited);
972 copy_if_shared (&DECL_SIZE_UNIT (DECL_RESULT (fndecl)), visited);
974 delete visited;
976 if (cgn)
977 for (cgn = first_nested_function (cgn); cgn;
978 cgn = next_nested_function (cgn))
979 unshare_body (cgn->decl);
982 /* Callback for walk_tree to unmark the visited trees rooted at *TP.
983 Subtrees are walked until the first unvisited node is encountered. */
985 static tree
986 unmark_visited_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
988 tree t = *tp;
990 /* If this node has been visited, unmark it and keep looking. */
991 if (TREE_VISITED (t))
992 TREE_VISITED (t) = 0;
994 /* Otherwise, don't look any deeper. */
995 else
996 *walk_subtrees = 0;
998 return NULL_TREE;
1001 /* Unmark the visited trees rooted at *TP. */
1003 static inline void
1004 unmark_visited (tree *tp)
1006 walk_tree (tp, unmark_visited_r, NULL, NULL);
1009 /* Likewise, but mark all trees as not visited. */
1011 static void
1012 unvisit_body (tree fndecl)
1014 struct cgraph_node *cgn = cgraph_node::get (fndecl);
1016 unmark_visited (&DECL_SAVED_TREE (fndecl));
1017 unmark_visited (&DECL_SIZE (DECL_RESULT (fndecl)));
1018 unmark_visited (&DECL_SIZE_UNIT (DECL_RESULT (fndecl)));
1020 if (cgn)
1021 for (cgn = first_nested_function (cgn);
1022 cgn; cgn = next_nested_function (cgn))
1023 unvisit_body (cgn->decl);
1026 /* Unconditionally make an unshared copy of EXPR. This is used when using
1027 stored expressions which span multiple functions, such as BINFO_VTABLE,
1028 as the normal unsharing process can't tell that they're shared. */
1030 tree
1031 unshare_expr (tree expr)
1033 walk_tree (&expr, mostly_copy_tree_r, NULL, NULL);
1034 return expr;
1037 /* Worker for unshare_expr_without_location. */
1039 static tree
1040 prune_expr_location (tree *tp, int *walk_subtrees, void *)
1042 if (EXPR_P (*tp))
1043 SET_EXPR_LOCATION (*tp, UNKNOWN_LOCATION);
1044 else
1045 *walk_subtrees = 0;
1046 return NULL_TREE;
1049 /* Similar to unshare_expr but also prune all expression locations
1050 from EXPR. */
1052 tree
1053 unshare_expr_without_location (tree expr)
1055 walk_tree (&expr, mostly_copy_tree_r, NULL, NULL);
1056 if (EXPR_P (expr))
1057 walk_tree (&expr, prune_expr_location, NULL, NULL);
1058 return expr;
1061 /* Return the EXPR_LOCATION of EXPR, if it (maybe recursively) has
1062 one, OR_ELSE otherwise. The location of a STATEMENT_LISTs
1063 comprising at least one DEBUG_BEGIN_STMT followed by exactly one
1064 EXPR is the location of the EXPR. */
1066 static location_t
1067 rexpr_location (tree expr, location_t or_else = UNKNOWN_LOCATION)
1069 if (!expr)
1070 return or_else;
1072 if (EXPR_HAS_LOCATION (expr))
1073 return EXPR_LOCATION (expr);
1075 if (TREE_CODE (expr) != STATEMENT_LIST)
1076 return or_else;
1078 tree_stmt_iterator i = tsi_start (expr);
1080 bool found = false;
1081 while (!tsi_end_p (i) && TREE_CODE (tsi_stmt (i)) == DEBUG_BEGIN_STMT)
1083 found = true;
1084 tsi_next (&i);
1087 if (!found || !tsi_one_before_end_p (i))
1088 return or_else;
1090 return rexpr_location (tsi_stmt (i), or_else);
1093 /* Return TRUE iff EXPR (maybe recursively) has a location; see
1094 rexpr_location for the potential recursion. */
1096 static inline bool
1097 rexpr_has_location (tree expr)
1099 return rexpr_location (expr) != UNKNOWN_LOCATION;
1103 /* WRAPPER is a code such as BIND_EXPR or CLEANUP_POINT_EXPR which can both
1104 contain statements and have a value. Assign its value to a temporary
1105 and give it void_type_node. Return the temporary, or NULL_TREE if
1106 WRAPPER was already void. */
1108 tree
1109 voidify_wrapper_expr (tree wrapper, tree temp)
1111 tree type = TREE_TYPE (wrapper);
1112 if (type && !VOID_TYPE_P (type))
1114 tree *p;
1116 /* Set p to point to the body of the wrapper. Loop until we find
1117 something that isn't a wrapper. */
1118 for (p = &wrapper; p && *p; )
1120 switch (TREE_CODE (*p))
1122 case BIND_EXPR:
1123 TREE_SIDE_EFFECTS (*p) = 1;
1124 TREE_TYPE (*p) = void_type_node;
1125 /* For a BIND_EXPR, the body is operand 1. */
1126 p = &BIND_EXPR_BODY (*p);
1127 break;
1129 case CLEANUP_POINT_EXPR:
1130 case TRY_FINALLY_EXPR:
1131 case TRY_CATCH_EXPR:
1132 TREE_SIDE_EFFECTS (*p) = 1;
1133 TREE_TYPE (*p) = void_type_node;
1134 p = &TREE_OPERAND (*p, 0);
1135 break;
1137 case STATEMENT_LIST:
1139 tree_stmt_iterator i = tsi_last (*p);
1140 TREE_SIDE_EFFECTS (*p) = 1;
1141 TREE_TYPE (*p) = void_type_node;
1142 p = tsi_end_p (i) ? NULL : tsi_stmt_ptr (i);
1144 break;
1146 case COMPOUND_EXPR:
1147 /* Advance to the last statement. Set all container types to
1148 void. */
1149 for (; TREE_CODE (*p) == COMPOUND_EXPR; p = &TREE_OPERAND (*p, 1))
1151 TREE_SIDE_EFFECTS (*p) = 1;
1152 TREE_TYPE (*p) = void_type_node;
1154 break;
1156 case TRANSACTION_EXPR:
1157 TREE_SIDE_EFFECTS (*p) = 1;
1158 TREE_TYPE (*p) = void_type_node;
1159 p = &TRANSACTION_EXPR_BODY (*p);
1160 break;
1162 default:
1163 /* Assume that any tree upon which voidify_wrapper_expr is
1164 directly called is a wrapper, and that its body is op0. */
1165 if (p == &wrapper)
1167 TREE_SIDE_EFFECTS (*p) = 1;
1168 TREE_TYPE (*p) = void_type_node;
1169 p = &TREE_OPERAND (*p, 0);
1170 break;
1172 goto out;
1176 out:
1177 if (p == NULL || IS_EMPTY_STMT (*p))
1178 temp = NULL_TREE;
1179 else if (temp)
1181 /* The wrapper is on the RHS of an assignment that we're pushing
1182 down. */
1183 gcc_assert (TREE_CODE (temp) == INIT_EXPR
1184 || TREE_CODE (temp) == MODIFY_EXPR);
1185 TREE_OPERAND (temp, 1) = *p;
1186 *p = temp;
1188 else
1190 temp = create_tmp_var (type, "retval");
1191 *p = build2 (INIT_EXPR, type, temp, *p);
1194 return temp;
1197 return NULL_TREE;
1200 /* Prepare calls to builtins to SAVE and RESTORE the stack as well as
1201 a temporary through which they communicate. */
1203 static void
1204 build_stack_save_restore (gcall **save, gcall **restore)
1206 tree tmp_var;
1208 *save = gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_SAVE), 0);
1209 tmp_var = create_tmp_var (ptr_type_node, "saved_stack");
1210 gimple_call_set_lhs (*save, tmp_var);
1212 *restore
1213 = gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_RESTORE),
1214 1, tmp_var);
1217 /* Generate IFN_ASAN_MARK call that poisons shadow of a for DECL variable. */
1219 static tree
1220 build_asan_poison_call_expr (tree decl)
1222 /* Do not poison variables that have size equal to zero. */
1223 tree unit_size = DECL_SIZE_UNIT (decl);
1224 if (zerop (unit_size))
1225 return NULL_TREE;
1227 tree base = build_fold_addr_expr (decl);
1229 return build_call_expr_internal_loc (UNKNOWN_LOCATION, IFN_ASAN_MARK,
1230 void_type_node, 3,
1231 build_int_cst (integer_type_node,
1232 ASAN_MARK_POISON),
1233 base, unit_size);
1236 /* Generate IFN_ASAN_MARK call that would poison or unpoison, depending
1237 on POISON flag, shadow memory of a DECL variable. The call will be
1238 put on location identified by IT iterator, where BEFORE flag drives
1239 position where the stmt will be put. */
1241 static void
1242 asan_poison_variable (tree decl, bool poison, gimple_stmt_iterator *it,
1243 bool before)
1245 tree unit_size = DECL_SIZE_UNIT (decl);
1246 tree base = build_fold_addr_expr (decl);
1248 /* Do not poison variables that have size equal to zero. */
1249 if (zerop (unit_size))
1250 return;
1252 /* It's necessary to have all stack variables aligned to ASAN granularity
1253 bytes. */
1254 gcc_assert (!hwasan_sanitize_p () || hwasan_sanitize_stack_p ());
1255 unsigned shadow_granularity
1256 = hwasan_sanitize_p () ? HWASAN_TAG_GRANULE_SIZE : ASAN_SHADOW_GRANULARITY;
1257 if (DECL_ALIGN_UNIT (decl) <= shadow_granularity)
1258 SET_DECL_ALIGN (decl, BITS_PER_UNIT * shadow_granularity);
1260 HOST_WIDE_INT flags = poison ? ASAN_MARK_POISON : ASAN_MARK_UNPOISON;
1262 gimple *g
1263 = gimple_build_call_internal (IFN_ASAN_MARK, 3,
1264 build_int_cst (integer_type_node, flags),
1265 base, unit_size);
1267 if (before)
1268 gsi_insert_before (it, g, GSI_NEW_STMT);
1269 else
1270 gsi_insert_after (it, g, GSI_NEW_STMT);
1273 /* Generate IFN_ASAN_MARK internal call that depending on POISON flag
1274 either poisons or unpoisons a DECL. Created statement is appended
1275 to SEQ_P gimple sequence. */
1277 static void
1278 asan_poison_variable (tree decl, bool poison, gimple_seq *seq_p)
1280 gimple_stmt_iterator it = gsi_last (*seq_p);
1281 bool before = false;
1283 if (gsi_end_p (it))
1284 before = true;
1286 asan_poison_variable (decl, poison, &it, before);
1289 /* Sort pair of VAR_DECLs A and B by DECL_UID. */
1291 static int
1292 sort_by_decl_uid (const void *a, const void *b)
1294 const tree *t1 = (const tree *)a;
1295 const tree *t2 = (const tree *)b;
1297 int uid1 = DECL_UID (*t1);
1298 int uid2 = DECL_UID (*t2);
1300 if (uid1 < uid2)
1301 return -1;
1302 else if (uid1 > uid2)
1303 return 1;
1304 else
1305 return 0;
1308 /* Generate IFN_ASAN_MARK internal call for all VARIABLES
1309 depending on POISON flag. Created statement is appended
1310 to SEQ_P gimple sequence. */
1312 static void
1313 asan_poison_variables (hash_set<tree> *variables, bool poison, gimple_seq *seq_p)
1315 unsigned c = variables->elements ();
1316 if (c == 0)
1317 return;
1319 auto_vec<tree> sorted_variables (c);
1321 for (hash_set<tree>::iterator it = variables->begin ();
1322 it != variables->end (); ++it)
1323 sorted_variables.safe_push (*it);
1325 sorted_variables.qsort (sort_by_decl_uid);
1327 unsigned i;
1328 tree var;
1329 FOR_EACH_VEC_ELT (sorted_variables, i, var)
1331 asan_poison_variable (var, poison, seq_p);
1333 /* Add use_after_scope_memory attribute for the variable in order
1334 to prevent re-written into SSA. */
1335 if (!lookup_attribute (ASAN_USE_AFTER_SCOPE_ATTRIBUTE,
1336 DECL_ATTRIBUTES (var)))
1337 DECL_ATTRIBUTES (var)
1338 = tree_cons (get_identifier (ASAN_USE_AFTER_SCOPE_ATTRIBUTE),
1339 integer_one_node,
1340 DECL_ATTRIBUTES (var));
1344 /* Gimplify a BIND_EXPR. Just voidify and recurse. */
1346 static enum gimplify_status
1347 gimplify_bind_expr (tree *expr_p, gimple_seq *pre_p)
1349 tree bind_expr = *expr_p;
1350 bool old_keep_stack = gimplify_ctxp->keep_stack;
1351 bool old_save_stack = gimplify_ctxp->save_stack;
1352 tree t;
1353 gbind *bind_stmt;
1354 gimple_seq body, cleanup;
1355 gcall *stack_save;
1356 location_t start_locus = 0, end_locus = 0;
1357 tree ret_clauses = NULL;
1359 tree temp = voidify_wrapper_expr (bind_expr, NULL);
1361 /* Mark variables seen in this bind expr. */
1362 for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
1364 if (VAR_P (t))
1366 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
1367 tree attr;
1369 if (flag_openmp
1370 && !is_global_var (t)
1371 && DECL_CONTEXT (t) == current_function_decl
1372 && TREE_USED (t)
1373 && (attr = lookup_attribute ("omp allocate", DECL_ATTRIBUTES (t)))
1374 != NULL_TREE)
1376 gcc_assert (!DECL_HAS_VALUE_EXPR_P (t));
1377 tree alloc = TREE_PURPOSE (TREE_VALUE (attr));
1378 tree align = TREE_VALUE (TREE_VALUE (attr));
1379 /* Allocate directives that appear in a target region must specify
1380 an allocator clause unless a requires directive with the
1381 dynamic_allocators clause is present in the same compilation
1382 unit. */
1383 bool missing_dyn_alloc = false;
1384 if (alloc == NULL_TREE
1385 && ((omp_requires_mask & OMP_REQUIRES_DYNAMIC_ALLOCATORS)
1386 == 0))
1388 /* This comes too early for omp_discover_declare_target...,
1389 but should at least catch the most common cases. */
1390 missing_dyn_alloc
1391 = cgraph_node::get (current_function_decl)->offloadable;
1392 for (struct gimplify_omp_ctx *ctx2 = ctx;
1393 ctx2 && !missing_dyn_alloc; ctx2 = ctx2->outer_context)
1394 if (ctx2->code == OMP_TARGET)
1395 missing_dyn_alloc = true;
1397 if (missing_dyn_alloc)
1398 error_at (DECL_SOURCE_LOCATION (t),
1399 "%<allocate%> directive for %qD inside a target "
1400 "region must specify an %<allocator%> clause", t);
1401 /* Skip for omp_default_mem_alloc (= 1),
1402 unless align is present. */
1403 else if (!errorcount
1404 && (align != NULL_TREE
1405 || alloc == NULL_TREE
1406 || !integer_onep (alloc)))
1408 /* Fortran might already use a pointer type internally;
1409 use that pointer except for type(C_ptr) and type(C_funptr);
1410 note that normal proc pointers are rejected. */
1411 tree type = TREE_TYPE (t);
1412 tree tmp, v;
1413 if (lang_GNU_Fortran ()
1414 && POINTER_TYPE_P (type)
1415 && TREE_TYPE (type) != void_type_node
1416 && TREE_CODE (TREE_TYPE (type)) != FUNCTION_TYPE)
1418 type = TREE_TYPE (type);
1419 v = t;
1421 else
1423 tmp = build_pointer_type (type);
1424 v = create_tmp_var (tmp, get_name (t));
1425 DECL_IGNORED_P (v) = 0;
1426 DECL_ATTRIBUTES (v)
1427 = tree_cons (get_identifier ("omp allocate var"),
1428 build_tree_list (NULL_TREE, t),
1429 remove_attribute ("omp allocate",
1430 DECL_ATTRIBUTES (t)));
1431 tmp = build_fold_indirect_ref (v);
1432 TREE_THIS_NOTRAP (tmp) = 1;
1433 SET_DECL_VALUE_EXPR (t, tmp);
1434 DECL_HAS_VALUE_EXPR_P (t) = 1;
1436 tree sz = TYPE_SIZE_UNIT (type);
1437 /* The size to use in Fortran might not match TYPE_SIZE_UNIT;
1438 hence, for some decls, a size variable is saved in the
1439 attributes; use it, if available. */
1440 if (TREE_CHAIN (TREE_VALUE (attr))
1441 && TREE_CHAIN (TREE_CHAIN (TREE_VALUE (attr)))
1442 && TREE_PURPOSE (
1443 TREE_CHAIN (TREE_CHAIN (TREE_VALUE (attr)))))
1445 sz = TREE_CHAIN (TREE_CHAIN (TREE_VALUE (attr)));
1446 sz = TREE_PURPOSE (sz);
1448 if (alloc == NULL_TREE)
1449 alloc = build_zero_cst (ptr_type_node);
1450 if (align == NULL_TREE)
1451 align = build_int_cst (size_type_node, DECL_ALIGN_UNIT (t));
1452 else
1453 align = build_int_cst (size_type_node,
1454 MAX (tree_to_uhwi (align),
1455 DECL_ALIGN_UNIT (t)));
1456 location_t loc = DECL_SOURCE_LOCATION (t);
1457 tmp = builtin_decl_explicit (BUILT_IN_GOMP_ALLOC);
1458 tmp = build_call_expr_loc (loc, tmp, 3, align, sz, alloc);
1459 tmp = fold_build2_loc (loc, MODIFY_EXPR, TREE_TYPE (v), v,
1460 fold_convert (TREE_TYPE (v), tmp));
1461 gcc_assert (BIND_EXPR_BODY (bind_expr) != NULL_TREE);
1462 /* Ensure that either TREE_CHAIN (TREE_VALUE (attr) is set
1463 and GOMP_FREE added here or that DECL_HAS_VALUE_EXPR_P (t)
1464 is set, using in a condition much further below. */
1465 gcc_assert (DECL_HAS_VALUE_EXPR_P (t)
1466 || TREE_CHAIN (TREE_VALUE (attr)));
1467 if (TREE_CHAIN (TREE_VALUE (attr)))
1469 /* Fortran is special as it does not have properly nest
1470 declarations in blocks. And as there is no
1471 initializer, there is also no expression to look for.
1472 Hence, the FE makes the statement list of the
1473 try-finally block available. We can put the GOMP_alloc
1474 at the top, unless an allocator or size expression
1475 requires to put it afterward; note that the size is
1476 always later in generated code; for strings, no
1477 size expr but still an expr might be available.
1478 As LTO does not handle a statement list, 'sl' has
1479 to be removed; done so by removing the attribute. */
1480 DECL_ATTRIBUTES (t)
1481 = remove_attribute ("omp allocate",
1482 DECL_ATTRIBUTES (t));
1483 tree sl = TREE_PURPOSE (TREE_CHAIN (TREE_VALUE (attr)));
1484 tree_stmt_iterator e = tsi_start (sl);
1485 tree needle = NULL_TREE;
1486 if (TREE_CHAIN (TREE_CHAIN (TREE_VALUE (attr))))
1488 needle = TREE_CHAIN (TREE_CHAIN (TREE_VALUE (attr)));
1489 needle = (TREE_VALUE (needle) ? TREE_VALUE (needle)
1490 : sz);
1492 else if (TREE_CHAIN (TREE_CHAIN (TREE_VALUE (attr))))
1493 needle = sz;
1494 else if (DECL_P (alloc) && DECL_ARTIFICIAL (alloc))
1495 needle = alloc;
1497 if (needle != NULL_TREE)
1499 while (!tsi_end_p (e))
1501 if (*e == needle
1502 || (TREE_CODE (*e) == MODIFY_EXPR
1503 && TREE_OPERAND (*e, 0) == needle))
1504 break;
1505 ++e;
1507 gcc_assert (!tsi_end_p (e));
1509 tsi_link_after (&e, tmp, TSI_SAME_STMT);
1511 /* As the cleanup is in BIND_EXPR_BODY, GOMP_free is added
1512 here; for C/C++ it will be added in the 'cleanup'
1513 section after gimplification. But Fortran already has
1514 a try-finally block. */
1515 sl = TREE_VALUE (TREE_CHAIN (TREE_VALUE (attr)));
1516 e = tsi_last (sl);
1517 tmp = builtin_decl_explicit (BUILT_IN_GOMP_FREE);
1518 tmp = build_call_expr_loc (EXPR_LOCATION (*e), tmp, 2, v,
1519 build_zero_cst (ptr_type_node));
1520 tsi_link_after (&e, tmp, TSI_SAME_STMT);
1521 tmp = build_clobber (TREE_TYPE (v), CLOBBER_EOL);
1522 tmp = fold_build2_loc (loc, MODIFY_EXPR, TREE_TYPE (v), v,
1523 fold_convert (TREE_TYPE (v), tmp));
1524 ++e;
1525 tsi_link_after (&e, tmp, TSI_SAME_STMT);
1527 else
1529 gcc_assert (TREE_CODE (BIND_EXPR_BODY (bind_expr))
1530 == STATEMENT_LIST);
1531 tree_stmt_iterator e;
1532 e = tsi_start (BIND_EXPR_BODY (bind_expr));
1533 while (!tsi_end_p (e))
1535 if ((TREE_CODE (*e) == DECL_EXPR
1536 && TREE_OPERAND (*e, 0) == t)
1537 || (TREE_CODE (*e) == CLEANUP_POINT_EXPR
1538 && (TREE_CODE (TREE_OPERAND (*e, 0))
1539 == DECL_EXPR)
1540 && (TREE_OPERAND (TREE_OPERAND (*e, 0), 0)
1541 == t)))
1542 break;
1543 ++e;
1545 gcc_assert (!tsi_end_p (e));
1546 tsi_link_before (&e, tmp, TSI_SAME_STMT);
1551 /* Mark variable as local. */
1552 if (ctx && ctx->region_type != ORT_NONE && !DECL_EXTERNAL (t))
1554 if (! DECL_SEEN_IN_BIND_EXPR_P (t)
1555 || splay_tree_lookup (ctx->variables,
1556 (splay_tree_key) t) == NULL)
1558 int flag = GOVD_LOCAL;
1559 if (ctx->region_type == ORT_SIMD
1560 && TREE_ADDRESSABLE (t)
1561 && !TREE_STATIC (t))
1563 if (TREE_CODE (DECL_SIZE_UNIT (t)) != INTEGER_CST)
1564 ctx->add_safelen1 = true;
1565 else
1566 flag = GOVD_PRIVATE;
1568 omp_add_variable (ctx, t, flag | GOVD_SEEN);
1570 /* Static locals inside of target construct or offloaded
1571 routines need to be "omp declare target". */
1572 if (TREE_STATIC (t))
1573 for (; ctx; ctx = ctx->outer_context)
1574 if ((ctx->region_type & ORT_TARGET) != 0)
1576 if (!lookup_attribute ("omp declare target",
1577 DECL_ATTRIBUTES (t)))
1579 tree id = get_identifier ("omp declare target");
1580 DECL_ATTRIBUTES (t)
1581 = tree_cons (id, NULL_TREE, DECL_ATTRIBUTES (t));
1582 varpool_node *node = varpool_node::get (t);
1583 if (node)
1585 node->offloadable = 1;
1586 if (ENABLE_OFFLOADING && !DECL_EXTERNAL (t))
1588 g->have_offload = true;
1589 if (!in_lto_p)
1590 vec_safe_push (offload_vars, t);
1594 break;
1598 DECL_SEEN_IN_BIND_EXPR_P (t) = 1;
1600 if (DECL_HARD_REGISTER (t) && !is_global_var (t) && cfun)
1601 cfun->has_local_explicit_reg_vars = true;
1605 bind_stmt = gimple_build_bind (BIND_EXPR_VARS (bind_expr), NULL,
1606 BIND_EXPR_BLOCK (bind_expr));
1607 gimple_push_bind_expr (bind_stmt);
1609 gimplify_ctxp->keep_stack = false;
1610 gimplify_ctxp->save_stack = false;
1612 /* Gimplify the body into the GIMPLE_BIND tuple's body. */
1613 body = NULL;
1614 gimplify_stmt (&BIND_EXPR_BODY (bind_expr), &body);
1615 gimple_bind_set_body (bind_stmt, body);
1617 /* Source location wise, the cleanup code (stack_restore and clobbers)
1618 belongs to the end of the block, so propagate what we have. The
1619 stack_save operation belongs to the beginning of block, which we can
1620 infer from the bind_expr directly if the block has no explicit
1621 assignment. */
1622 if (BIND_EXPR_BLOCK (bind_expr))
1624 end_locus = BLOCK_SOURCE_END_LOCATION (BIND_EXPR_BLOCK (bind_expr));
1625 start_locus = BLOCK_SOURCE_LOCATION (BIND_EXPR_BLOCK (bind_expr));
1627 if (start_locus == 0)
1628 start_locus = EXPR_LOCATION (bind_expr);
1630 cleanup = NULL;
1631 stack_save = NULL;
1633 /* Add clobbers for all variables that go out of scope. */
1634 for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
1636 if (VAR_P (t)
1637 && !is_global_var (t)
1638 && DECL_CONTEXT (t) == current_function_decl)
1640 if (flag_openmp
1641 && DECL_HAS_VALUE_EXPR_P (t)
1642 && TREE_USED (t)
1643 && lookup_attribute ("omp allocate", DECL_ATTRIBUTES (t)))
1645 /* For Fortran, TREE_CHAIN (TREE_VALUE (attr)) is set, which
1646 causes that the GOMP_free call is already added above;
1647 and "omp allocate" is removed from DECL_ATTRIBUTES. */
1648 tree v = TREE_OPERAND (DECL_VALUE_EXPR (t), 0);
1649 tree tmp = builtin_decl_explicit (BUILT_IN_GOMP_FREE);
1650 tmp = build_call_expr_loc (end_locus, tmp, 2, v,
1651 build_zero_cst (ptr_type_node));
1652 gimplify_and_add (tmp, &cleanup);
1653 gimple *clobber_stmt;
1654 tmp = build_clobber (TREE_TYPE (v), CLOBBER_EOL);
1655 clobber_stmt = gimple_build_assign (v, tmp);
1656 gimple_set_location (clobber_stmt, end_locus);
1657 gimplify_seq_add_stmt (&cleanup, clobber_stmt);
1659 if (!DECL_HARD_REGISTER (t)
1660 && !TREE_THIS_VOLATILE (t)
1661 && !DECL_HAS_VALUE_EXPR_P (t)
1662 /* Only care for variables that have to be in memory. Others
1663 will be rewritten into SSA names, hence moved to the
1664 top-level. */
1665 && !is_gimple_reg (t)
1666 && flag_stack_reuse != SR_NONE)
1668 tree clobber = build_clobber (TREE_TYPE (t), CLOBBER_EOL);
1669 gimple *clobber_stmt;
1670 clobber_stmt = gimple_build_assign (t, clobber);
1671 gimple_set_location (clobber_stmt, end_locus);
1672 gimplify_seq_add_stmt (&cleanup, clobber_stmt);
1675 if (flag_openacc && oacc_declare_returns != NULL)
1677 tree key = t;
1678 if (DECL_HAS_VALUE_EXPR_P (key))
1680 key = DECL_VALUE_EXPR (key);
1681 if (INDIRECT_REF_P (key))
1682 key = TREE_OPERAND (key, 0);
1684 tree *c = oacc_declare_returns->get (key);
1685 if (c != NULL)
1687 if (ret_clauses)
1688 OMP_CLAUSE_CHAIN (*c) = ret_clauses;
1690 ret_clauses = unshare_expr (*c);
1692 oacc_declare_returns->remove (key);
1694 if (oacc_declare_returns->is_empty ())
1696 delete oacc_declare_returns;
1697 oacc_declare_returns = NULL;
1703 if (asan_poisoned_variables != NULL
1704 && asan_poisoned_variables->contains (t))
1706 asan_poisoned_variables->remove (t);
1707 asan_poison_variable (t, true, &cleanup);
1710 if (gimplify_ctxp->live_switch_vars != NULL
1711 && gimplify_ctxp->live_switch_vars->contains (t))
1712 gimplify_ctxp->live_switch_vars->remove (t);
1715 /* If the code both contains VLAs and calls alloca, then we cannot reclaim
1716 the stack space allocated to the VLAs. */
1717 if (gimplify_ctxp->save_stack && !gimplify_ctxp->keep_stack)
1719 gcall *stack_restore;
1721 /* Save stack on entry and restore it on exit. Add a try_finally
1722 block to achieve this. */
1723 build_stack_save_restore (&stack_save, &stack_restore);
1725 gimple_set_location (stack_save, start_locus);
1726 gimple_set_location (stack_restore, end_locus);
1728 gimplify_seq_add_stmt (&cleanup, stack_restore);
1731 if (ret_clauses)
1733 gomp_target *stmt;
1734 gimple_stmt_iterator si = gsi_start (cleanup);
1736 stmt = gimple_build_omp_target (NULL, GF_OMP_TARGET_KIND_OACC_DECLARE,
1737 ret_clauses);
1738 gsi_insert_seq_before_without_update (&si, stmt, GSI_NEW_STMT);
1741 if (cleanup)
1743 gtry *gs;
1744 gimple_seq new_body;
1746 new_body = NULL;
1747 gs = gimple_build_try (gimple_bind_body (bind_stmt), cleanup,
1748 GIMPLE_TRY_FINALLY);
1750 if (stack_save)
1751 gimplify_seq_add_stmt (&new_body, stack_save);
1752 gimplify_seq_add_stmt (&new_body, gs);
1753 gimple_bind_set_body (bind_stmt, new_body);
1756 /* keep_stack propagates all the way up to the outermost BIND_EXPR. */
1757 if (!gimplify_ctxp->keep_stack)
1758 gimplify_ctxp->keep_stack = old_keep_stack;
1759 gimplify_ctxp->save_stack = old_save_stack;
1761 gimple_pop_bind_expr ();
1763 gimplify_seq_add_stmt (pre_p, bind_stmt);
1765 if (temp)
1767 *expr_p = temp;
1768 return GS_OK;
1771 *expr_p = NULL_TREE;
1772 return GS_ALL_DONE;
1775 /* Maybe add early return predict statement to PRE_P sequence. */
1777 static void
1778 maybe_add_early_return_predict_stmt (gimple_seq *pre_p)
1780 /* If we are not in a conditional context, add PREDICT statement. */
1781 if (gimple_conditional_context ())
1783 gimple *predict = gimple_build_predict (PRED_TREE_EARLY_RETURN,
1784 NOT_TAKEN);
1785 gimplify_seq_add_stmt (pre_p, predict);
1789 /* Gimplify a RETURN_EXPR. If the expression to be returned is not a
1790 GIMPLE value, it is assigned to a new temporary and the statement is
1791 re-written to return the temporary.
1793 PRE_P points to the sequence where side effects that must happen before
1794 STMT should be stored. */
1796 static enum gimplify_status
1797 gimplify_return_expr (tree stmt, gimple_seq *pre_p)
1799 greturn *ret;
1800 tree ret_expr = TREE_OPERAND (stmt, 0);
1801 tree result_decl, result;
1803 if (ret_expr == error_mark_node)
1804 return GS_ERROR;
1806 if (!ret_expr
1807 || TREE_CODE (ret_expr) == RESULT_DECL)
1809 maybe_add_early_return_predict_stmt (pre_p);
1810 greturn *ret = gimple_build_return (ret_expr);
1811 copy_warning (ret, stmt);
1812 gimplify_seq_add_stmt (pre_p, ret);
1813 return GS_ALL_DONE;
1816 if (VOID_TYPE_P (TREE_TYPE (TREE_TYPE (current_function_decl))))
1817 result_decl = NULL_TREE;
1818 else if (TREE_CODE (ret_expr) == COMPOUND_EXPR)
1820 /* Used in C++ for handling EH cleanup of the return value if a local
1821 cleanup throws. Assume the front-end knows what it's doing. */
1822 result_decl = DECL_RESULT (current_function_decl);
1823 /* But crash if we end up trying to modify ret_expr below. */
1824 ret_expr = NULL_TREE;
1826 else
1828 result_decl = TREE_OPERAND (ret_expr, 0);
1830 /* See through a return by reference. */
1831 if (INDIRECT_REF_P (result_decl))
1832 result_decl = TREE_OPERAND (result_decl, 0);
1834 gcc_assert ((TREE_CODE (ret_expr) == MODIFY_EXPR
1835 || TREE_CODE (ret_expr) == INIT_EXPR)
1836 && TREE_CODE (result_decl) == RESULT_DECL);
1839 /* If aggregate_value_p is true, then we can return the bare RESULT_DECL.
1840 Recall that aggregate_value_p is FALSE for any aggregate type that is
1841 returned in registers. If we're returning values in registers, then
1842 we don't want to extend the lifetime of the RESULT_DECL, particularly
1843 across another call. In addition, for those aggregates for which
1844 hard_function_value generates a PARALLEL, we'll die during normal
1845 expansion of structure assignments; there's special code in expand_return
1846 to handle this case that does not exist in expand_expr. */
1847 if (!result_decl)
1848 result = NULL_TREE;
1849 else if (aggregate_value_p (result_decl, TREE_TYPE (current_function_decl)))
1851 if (!poly_int_tree_p (DECL_SIZE (result_decl)))
1853 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (result_decl)))
1854 gimplify_type_sizes (TREE_TYPE (result_decl), pre_p);
1855 /* Note that we don't use gimplify_vla_decl because the RESULT_DECL
1856 should be effectively allocated by the caller, i.e. all calls to
1857 this function must be subject to the Return Slot Optimization. */
1858 gimplify_one_sizepos (&DECL_SIZE (result_decl), pre_p);
1859 gimplify_one_sizepos (&DECL_SIZE_UNIT (result_decl), pre_p);
1861 result = result_decl;
1863 else if (gimplify_ctxp->return_temp)
1864 result = gimplify_ctxp->return_temp;
1865 else
1867 result = create_tmp_reg (TREE_TYPE (result_decl));
1869 /* ??? With complex control flow (usually involving abnormal edges),
1870 we can wind up warning about an uninitialized value for this. Due
1871 to how this variable is constructed and initialized, this is never
1872 true. Give up and never warn. */
1873 suppress_warning (result, OPT_Wuninitialized);
1875 gimplify_ctxp->return_temp = result;
1878 /* Smash the lhs of the MODIFY_EXPR to the temporary we plan to use.
1879 Then gimplify the whole thing. */
1880 if (result != result_decl)
1881 TREE_OPERAND (ret_expr, 0) = result;
1883 gimplify_and_add (TREE_OPERAND (stmt, 0), pre_p);
1885 maybe_add_early_return_predict_stmt (pre_p);
1886 ret = gimple_build_return (result);
1887 copy_warning (ret, stmt);
1888 gimplify_seq_add_stmt (pre_p, ret);
1890 return GS_ALL_DONE;
1893 /* Gimplify a variable-length array DECL. */
1895 static void
1896 gimplify_vla_decl (tree decl, gimple_seq *seq_p)
1898 /* This is a variable-sized decl. Simplify its size and mark it
1899 for deferred expansion. */
1900 tree t, addr, ptr_type;
1902 gimplify_one_sizepos (&DECL_SIZE (decl), seq_p);
1903 gimplify_one_sizepos (&DECL_SIZE_UNIT (decl), seq_p);
1905 /* Don't mess with a DECL_VALUE_EXPR set by the front-end. */
1906 if (DECL_HAS_VALUE_EXPR_P (decl))
1907 return;
1909 /* All occurrences of this decl in final gimplified code will be
1910 replaced by indirection. Setting DECL_VALUE_EXPR does two
1911 things: First, it lets the rest of the gimplifier know what
1912 replacement to use. Second, it lets the debug info know
1913 where to find the value. */
1914 ptr_type = build_pointer_type (TREE_TYPE (decl));
1915 addr = create_tmp_var (ptr_type, get_name (decl));
1916 DECL_IGNORED_P (addr) = 0;
1917 t = build_fold_indirect_ref (addr);
1918 TREE_THIS_NOTRAP (t) = 1;
1919 SET_DECL_VALUE_EXPR (decl, t);
1920 DECL_HAS_VALUE_EXPR_P (decl) = 1;
1922 t = build_alloca_call_expr (DECL_SIZE_UNIT (decl), DECL_ALIGN (decl),
1923 max_int_size_in_bytes (TREE_TYPE (decl)));
1924 /* The call has been built for a variable-sized object. */
1925 CALL_ALLOCA_FOR_VAR_P (t) = 1;
1926 t = fold_convert (ptr_type, t);
1927 t = build2 (MODIFY_EXPR, TREE_TYPE (addr), addr, t);
1929 gimplify_and_add (t, seq_p);
1931 /* Record the dynamic allocation associated with DECL if requested. */
1932 if (flag_callgraph_info & CALLGRAPH_INFO_DYNAMIC_ALLOC)
1933 record_dynamic_alloc (decl);
1936 /* A helper function to be called via walk_tree. Mark all labels under *TP
1937 as being forced. To be called for DECL_INITIAL of static variables. */
1939 static tree
1940 force_labels_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
1942 if (TYPE_P (*tp))
1943 *walk_subtrees = 0;
1944 if (TREE_CODE (*tp) == LABEL_DECL)
1946 FORCED_LABEL (*tp) = 1;
1947 cfun->has_forced_label_in_static = 1;
1950 return NULL_TREE;
1953 /* Generate an initialization to automatic variable DECL based on INIT_TYPE.
1954 Build a call to internal const function DEFERRED_INIT:
1955 1st argument: SIZE of the DECL;
1956 2nd argument: INIT_TYPE;
1957 3rd argument: NAME of the DECL;
1959 as LHS = DEFERRED_INIT (SIZE of the DECL, INIT_TYPE, NAME of the DECL). */
1961 static void
1962 gimple_add_init_for_auto_var (tree decl,
1963 enum auto_init_type init_type,
1964 gimple_seq *seq_p)
1966 gcc_assert (auto_var_p (decl));
1967 gcc_assert (init_type > AUTO_INIT_UNINITIALIZED);
1968 location_t loc = EXPR_LOCATION (decl);
1969 tree decl_size = TYPE_SIZE_UNIT (TREE_TYPE (decl));
1971 tree init_type_node
1972 = build_int_cst (integer_type_node, (int) init_type);
1974 tree decl_name = NULL_TREE;
1975 if (DECL_NAME (decl))
1977 decl_name = build_string_literal (DECL_NAME (decl));
1979 else
1981 char decl_name_anonymous[3 + (HOST_BITS_PER_INT + 2) / 3];
1982 sprintf (decl_name_anonymous, "D.%u", DECL_UID (decl));
1983 decl_name = build_string_literal (decl_name_anonymous);
1986 tree call = build_call_expr_internal_loc (loc, IFN_DEFERRED_INIT,
1987 TREE_TYPE (decl), 3,
1988 decl_size, init_type_node,
1989 decl_name);
1991 gimplify_assign (decl, call, seq_p);
1994 /* Generate padding initialization for automatic vairable DECL.
1995 C guarantees that brace-init with fewer initializers than members
1996 aggregate will initialize the rest of the aggregate as-if it were
1997 static initialization. In turn static initialization guarantees
1998 that padding is initialized to zero. So, we always initialize paddings
1999 to zeroes regardless INIT_TYPE.
2000 To do the padding initialization, we insert a call to
2001 __builtin_clear_padding (&decl, 0, for_auto_init = true).
2002 Note, we add an additional dummy argument for __builtin_clear_padding,
2003 'for_auto_init' to distinguish whether this call is for automatic
2004 variable initialization or not.
2006 static void
2007 gimple_add_padding_init_for_auto_var (tree decl, bool is_vla,
2008 gimple_seq *seq_p)
2010 tree addr_of_decl = NULL_TREE;
2011 tree fn = builtin_decl_explicit (BUILT_IN_CLEAR_PADDING);
2013 if (is_vla)
2015 /* The temporary address variable for this vla should be
2016 created in gimplify_vla_decl. */
2017 gcc_assert (DECL_HAS_VALUE_EXPR_P (decl));
2018 gcc_assert (INDIRECT_REF_P (DECL_VALUE_EXPR (decl)));
2019 addr_of_decl = TREE_OPERAND (DECL_VALUE_EXPR (decl), 0);
2021 else
2023 mark_addressable (decl);
2024 addr_of_decl = build_fold_addr_expr (decl);
2027 gimple *call = gimple_build_call (fn, 2, addr_of_decl,
2028 build_one_cst (TREE_TYPE (addr_of_decl)));
2029 gimplify_seq_add_stmt (seq_p, call);
2032 /* Return true if the DECL need to be automaticly initialized by the
2033 compiler. */
2034 static bool
2035 is_var_need_auto_init (tree decl)
2037 if (auto_var_p (decl)
2038 && (TREE_CODE (decl) != VAR_DECL
2039 || !DECL_HARD_REGISTER (decl))
2040 && (flag_auto_var_init > AUTO_INIT_UNINITIALIZED)
2041 && (!lookup_attribute ("uninitialized", DECL_ATTRIBUTES (decl)))
2042 && !OPAQUE_TYPE_P (TREE_TYPE (decl))
2043 && !is_empty_type (TREE_TYPE (decl)))
2044 return true;
2045 return false;
2048 /* Gimplify a DECL_EXPR node *STMT_P by making any necessary allocation
2049 and initialization explicit. */
2051 static enum gimplify_status
2052 gimplify_decl_expr (tree *stmt_p, gimple_seq *seq_p)
2054 tree stmt = *stmt_p;
2055 tree decl = DECL_EXPR_DECL (stmt);
2057 *stmt_p = NULL_TREE;
2059 if (TREE_TYPE (decl) == error_mark_node)
2060 return GS_ERROR;
2062 if ((TREE_CODE (decl) == TYPE_DECL
2063 || VAR_P (decl))
2064 && !TYPE_SIZES_GIMPLIFIED (TREE_TYPE (decl)))
2066 gimplify_type_sizes (TREE_TYPE (decl), seq_p);
2067 if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE)
2068 gimplify_type_sizes (TREE_TYPE (TREE_TYPE (decl)), seq_p);
2071 /* ??? DECL_ORIGINAL_TYPE is streamed for LTO so it needs to be gimplified
2072 in case its size expressions contain problematic nodes like CALL_EXPR. */
2073 if (TREE_CODE (decl) == TYPE_DECL
2074 && DECL_ORIGINAL_TYPE (decl)
2075 && !TYPE_SIZES_GIMPLIFIED (DECL_ORIGINAL_TYPE (decl)))
2077 gimplify_type_sizes (DECL_ORIGINAL_TYPE (decl), seq_p);
2078 if (TREE_CODE (DECL_ORIGINAL_TYPE (decl)) == REFERENCE_TYPE)
2079 gimplify_type_sizes (TREE_TYPE (DECL_ORIGINAL_TYPE (decl)), seq_p);
2082 if (VAR_P (decl) && !DECL_EXTERNAL (decl))
2084 tree init = DECL_INITIAL (decl);
2085 bool is_vla = false;
2086 /* Check whether a decl has FE created VALUE_EXPR here BEFORE
2087 gimplify_vla_decl creates VALUE_EXPR for a vla decl.
2088 If the decl has VALUE_EXPR that was created by FE (usually
2089 C++FE), it's a proxy varaible, and FE already initialized
2090 the VALUE_EXPR of it, we should not initialize it anymore. */
2091 bool decl_had_value_expr_p = DECL_HAS_VALUE_EXPR_P (decl);
2093 poly_uint64 size;
2094 if (!poly_int_tree_p (DECL_SIZE_UNIT (decl), &size)
2095 || (!TREE_STATIC (decl)
2096 && flag_stack_check == GENERIC_STACK_CHECK
2097 && maybe_gt (size,
2098 (unsigned HOST_WIDE_INT) STACK_CHECK_MAX_VAR_SIZE)))
2100 gimplify_vla_decl (decl, seq_p);
2101 is_vla = true;
2104 if (asan_poisoned_variables
2105 && !is_vla
2106 && TREE_ADDRESSABLE (decl)
2107 && !TREE_STATIC (decl)
2108 && !DECL_HAS_VALUE_EXPR_P (decl)
2109 && DECL_ALIGN (decl) <= MAX_SUPPORTED_STACK_ALIGNMENT
2110 && dbg_cnt (asan_use_after_scope)
2111 && !gimplify_omp_ctxp
2112 /* GNAT introduces temporaries to hold return values of calls in
2113 initializers of variables defined in other units, so the
2114 declaration of the variable is discarded completely. We do not
2115 want to issue poison calls for such dropped variables. */
2116 && (DECL_SEEN_IN_BIND_EXPR_P (decl)
2117 || (DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)))
2119 asan_poisoned_variables->add (decl);
2120 asan_poison_variable (decl, false, seq_p);
2121 if (!DECL_ARTIFICIAL (decl) && gimplify_ctxp->live_switch_vars)
2122 gimplify_ctxp->live_switch_vars->add (decl);
2125 /* Some front ends do not explicitly declare all anonymous
2126 artificial variables. We compensate here by declaring the
2127 variables, though it would be better if the front ends would
2128 explicitly declare them. */
2129 if (!DECL_SEEN_IN_BIND_EXPR_P (decl)
2130 && DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)
2131 gimple_add_tmp_var (decl);
2133 if (init && init != error_mark_node)
2135 if (!TREE_STATIC (decl))
2137 DECL_INITIAL (decl) = NULL_TREE;
2138 init = build2 (INIT_EXPR, void_type_node, decl, init);
2139 gimplify_and_add (init, seq_p);
2140 ggc_free (init);
2141 /* Clear TREE_READONLY if we really have an initialization. */
2142 if (!DECL_INITIAL (decl)
2143 && !omp_privatize_by_reference (decl))
2144 TREE_READONLY (decl) = 0;
2146 else
2147 /* We must still examine initializers for static variables
2148 as they may contain a label address. */
2149 walk_tree (&init, force_labels_r, NULL, NULL);
2151 /* When there is no explicit initializer, if the user requested,
2152 We should insert an artifical initializer for this automatic
2153 variable. */
2154 else if (is_var_need_auto_init (decl)
2155 && !decl_had_value_expr_p)
2157 gimple_add_init_for_auto_var (decl,
2158 flag_auto_var_init,
2159 seq_p);
2160 /* The expanding of a call to the above .DEFERRED_INIT will apply
2161 block initialization to the whole space covered by this variable.
2162 As a result, all the paddings will be initialized to zeroes
2163 for zero initialization and 0xFE byte-repeatable patterns for
2164 pattern initialization.
2165 In order to make the paddings as zeroes for pattern init, We
2166 should add a call to __builtin_clear_padding to clear the
2167 paddings to zero in compatiple with CLANG.
2168 We cannot insert this call if the variable is a gimple register
2169 since __builtin_clear_padding will take the address of the
2170 variable. As a result, if a long double/_Complex long double
2171 variable will spilled into stack later, its padding is 0XFE. */
2172 if (flag_auto_var_init == AUTO_INIT_PATTERN
2173 && !is_gimple_reg (decl)
2174 && clear_padding_type_may_have_padding_p (TREE_TYPE (decl)))
2175 gimple_add_padding_init_for_auto_var (decl, is_vla, seq_p);
2179 return GS_ALL_DONE;
2182 /* Gimplify a LOOP_EXPR. Normally this just involves gimplifying the body
2183 and replacing the LOOP_EXPR with goto, but if the loop contains an
2184 EXIT_EXPR, we need to append a label for it to jump to. */
2186 static enum gimplify_status
2187 gimplify_loop_expr (tree *expr_p, gimple_seq *pre_p)
2189 tree saved_label = gimplify_ctxp->exit_label;
2190 tree start_label = create_artificial_label (UNKNOWN_LOCATION);
2192 gimplify_seq_add_stmt (pre_p, gimple_build_label (start_label));
2194 gimplify_ctxp->exit_label = NULL_TREE;
2196 gimplify_and_add (LOOP_EXPR_BODY (*expr_p), pre_p);
2198 gimplify_seq_add_stmt (pre_p, gimple_build_goto (start_label));
2200 if (gimplify_ctxp->exit_label)
2201 gimplify_seq_add_stmt (pre_p,
2202 gimple_build_label (gimplify_ctxp->exit_label));
2204 gimplify_ctxp->exit_label = saved_label;
2206 *expr_p = NULL;
2207 return GS_ALL_DONE;
2210 /* Gimplify a statement list onto a sequence. These may be created either
2211 by an enlightened front-end, or by shortcut_cond_expr. */
2213 static enum gimplify_status
2214 gimplify_statement_list (tree *expr_p, gimple_seq *pre_p)
2216 tree temp = voidify_wrapper_expr (*expr_p, NULL);
2218 tree_stmt_iterator i = tsi_start (*expr_p);
2220 while (!tsi_end_p (i))
2222 gimplify_stmt (tsi_stmt_ptr (i), pre_p);
2223 tsi_delink (&i);
2226 if (temp)
2228 *expr_p = temp;
2229 return GS_OK;
2232 return GS_ALL_DONE;
2236 /* Emit warning for the unreachable statment STMT if needed.
2237 Return the gimple itself when the warning is emitted, otherwise
2238 return NULL. */
2239 static gimple *
2240 emit_warn_switch_unreachable (gimple *stmt)
2242 if (gimple_code (stmt) == GIMPLE_GOTO
2243 && TREE_CODE (gimple_goto_dest (stmt)) == LABEL_DECL
2244 && DECL_ARTIFICIAL (gimple_goto_dest (stmt)))
2245 /* Don't warn for compiler-generated gotos. These occur
2246 in Duff's devices, for example. */
2247 return NULL;
2248 else if ((flag_auto_var_init > AUTO_INIT_UNINITIALIZED)
2249 && ((gimple_call_internal_p (stmt, IFN_DEFERRED_INIT))
2250 || (gimple_call_builtin_p (stmt, BUILT_IN_CLEAR_PADDING)
2251 && (bool) TREE_INT_CST_LOW (gimple_call_arg (stmt, 1)))
2252 || (is_gimple_assign (stmt)
2253 && gimple_assign_single_p (stmt)
2254 && (TREE_CODE (gimple_assign_rhs1 (stmt)) == SSA_NAME)
2255 && gimple_call_internal_p (
2256 SSA_NAME_DEF_STMT (gimple_assign_rhs1 (stmt)),
2257 IFN_DEFERRED_INIT))))
2258 /* Don't warn for compiler-generated initializations for
2259 -ftrivial-auto-var-init.
2260 There are 3 cases:
2261 case 1: a call to .DEFERRED_INIT;
2262 case 2: a call to __builtin_clear_padding with the 2nd argument is
2263 present and non-zero;
2264 case 3: a gimple assign store right after the call to .DEFERRED_INIT
2265 that has the LHS of .DEFERRED_INIT as the RHS as following:
2266 _1 = .DEFERRED_INIT (4, 2, &"i1"[0]);
2267 i1 = _1. */
2268 return NULL;
2269 else
2270 warning_at (gimple_location (stmt), OPT_Wswitch_unreachable,
2271 "statement will never be executed");
2272 return stmt;
2275 /* Callback for walk_gimple_seq. */
2277 static tree
2278 warn_switch_unreachable_and_auto_init_r (gimple_stmt_iterator *gsi_p,
2279 bool *handled_ops_p,
2280 struct walk_stmt_info *wi)
2282 gimple *stmt = gsi_stmt (*gsi_p);
2283 bool unreachable_issued = wi->info != NULL;
2285 *handled_ops_p = true;
2286 switch (gimple_code (stmt))
2288 case GIMPLE_TRY:
2289 /* A compiler-generated cleanup or a user-written try block.
2290 If it's empty, don't dive into it--that would result in
2291 worse location info. */
2292 if (gimple_try_eval (stmt) == NULL)
2294 if (warn_switch_unreachable && !unreachable_issued)
2295 wi->info = emit_warn_switch_unreachable (stmt);
2297 /* Stop when auto var init warning is not on. */
2298 if (!warn_trivial_auto_var_init)
2299 return integer_zero_node;
2301 /* Fall through. */
2302 case GIMPLE_BIND:
2303 case GIMPLE_CATCH:
2304 case GIMPLE_EH_FILTER:
2305 case GIMPLE_TRANSACTION:
2306 /* Walk the sub-statements. */
2307 *handled_ops_p = false;
2308 break;
2310 case GIMPLE_DEBUG:
2311 /* Ignore these. We may generate them before declarations that
2312 are never executed. If there's something to warn about,
2313 there will be non-debug stmts too, and we'll catch those. */
2314 break;
2316 case GIMPLE_LABEL:
2317 /* Stop till the first Label. */
2318 return integer_zero_node;
2319 case GIMPLE_CALL:
2320 if (gimple_call_internal_p (stmt, IFN_ASAN_MARK))
2322 *handled_ops_p = false;
2323 break;
2325 if (warn_trivial_auto_var_init
2326 && flag_auto_var_init > AUTO_INIT_UNINITIALIZED
2327 && gimple_call_internal_p (stmt, IFN_DEFERRED_INIT))
2329 /* Get the variable name from the 3rd argument of call. */
2330 tree var_name = gimple_call_arg (stmt, 2);
2331 var_name = TREE_OPERAND (TREE_OPERAND (var_name, 0), 0);
2332 const char *var_name_str = TREE_STRING_POINTER (var_name);
2334 warning_at (gimple_location (stmt), OPT_Wtrivial_auto_var_init,
2335 "%qs cannot be initialized with"
2336 "%<-ftrivial-auto-var_init%>",
2337 var_name_str);
2338 break;
2341 /* Fall through. */
2342 default:
2343 /* check the first "real" statement (not a decl/lexical scope/...), issue
2344 warning if needed. */
2345 if (warn_switch_unreachable && !unreachable_issued)
2346 wi->info = emit_warn_switch_unreachable (stmt);
2347 /* Stop when auto var init warning is not on. */
2348 if (!warn_trivial_auto_var_init)
2349 return integer_zero_node;
2350 break;
2352 return NULL_TREE;
2356 /* Possibly warn about unreachable statements between switch's controlling
2357 expression and the first case. Also warn about -ftrivial-auto-var-init
2358 cannot initialize the auto variable under such situation.
2359 SEQ is the body of a switch expression. */
2361 static void
2362 maybe_warn_switch_unreachable_and_auto_init (gimple_seq seq)
2364 if ((!warn_switch_unreachable && !warn_trivial_auto_var_init)
2365 /* This warning doesn't play well with Fortran when optimizations
2366 are on. */
2367 || lang_GNU_Fortran ()
2368 || seq == NULL)
2369 return;
2371 struct walk_stmt_info wi;
2373 memset (&wi, 0, sizeof (wi));
2374 walk_gimple_seq (seq, warn_switch_unreachable_and_auto_init_r, NULL, &wi);
2378 /* A label entry that pairs label and a location. */
2379 struct label_entry
2381 tree label;
2382 location_t loc;
2385 /* Find LABEL in vector of label entries VEC. */
2387 static struct label_entry *
2388 find_label_entry (const auto_vec<struct label_entry> *vec, tree label)
2390 unsigned int i;
2391 struct label_entry *l;
2393 FOR_EACH_VEC_ELT (*vec, i, l)
2394 if (l->label == label)
2395 return l;
2396 return NULL;
2399 /* Return true if LABEL, a LABEL_DECL, represents a case label
2400 in a vector of labels CASES. */
2402 static bool
2403 case_label_p (const vec<tree> *cases, tree label)
2405 unsigned int i;
2406 tree l;
2408 FOR_EACH_VEC_ELT (*cases, i, l)
2409 if (CASE_LABEL (l) == label)
2410 return true;
2411 return false;
2414 /* Find the last nondebug statement in a scope STMT. */
2416 static gimple *
2417 last_stmt_in_scope (gimple *stmt)
2419 if (!stmt)
2420 return NULL;
2422 switch (gimple_code (stmt))
2424 case GIMPLE_BIND:
2426 gbind *bind = as_a <gbind *> (stmt);
2427 stmt = gimple_seq_last_nondebug_stmt (gimple_bind_body (bind));
2428 return last_stmt_in_scope (stmt);
2431 case GIMPLE_TRY:
2433 gtry *try_stmt = as_a <gtry *> (stmt);
2434 stmt = gimple_seq_last_nondebug_stmt (gimple_try_eval (try_stmt));
2435 gimple *last_eval = last_stmt_in_scope (stmt);
2436 if (gimple_stmt_may_fallthru (last_eval)
2437 && (last_eval == NULL
2438 || !gimple_call_internal_p (last_eval, IFN_FALLTHROUGH))
2439 && gimple_try_kind (try_stmt) == GIMPLE_TRY_FINALLY)
2441 stmt = gimple_seq_last_nondebug_stmt (gimple_try_cleanup (try_stmt));
2442 return last_stmt_in_scope (stmt);
2444 else
2445 return last_eval;
2448 case GIMPLE_DEBUG:
2449 gcc_unreachable ();
2451 default:
2452 return stmt;
2456 /* Collect labels that may fall through into LABELS and return the statement
2457 preceding another case label, or a user-defined label. Store a location
2458 useful to give warnings at *PREVLOC (usually the location of the returned
2459 statement or of its surrounding scope). */
2461 static gimple *
2462 collect_fallthrough_labels (gimple_stmt_iterator *gsi_p,
2463 auto_vec <struct label_entry> *labels,
2464 location_t *prevloc)
2466 gimple *prev = NULL;
2468 *prevloc = UNKNOWN_LOCATION;
2471 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_BIND)
2473 /* Recognize the special GIMPLE_BIND added by gimplify_switch_expr,
2474 which starts on a GIMPLE_SWITCH and ends with a break label.
2475 Handle that as a single statement that can fall through. */
2476 gbind *bind = as_a <gbind *> (gsi_stmt (*gsi_p));
2477 gimple *first = gimple_seq_first_stmt (gimple_bind_body (bind));
2478 gimple *last = gimple_seq_last_stmt (gimple_bind_body (bind));
2479 if (last
2480 && gimple_code (first) == GIMPLE_SWITCH
2481 && gimple_code (last) == GIMPLE_LABEL)
2483 tree label = gimple_label_label (as_a <glabel *> (last));
2484 if (SWITCH_BREAK_LABEL_P (label))
2486 prev = bind;
2487 gsi_next (gsi_p);
2488 continue;
2492 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_BIND
2493 || gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_TRY)
2495 /* Nested scope. Only look at the last statement of
2496 the innermost scope. */
2497 location_t bind_loc = gimple_location (gsi_stmt (*gsi_p));
2498 gimple *last = last_stmt_in_scope (gsi_stmt (*gsi_p));
2499 if (last)
2501 prev = last;
2502 /* It might be a label without a location. Use the
2503 location of the scope then. */
2504 if (!gimple_has_location (prev))
2505 *prevloc = bind_loc;
2507 gsi_next (gsi_p);
2508 continue;
2511 /* Ifs are tricky. */
2512 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_COND)
2514 gcond *cond_stmt = as_a <gcond *> (gsi_stmt (*gsi_p));
2515 tree false_lab = gimple_cond_false_label (cond_stmt);
2516 location_t if_loc = gimple_location (cond_stmt);
2518 /* If we have e.g.
2519 if (i > 1) goto <D.2259>; else goto D;
2520 we can't do much with the else-branch. */
2521 if (!DECL_ARTIFICIAL (false_lab))
2522 break;
2524 /* Go on until the false label, then one step back. */
2525 for (; !gsi_end_p (*gsi_p); gsi_next (gsi_p))
2527 gimple *stmt = gsi_stmt (*gsi_p);
2528 if (gimple_code (stmt) == GIMPLE_LABEL
2529 && gimple_label_label (as_a <glabel *> (stmt)) == false_lab)
2530 break;
2533 /* Not found? Oops. */
2534 if (gsi_end_p (*gsi_p))
2535 break;
2537 /* A dead label can't fall through. */
2538 if (!UNUSED_LABEL_P (false_lab))
2540 struct label_entry l = { false_lab, if_loc };
2541 labels->safe_push (l);
2544 /* Go to the last statement of the then branch. */
2545 gsi_prev (gsi_p);
2547 /* if (i != 0) goto <D.1759>; else goto <D.1760>;
2548 <D.1759>:
2549 <stmt>;
2550 goto <D.1761>;
2551 <D.1760>:
2553 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_GOTO
2554 && !gimple_has_location (gsi_stmt (*gsi_p)))
2556 /* Look at the statement before, it might be
2557 attribute fallthrough, in which case don't warn. */
2558 gsi_prev (gsi_p);
2559 bool fallthru_before_dest
2560 = gimple_call_internal_p (gsi_stmt (*gsi_p), IFN_FALLTHROUGH);
2561 gsi_next (gsi_p);
2562 tree goto_dest = gimple_goto_dest (gsi_stmt (*gsi_p));
2563 if (!fallthru_before_dest)
2565 struct label_entry l = { goto_dest, if_loc };
2566 labels->safe_push (l);
2569 /* This case is about
2570 if (1 != 0) goto <D.2022>; else goto <D.2023>;
2571 <D.2022>:
2572 n = n + 1; // #1
2573 <D.2023>: // #2
2574 <D.1988>: // #3
2575 where #2 is UNUSED_LABEL_P and we want to warn about #1 falling
2576 through to #3. So set PREV to #1. */
2577 else if (UNUSED_LABEL_P (false_lab))
2578 prev = gsi_stmt (*gsi_p);
2580 /* And move back. */
2581 gsi_next (gsi_p);
2584 /* Remember the last statement. Skip labels that are of no interest
2585 to us. */
2586 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_LABEL)
2588 tree label = gimple_label_label (as_a <glabel *> (gsi_stmt (*gsi_p)));
2589 if (find_label_entry (labels, label))
2590 prev = gsi_stmt (*gsi_p);
2592 else if (gimple_call_internal_p (gsi_stmt (*gsi_p), IFN_ASAN_MARK))
2594 else if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_PREDICT)
2596 else if (!is_gimple_debug (gsi_stmt (*gsi_p)))
2597 prev = gsi_stmt (*gsi_p);
2598 gsi_next (gsi_p);
2600 while (!gsi_end_p (*gsi_p)
2601 /* Stop if we find a case or a user-defined label. */
2602 && (gimple_code (gsi_stmt (*gsi_p)) != GIMPLE_LABEL
2603 || !gimple_has_location (gsi_stmt (*gsi_p))));
2605 if (prev && gimple_has_location (prev))
2606 *prevloc = gimple_location (prev);
2607 return prev;
2610 /* Return true if the switch fallthough warning should occur. LABEL is
2611 the label statement that we're falling through to. */
2613 static bool
2614 should_warn_for_implicit_fallthrough (gimple_stmt_iterator *gsi_p, tree label)
2616 gimple_stmt_iterator gsi = *gsi_p;
2618 /* Don't warn if the label is marked with a "falls through" comment. */
2619 if (FALLTHROUGH_LABEL_P (label))
2620 return false;
2622 /* Don't warn for non-case labels followed by a statement:
2623 case 0:
2624 foo ();
2625 label:
2626 bar ();
2627 as these are likely intentional. */
2628 if (!case_label_p (&gimplify_ctxp->case_labels, label))
2630 tree l;
2631 while (!gsi_end_p (gsi)
2632 && gimple_code (gsi_stmt (gsi)) == GIMPLE_LABEL
2633 && (l = gimple_label_label (as_a <glabel *> (gsi_stmt (gsi))))
2634 && !case_label_p (&gimplify_ctxp->case_labels, l))
2635 gsi_next_nondebug (&gsi);
2636 if (gsi_end_p (gsi) || gimple_code (gsi_stmt (gsi)) != GIMPLE_LABEL)
2637 return false;
2640 /* Don't warn for terminated branches, i.e. when the subsequent case labels
2641 immediately breaks. */
2642 gsi = *gsi_p;
2644 /* Skip all immediately following labels. */
2645 while (!gsi_end_p (gsi)
2646 && (gimple_code (gsi_stmt (gsi)) == GIMPLE_LABEL
2647 || gimple_code (gsi_stmt (gsi)) == GIMPLE_PREDICT))
2648 gsi_next_nondebug (&gsi);
2650 /* { ... something; default:; } */
2651 if (gsi_end_p (gsi)
2652 /* { ... something; default: break; } or
2653 { ... something; default: goto L; } */
2654 || gimple_code (gsi_stmt (gsi)) == GIMPLE_GOTO
2655 /* { ... something; default: return; } */
2656 || gimple_code (gsi_stmt (gsi)) == GIMPLE_RETURN)
2657 return false;
2659 return true;
2662 /* Callback for walk_gimple_seq. */
2664 static tree
2665 warn_implicit_fallthrough_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
2666 struct walk_stmt_info *)
2668 gimple *stmt = gsi_stmt (*gsi_p);
2670 *handled_ops_p = true;
2671 switch (gimple_code (stmt))
2673 case GIMPLE_TRY:
2674 case GIMPLE_BIND:
2675 case GIMPLE_CATCH:
2676 case GIMPLE_EH_FILTER:
2677 case GIMPLE_TRANSACTION:
2678 /* Walk the sub-statements. */
2679 *handled_ops_p = false;
2680 break;
2682 /* Find a sequence of form:
2684 GIMPLE_LABEL
2685 [...]
2686 <may fallthru stmt>
2687 GIMPLE_LABEL
2689 and possibly warn. */
2690 case GIMPLE_LABEL:
2692 /* Found a label. Skip all immediately following labels. */
2693 while (!gsi_end_p (*gsi_p)
2694 && gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_LABEL)
2695 gsi_next_nondebug (gsi_p);
2697 /* There might be no more statements. */
2698 if (gsi_end_p (*gsi_p))
2699 return integer_zero_node;
2701 /* Vector of labels that fall through. */
2702 auto_vec <struct label_entry> labels;
2703 location_t prevloc;
2704 gimple *prev = collect_fallthrough_labels (gsi_p, &labels, &prevloc);
2706 /* There might be no more statements. */
2707 if (gsi_end_p (*gsi_p))
2708 return integer_zero_node;
2710 gimple *next = gsi_stmt (*gsi_p);
2711 tree label;
2712 /* If what follows is a label, then we may have a fallthrough. */
2713 if (gimple_code (next) == GIMPLE_LABEL
2714 && gimple_has_location (next)
2715 && (label = gimple_label_label (as_a <glabel *> (next)))
2716 && prev != NULL)
2718 struct label_entry *l;
2719 bool warned_p = false;
2720 auto_diagnostic_group d;
2721 if (!should_warn_for_implicit_fallthrough (gsi_p, label))
2722 /* Quiet. */;
2723 else if (gimple_code (prev) == GIMPLE_LABEL
2724 && (label = gimple_label_label (as_a <glabel *> (prev)))
2725 && (l = find_label_entry (&labels, label)))
2726 warned_p = warning_at (l->loc, OPT_Wimplicit_fallthrough_,
2727 "this statement may fall through");
2728 else if (!gimple_call_internal_p (prev, IFN_FALLTHROUGH)
2729 /* Try to be clever and don't warn when the statement
2730 can't actually fall through. */
2731 && gimple_stmt_may_fallthru (prev)
2732 && prevloc != UNKNOWN_LOCATION)
2733 warned_p = warning_at (prevloc,
2734 OPT_Wimplicit_fallthrough_,
2735 "this statement may fall through");
2736 if (warned_p)
2737 inform (gimple_location (next), "here");
2739 /* Mark this label as processed so as to prevent multiple
2740 warnings in nested switches. */
2741 FALLTHROUGH_LABEL_P (label) = true;
2743 /* So that next warn_implicit_fallthrough_r will start looking for
2744 a new sequence starting with this label. */
2745 gsi_prev (gsi_p);
2748 break;
2749 default:
2750 break;
2752 return NULL_TREE;
2755 /* Warn when a switch case falls through. */
2757 static void
2758 maybe_warn_implicit_fallthrough (gimple_seq seq)
2760 if (!warn_implicit_fallthrough)
2761 return;
2763 /* This warning is meant for C/C++/ObjC/ObjC++ only. */
2764 if (!(lang_GNU_C ()
2765 || lang_GNU_CXX ()
2766 || lang_GNU_OBJC ()))
2767 return;
2769 struct walk_stmt_info wi;
2770 memset (&wi, 0, sizeof (wi));
2771 walk_gimple_seq (seq, warn_implicit_fallthrough_r, NULL, &wi);
2774 /* Callback for walk_gimple_seq. */
2776 static tree
2777 expand_FALLTHROUGH_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
2778 struct walk_stmt_info *wi)
2780 gimple *stmt = gsi_stmt (*gsi_p);
2782 *handled_ops_p = true;
2783 switch (gimple_code (stmt))
2785 case GIMPLE_TRY:
2786 case GIMPLE_BIND:
2787 case GIMPLE_CATCH:
2788 case GIMPLE_EH_FILTER:
2789 case GIMPLE_TRANSACTION:
2790 /* Walk the sub-statements. */
2791 *handled_ops_p = false;
2792 break;
2793 case GIMPLE_CALL:
2794 static_cast<location_t *>(wi->info)[0] = UNKNOWN_LOCATION;
2795 if (gimple_call_internal_p (stmt, IFN_FALLTHROUGH))
2797 location_t loc = gimple_location (stmt);
2798 gsi_remove (gsi_p, true);
2799 wi->removed_stmt = true;
2801 /* nothrow flag is added by genericize_c_loop to mark fallthrough
2802 statement at the end of some loop's body. Those should be
2803 always diagnosed, either because they indeed don't precede
2804 a case label or default label, or because the next statement
2805 is not within the same iteration statement. */
2806 if ((stmt->subcode & GF_CALL_NOTHROW) != 0)
2808 pedwarn (loc, 0, "attribute %<fallthrough%> not preceding "
2809 "a case label or default label");
2810 break;
2813 if (gsi_end_p (*gsi_p))
2815 static_cast<location_t *>(wi->info)[0] = BUILTINS_LOCATION;
2816 static_cast<location_t *>(wi->info)[1] = loc;
2817 break;
2820 bool found = false;
2822 gimple_stmt_iterator gsi2 = *gsi_p;
2823 stmt = gsi_stmt (gsi2);
2824 if (gimple_code (stmt) == GIMPLE_GOTO && !gimple_has_location (stmt))
2826 /* Go on until the artificial label. */
2827 tree goto_dest = gimple_goto_dest (stmt);
2828 for (; !gsi_end_p (gsi2); gsi_next (&gsi2))
2830 if (gimple_code (gsi_stmt (gsi2)) == GIMPLE_LABEL
2831 && gimple_label_label (as_a <glabel *> (gsi_stmt (gsi2)))
2832 == goto_dest)
2833 break;
2836 /* Not found? Stop. */
2837 if (gsi_end_p (gsi2))
2838 break;
2840 /* Look one past it. */
2841 gsi_next (&gsi2);
2844 /* We're looking for a case label or default label here. */
2845 while (!gsi_end_p (gsi2))
2847 stmt = gsi_stmt (gsi2);
2848 if (gimple_code (stmt) == GIMPLE_LABEL)
2850 tree label = gimple_label_label (as_a <glabel *> (stmt));
2851 if (gimple_has_location (stmt) && DECL_ARTIFICIAL (label))
2853 found = true;
2854 break;
2857 else if (gimple_call_internal_p (stmt, IFN_ASAN_MARK))
2859 else if (!is_gimple_debug (stmt))
2860 /* Anything else is not expected. */
2861 break;
2862 gsi_next (&gsi2);
2864 if (!found)
2865 pedwarn (loc, 0, "attribute %<fallthrough%> not preceding "
2866 "a case label or default label");
2868 break;
2869 default:
2870 static_cast<location_t *>(wi->info)[0] = UNKNOWN_LOCATION;
2871 break;
2873 return NULL_TREE;
2876 /* Expand all FALLTHROUGH () calls in SEQ. */
2878 static void
2879 expand_FALLTHROUGH (gimple_seq *seq_p)
2881 struct walk_stmt_info wi;
2882 location_t loc[2];
2883 memset (&wi, 0, sizeof (wi));
2884 loc[0] = UNKNOWN_LOCATION;
2885 loc[1] = UNKNOWN_LOCATION;
2886 wi.info = (void *) &loc[0];
2887 walk_gimple_seq_mod (seq_p, expand_FALLTHROUGH_r, NULL, &wi);
2888 if (loc[0] != UNKNOWN_LOCATION)
2889 /* We've found [[fallthrough]]; at the end of a switch, which the C++
2890 standard says is ill-formed; see [dcl.attr.fallthrough]. */
2891 pedwarn (loc[1], 0, "attribute %<fallthrough%> not preceding "
2892 "a case label or default label");
2896 /* Gimplify a SWITCH_EXPR, and collect the vector of labels it can
2897 branch to. */
2899 static enum gimplify_status
2900 gimplify_switch_expr (tree *expr_p, gimple_seq *pre_p)
2902 tree switch_expr = *expr_p;
2903 gimple_seq switch_body_seq = NULL;
2904 enum gimplify_status ret;
2905 tree index_type = TREE_TYPE (switch_expr);
2906 if (index_type == NULL_TREE)
2907 index_type = TREE_TYPE (SWITCH_COND (switch_expr));
2909 ret = gimplify_expr (&SWITCH_COND (switch_expr), pre_p, NULL, is_gimple_val,
2910 fb_rvalue);
2911 if (ret == GS_ERROR || ret == GS_UNHANDLED)
2912 return ret;
2914 if (SWITCH_BODY (switch_expr))
2916 vec<tree> labels;
2917 vec<tree> saved_labels;
2918 hash_set<tree> *saved_live_switch_vars = NULL;
2919 tree default_case = NULL_TREE;
2920 gswitch *switch_stmt;
2922 /* Save old labels, get new ones from body, then restore the old
2923 labels. Save all the things from the switch body to append after. */
2924 saved_labels = gimplify_ctxp->case_labels;
2925 gimplify_ctxp->case_labels.create (8);
2927 /* Do not create live_switch_vars if SWITCH_BODY is not a BIND_EXPR. */
2928 saved_live_switch_vars = gimplify_ctxp->live_switch_vars;
2929 tree_code body_type = TREE_CODE (SWITCH_BODY (switch_expr));
2930 if (body_type == BIND_EXPR || body_type == STATEMENT_LIST)
2931 gimplify_ctxp->live_switch_vars = new hash_set<tree> (4);
2932 else
2933 gimplify_ctxp->live_switch_vars = NULL;
2935 bool old_in_switch_expr = gimplify_ctxp->in_switch_expr;
2936 gimplify_ctxp->in_switch_expr = true;
2938 gimplify_stmt (&SWITCH_BODY (switch_expr), &switch_body_seq);
2940 gimplify_ctxp->in_switch_expr = old_in_switch_expr;
2941 maybe_warn_switch_unreachable_and_auto_init (switch_body_seq);
2942 maybe_warn_implicit_fallthrough (switch_body_seq);
2943 /* Only do this for the outermost GIMPLE_SWITCH. */
2944 if (!gimplify_ctxp->in_switch_expr)
2945 expand_FALLTHROUGH (&switch_body_seq);
2947 labels = gimplify_ctxp->case_labels;
2948 gimplify_ctxp->case_labels = saved_labels;
2950 if (gimplify_ctxp->live_switch_vars)
2952 gcc_assert (gimplify_ctxp->live_switch_vars->is_empty ());
2953 delete gimplify_ctxp->live_switch_vars;
2955 gimplify_ctxp->live_switch_vars = saved_live_switch_vars;
2957 preprocess_case_label_vec_for_gimple (labels, index_type,
2958 &default_case);
2960 bool add_bind = false;
2961 if (!default_case)
2963 glabel *new_default;
2965 default_case
2966 = build_case_label (NULL_TREE, NULL_TREE,
2967 create_artificial_label (UNKNOWN_LOCATION));
2968 if (old_in_switch_expr)
2970 SWITCH_BREAK_LABEL_P (CASE_LABEL (default_case)) = 1;
2971 add_bind = true;
2973 new_default = gimple_build_label (CASE_LABEL (default_case));
2974 gimplify_seq_add_stmt (&switch_body_seq, new_default);
2976 else if (old_in_switch_expr)
2978 gimple *last = gimple_seq_last_stmt (switch_body_seq);
2979 if (last && gimple_code (last) == GIMPLE_LABEL)
2981 tree label = gimple_label_label (as_a <glabel *> (last));
2982 if (SWITCH_BREAK_LABEL_P (label))
2983 add_bind = true;
2987 switch_stmt = gimple_build_switch (SWITCH_COND (switch_expr),
2988 default_case, labels);
2989 /* For the benefit of -Wimplicit-fallthrough, if switch_body_seq
2990 ends with a GIMPLE_LABEL holding SWITCH_BREAK_LABEL_P LABEL_DECL,
2991 wrap the GIMPLE_SWITCH up to that GIMPLE_LABEL into a GIMPLE_BIND,
2992 so that we can easily find the start and end of the switch
2993 statement. */
2994 if (add_bind)
2996 gimple_seq bind_body = NULL;
2997 gimplify_seq_add_stmt (&bind_body, switch_stmt);
2998 gimple_seq_add_seq (&bind_body, switch_body_seq);
2999 gbind *bind = gimple_build_bind (NULL_TREE, bind_body, NULL_TREE);
3000 gimple_set_location (bind, EXPR_LOCATION (switch_expr));
3001 gimplify_seq_add_stmt (pre_p, bind);
3003 else
3005 gimplify_seq_add_stmt (pre_p, switch_stmt);
3006 gimplify_seq_add_seq (pre_p, switch_body_seq);
3008 labels.release ();
3010 else
3011 gcc_unreachable ();
3013 return GS_ALL_DONE;
3016 /* Gimplify the LABEL_EXPR pointed to by EXPR_P. */
3018 static enum gimplify_status
3019 gimplify_label_expr (tree *expr_p, gimple_seq *pre_p)
3021 gcc_assert (decl_function_context (LABEL_EXPR_LABEL (*expr_p))
3022 == current_function_decl);
3024 tree label = LABEL_EXPR_LABEL (*expr_p);
3025 glabel *label_stmt = gimple_build_label (label);
3026 gimple_set_location (label_stmt, EXPR_LOCATION (*expr_p));
3027 gimplify_seq_add_stmt (pre_p, label_stmt);
3029 if (lookup_attribute ("cold", DECL_ATTRIBUTES (label)))
3030 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_COLD_LABEL,
3031 NOT_TAKEN));
3032 else if (lookup_attribute ("hot", DECL_ATTRIBUTES (label)))
3033 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_HOT_LABEL,
3034 TAKEN));
3036 return GS_ALL_DONE;
3039 /* Gimplify the CASE_LABEL_EXPR pointed to by EXPR_P. */
3041 static enum gimplify_status
3042 gimplify_case_label_expr (tree *expr_p, gimple_seq *pre_p)
3044 struct gimplify_ctx *ctxp;
3045 glabel *label_stmt;
3047 /* Invalid programs can play Duff's Device type games with, for example,
3048 #pragma omp parallel. At least in the C front end, we don't
3049 detect such invalid branches until after gimplification, in the
3050 diagnose_omp_blocks pass. */
3051 for (ctxp = gimplify_ctxp; ; ctxp = ctxp->prev_context)
3052 if (ctxp->case_labels.exists ())
3053 break;
3055 tree label = CASE_LABEL (*expr_p);
3056 label_stmt = gimple_build_label (label);
3057 gimple_set_location (label_stmt, EXPR_LOCATION (*expr_p));
3058 ctxp->case_labels.safe_push (*expr_p);
3059 gimplify_seq_add_stmt (pre_p, label_stmt);
3061 if (lookup_attribute ("cold", DECL_ATTRIBUTES (label)))
3062 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_COLD_LABEL,
3063 NOT_TAKEN));
3064 else if (lookup_attribute ("hot", DECL_ATTRIBUTES (label)))
3065 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_HOT_LABEL,
3066 TAKEN));
3068 return GS_ALL_DONE;
3071 /* Build a GOTO to the LABEL_DECL pointed to by LABEL_P, building it first
3072 if necessary. */
3074 tree
3075 build_and_jump (tree *label_p)
3077 if (label_p == NULL)
3078 /* If there's nowhere to jump, just fall through. */
3079 return NULL_TREE;
3081 if (*label_p == NULL_TREE)
3083 tree label = create_artificial_label (UNKNOWN_LOCATION);
3084 *label_p = label;
3087 return build1 (GOTO_EXPR, void_type_node, *label_p);
3090 /* Gimplify an EXIT_EXPR by converting to a GOTO_EXPR inside a COND_EXPR.
3091 This also involves building a label to jump to and communicating it to
3092 gimplify_loop_expr through gimplify_ctxp->exit_label. */
3094 static enum gimplify_status
3095 gimplify_exit_expr (tree *expr_p)
3097 tree cond = TREE_OPERAND (*expr_p, 0);
3098 tree expr;
3100 expr = build_and_jump (&gimplify_ctxp->exit_label);
3101 expr = build3 (COND_EXPR, void_type_node, cond, expr, NULL_TREE);
3102 *expr_p = expr;
3104 return GS_OK;
3107 /* *EXPR_P is a COMPONENT_REF being used as an rvalue. If its type is
3108 different from its canonical type, wrap the whole thing inside a
3109 NOP_EXPR and force the type of the COMPONENT_REF to be the canonical
3110 type.
3112 The canonical type of a COMPONENT_REF is the type of the field being
3113 referenced--unless the field is a bit-field which can be read directly
3114 in a smaller mode, in which case the canonical type is the
3115 sign-appropriate type corresponding to that mode. */
3117 static void
3118 canonicalize_component_ref (tree *expr_p)
3120 tree expr = *expr_p;
3121 tree type;
3123 gcc_assert (TREE_CODE (expr) == COMPONENT_REF);
3125 if (INTEGRAL_TYPE_P (TREE_TYPE (expr)))
3126 type = TREE_TYPE (get_unwidened (expr, NULL_TREE));
3127 else
3128 type = TREE_TYPE (TREE_OPERAND (expr, 1));
3130 /* One could argue that all the stuff below is not necessary for
3131 the non-bitfield case and declare it a FE error if type
3132 adjustment would be needed. */
3133 if (TREE_TYPE (expr) != type)
3135 #ifdef ENABLE_TYPES_CHECKING
3136 tree old_type = TREE_TYPE (expr);
3137 #endif
3138 int type_quals;
3140 /* We need to preserve qualifiers and propagate them from
3141 operand 0. */
3142 type_quals = TYPE_QUALS (type)
3143 | TYPE_QUALS (TREE_TYPE (TREE_OPERAND (expr, 0)));
3144 if (TYPE_QUALS (type) != type_quals)
3145 type = build_qualified_type (TYPE_MAIN_VARIANT (type), type_quals);
3147 /* Set the type of the COMPONENT_REF to the underlying type. */
3148 TREE_TYPE (expr) = type;
3150 #ifdef ENABLE_TYPES_CHECKING
3151 /* It is now a FE error, if the conversion from the canonical
3152 type to the original expression type is not useless. */
3153 gcc_assert (useless_type_conversion_p (old_type, type));
3154 #endif
3158 /* If a NOP conversion is changing a pointer to array of foo to a pointer
3159 to foo, embed that change in the ADDR_EXPR by converting
3160 T array[U];
3161 (T *)&array
3163 &array[L]
3164 where L is the lower bound. For simplicity, only do this for constant
3165 lower bound.
3166 The constraint is that the type of &array[L] is trivially convertible
3167 to T *. */
3169 static void
3170 canonicalize_addr_expr (tree *expr_p)
3172 tree expr = *expr_p;
3173 tree addr_expr = TREE_OPERAND (expr, 0);
3174 tree datype, ddatype, pddatype;
3176 /* We simplify only conversions from an ADDR_EXPR to a pointer type. */
3177 if (!POINTER_TYPE_P (TREE_TYPE (expr))
3178 || TREE_CODE (addr_expr) != ADDR_EXPR)
3179 return;
3181 /* The addr_expr type should be a pointer to an array. */
3182 datype = TREE_TYPE (TREE_TYPE (addr_expr));
3183 if (TREE_CODE (datype) != ARRAY_TYPE)
3184 return;
3186 /* The pointer to element type shall be trivially convertible to
3187 the expression pointer type. */
3188 ddatype = TREE_TYPE (datype);
3189 pddatype = build_pointer_type (ddatype);
3190 if (!useless_type_conversion_p (TYPE_MAIN_VARIANT (TREE_TYPE (expr)),
3191 pddatype))
3192 return;
3194 /* The lower bound and element sizes must be constant. */
3195 if (!TYPE_SIZE_UNIT (ddatype)
3196 || TREE_CODE (TYPE_SIZE_UNIT (ddatype)) != INTEGER_CST
3197 || !TYPE_DOMAIN (datype) || !TYPE_MIN_VALUE (TYPE_DOMAIN (datype))
3198 || TREE_CODE (TYPE_MIN_VALUE (TYPE_DOMAIN (datype))) != INTEGER_CST)
3199 return;
3201 /* All checks succeeded. Build a new node to merge the cast. */
3202 *expr_p = build4 (ARRAY_REF, ddatype, TREE_OPERAND (addr_expr, 0),
3203 TYPE_MIN_VALUE (TYPE_DOMAIN (datype)),
3204 NULL_TREE, NULL_TREE);
3205 *expr_p = build1 (ADDR_EXPR, pddatype, *expr_p);
3207 /* We can have stripped a required restrict qualifier above. */
3208 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
3209 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
3212 /* *EXPR_P is a NOP_EXPR or CONVERT_EXPR. Remove it and/or other conversions
3213 underneath as appropriate. */
3215 static enum gimplify_status
3216 gimplify_conversion (tree *expr_p)
3218 location_t loc = EXPR_LOCATION (*expr_p);
3219 gcc_assert (CONVERT_EXPR_P (*expr_p));
3221 /* Then strip away all but the outermost conversion. */
3222 STRIP_SIGN_NOPS (TREE_OPERAND (*expr_p, 0));
3224 /* And remove the outermost conversion if it's useless. */
3225 if (tree_ssa_useless_type_conversion (*expr_p))
3226 *expr_p = TREE_OPERAND (*expr_p, 0);
3228 /* If we still have a conversion at the toplevel,
3229 then canonicalize some constructs. */
3230 if (CONVERT_EXPR_P (*expr_p))
3232 tree sub = TREE_OPERAND (*expr_p, 0);
3234 /* If a NOP conversion is changing the type of a COMPONENT_REF
3235 expression, then canonicalize its type now in order to expose more
3236 redundant conversions. */
3237 if (TREE_CODE (sub) == COMPONENT_REF)
3238 canonicalize_component_ref (&TREE_OPERAND (*expr_p, 0));
3240 /* If a NOP conversion is changing a pointer to array of foo
3241 to a pointer to foo, embed that change in the ADDR_EXPR. */
3242 else if (TREE_CODE (sub) == ADDR_EXPR)
3243 canonicalize_addr_expr (expr_p);
3246 /* If we have a conversion to a non-register type force the
3247 use of a VIEW_CONVERT_EXPR instead. */
3248 if (CONVERT_EXPR_P (*expr_p) && !is_gimple_reg_type (TREE_TYPE (*expr_p)))
3249 *expr_p = fold_build1_loc (loc, VIEW_CONVERT_EXPR, TREE_TYPE (*expr_p),
3250 TREE_OPERAND (*expr_p, 0));
3252 /* Canonicalize CONVERT_EXPR to NOP_EXPR. */
3253 if (TREE_CODE (*expr_p) == CONVERT_EXPR)
3254 TREE_SET_CODE (*expr_p, NOP_EXPR);
3256 return GS_OK;
3259 /* Gimplify a VAR_DECL or PARM_DECL. Return GS_OK if we expanded a
3260 DECL_VALUE_EXPR, and it's worth re-examining things. */
3262 static enum gimplify_status
3263 gimplify_var_or_parm_decl (tree *expr_p)
3265 tree decl = *expr_p;
3267 /* ??? If this is a local variable, and it has not been seen in any
3268 outer BIND_EXPR, then it's probably the result of a duplicate
3269 declaration, for which we've already issued an error. It would
3270 be really nice if the front end wouldn't leak these at all.
3271 Currently the only known culprit is C++ destructors, as seen
3272 in g++.old-deja/g++.jason/binding.C.
3273 Another possible culpit are size expressions for variably modified
3274 types which are lost in the FE or not gimplified correctly. */
3275 if (VAR_P (decl)
3276 && !DECL_SEEN_IN_BIND_EXPR_P (decl)
3277 && !TREE_STATIC (decl) && !DECL_EXTERNAL (decl)
3278 && decl_function_context (decl) == current_function_decl)
3280 gcc_assert (seen_error ());
3281 return GS_ERROR;
3284 /* When within an OMP context, notice uses of variables. */
3285 if (gimplify_omp_ctxp && omp_notice_variable (gimplify_omp_ctxp, decl, true))
3286 return GS_ALL_DONE;
3288 /* If the decl is an alias for another expression, substitute it now. */
3289 if (DECL_HAS_VALUE_EXPR_P (decl))
3291 *expr_p = unshare_expr (DECL_VALUE_EXPR (decl));
3292 return GS_OK;
3295 return GS_ALL_DONE;
3298 /* Recalculate the value of the TREE_SIDE_EFFECTS flag for T. */
3300 static void
3301 recalculate_side_effects (tree t)
3303 enum tree_code code = TREE_CODE (t);
3304 int len = TREE_OPERAND_LENGTH (t);
3305 int i;
3307 switch (TREE_CODE_CLASS (code))
3309 case tcc_expression:
3310 switch (code)
3312 case INIT_EXPR:
3313 case MODIFY_EXPR:
3314 case VA_ARG_EXPR:
3315 case PREDECREMENT_EXPR:
3316 case PREINCREMENT_EXPR:
3317 case POSTDECREMENT_EXPR:
3318 case POSTINCREMENT_EXPR:
3319 /* All of these have side-effects, no matter what their
3320 operands are. */
3321 return;
3323 default:
3324 break;
3326 /* Fall through. */
3328 case tcc_comparison: /* a comparison expression */
3329 case tcc_unary: /* a unary arithmetic expression */
3330 case tcc_binary: /* a binary arithmetic expression */
3331 case tcc_reference: /* a reference */
3332 case tcc_vl_exp: /* a function call */
3333 TREE_SIDE_EFFECTS (t) = TREE_THIS_VOLATILE (t);
3334 for (i = 0; i < len; ++i)
3336 tree op = TREE_OPERAND (t, i);
3337 if (op && TREE_SIDE_EFFECTS (op))
3338 TREE_SIDE_EFFECTS (t) = 1;
3340 break;
3342 case tcc_constant:
3343 /* No side-effects. */
3344 return;
3346 default:
3347 gcc_unreachable ();
3351 /* Gimplify the COMPONENT_REF, ARRAY_REF, REALPART_EXPR or IMAGPART_EXPR
3352 node *EXPR_P.
3354 compound_lval
3355 : min_lval '[' val ']'
3356 | min_lval '.' ID
3357 | compound_lval '[' val ']'
3358 | compound_lval '.' ID
3360 This is not part of the original SIMPLE definition, which separates
3361 array and member references, but it seems reasonable to handle them
3362 together. Also, this way we don't run into problems with union
3363 aliasing; gcc requires that for accesses through a union to alias, the
3364 union reference must be explicit, which was not always the case when we
3365 were splitting up array and member refs.
3367 PRE_P points to the sequence where side effects that must happen before
3368 *EXPR_P should be stored.
3370 POST_P points to the sequence where side effects that must happen after
3371 *EXPR_P should be stored. */
3373 static enum gimplify_status
3374 gimplify_compound_lval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
3375 fallback_t fallback)
3377 tree *p;
3378 enum gimplify_status ret = GS_ALL_DONE, tret;
3379 int i;
3380 location_t loc = EXPR_LOCATION (*expr_p);
3381 tree expr = *expr_p;
3383 /* Create a stack of the subexpressions so later we can walk them in
3384 order from inner to outer. */
3385 auto_vec<tree, 10> expr_stack;
3387 /* We can handle anything that get_inner_reference can deal with. */
3388 for (p = expr_p; ; p = &TREE_OPERAND (*p, 0))
3390 restart:
3391 /* Fold INDIRECT_REFs now to turn them into ARRAY_REFs. */
3392 if (TREE_CODE (*p) == INDIRECT_REF)
3393 *p = fold_indirect_ref_loc (loc, *p);
3395 if (handled_component_p (*p))
3397 /* Expand DECL_VALUE_EXPR now. In some cases that may expose
3398 additional COMPONENT_REFs. */
3399 else if ((VAR_P (*p) || TREE_CODE (*p) == PARM_DECL)
3400 && gimplify_var_or_parm_decl (p) == GS_OK)
3401 goto restart;
3402 else
3403 break;
3405 expr_stack.safe_push (*p);
3408 gcc_assert (expr_stack.length ());
3410 /* Now EXPR_STACK is a stack of pointers to all the refs we've
3411 walked through and P points to the innermost expression.
3413 Java requires that we elaborated nodes in source order. That
3414 means we must gimplify the inner expression followed by each of
3415 the indices, in order. But we can't gimplify the inner
3416 expression until we deal with any variable bounds, sizes, or
3417 positions in order to deal with PLACEHOLDER_EXPRs.
3419 The base expression may contain a statement expression that
3420 has declarations used in size expressions, so has to be
3421 gimplified before gimplifying the size expressions.
3423 So we do this in three steps. First we deal with variable
3424 bounds, sizes, and positions, then we gimplify the base and
3425 ensure it is memory if needed, then we deal with the annotations
3426 for any variables in the components and any indices, from left
3427 to right. */
3429 bool need_non_reg = false;
3430 for (i = expr_stack.length () - 1; i >= 0; i--)
3432 tree t = expr_stack[i];
3434 if (error_operand_p (TREE_OPERAND (t, 0)))
3435 return GS_ERROR;
3437 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
3439 /* Deal with the low bound and element type size and put them into
3440 the ARRAY_REF. If these values are set, they have already been
3441 gimplified. */
3442 if (TREE_OPERAND (t, 2) == NULL_TREE)
3444 tree low = unshare_expr (array_ref_low_bound (t));
3445 if (!is_gimple_min_invariant (low))
3447 TREE_OPERAND (t, 2) = low;
3451 if (TREE_OPERAND (t, 3) == NULL_TREE)
3453 tree elmt_size = array_ref_element_size (t);
3454 if (!is_gimple_min_invariant (elmt_size))
3456 elmt_size = unshare_expr (elmt_size);
3457 tree elmt_type = TREE_TYPE (TREE_TYPE (TREE_OPERAND (t, 0)));
3458 tree factor = size_int (TYPE_ALIGN_UNIT (elmt_type));
3460 /* Divide the element size by the alignment of the element
3461 type (above). */
3462 elmt_size = size_binop_loc (loc, EXACT_DIV_EXPR,
3463 elmt_size, factor);
3465 TREE_OPERAND (t, 3) = elmt_size;
3468 need_non_reg = true;
3470 else if (TREE_CODE (t) == COMPONENT_REF)
3472 /* Set the field offset into T and gimplify it. */
3473 if (TREE_OPERAND (t, 2) == NULL_TREE)
3475 tree offset = component_ref_field_offset (t);
3476 if (!is_gimple_min_invariant (offset))
3478 offset = unshare_expr (offset);
3479 tree field = TREE_OPERAND (t, 1);
3480 tree factor
3481 = size_int (DECL_OFFSET_ALIGN (field) / BITS_PER_UNIT);
3483 /* Divide the offset by its alignment. */
3484 offset = size_binop_loc (loc, EXACT_DIV_EXPR,
3485 offset, factor);
3487 TREE_OPERAND (t, 2) = offset;
3490 need_non_reg = true;
3492 else if (!is_gimple_reg_type (TREE_TYPE (t)))
3493 /* When the result of an operation, in particular a VIEW_CONVERT_EXPR
3494 is a non-register type then require the base object to be a
3495 non-register as well. */
3496 need_non_reg = true;
3499 /* Step 2 is to gimplify the base expression. Make sure lvalue is set
3500 so as to match the min_lval predicate. Failure to do so may result
3501 in the creation of large aggregate temporaries. */
3502 tret = gimplify_expr (p, pre_p, post_p, is_gimple_min_lval,
3503 fallback | fb_lvalue);
3504 ret = MIN (ret, tret);
3505 if (ret == GS_ERROR)
3506 return GS_ERROR;
3508 /* Step 2a: if we have component references we do not support on
3509 registers then make sure the base isn't a register. Of course
3510 we can only do so if an rvalue is OK. */
3511 if (need_non_reg && (fallback & fb_rvalue))
3512 prepare_gimple_addressable (p, pre_p);
3515 /* Step 3: gimplify size expressions and the indices and operands of
3516 ARRAY_REF. During this loop we also remove any useless conversions.
3517 If we operate on a register also make sure to properly gimplify
3518 to individual operations. */
3520 bool reg_operations = is_gimple_reg (*p);
3521 for (; expr_stack.length () > 0; )
3523 tree t = expr_stack.pop ();
3525 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
3527 gcc_assert (!reg_operations);
3529 /* Gimplify the low bound and element type size. */
3530 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
3531 is_gimple_reg, fb_rvalue);
3532 ret = MIN (ret, tret);
3534 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p, post_p,
3535 is_gimple_reg, fb_rvalue);
3536 ret = MIN (ret, tret);
3538 /* Gimplify the dimension. */
3539 tret = gimplify_expr (&TREE_OPERAND (t, 1), pre_p, post_p,
3540 is_gimple_val, fb_rvalue);
3541 ret = MIN (ret, tret);
3543 else if (TREE_CODE (t) == COMPONENT_REF)
3545 gcc_assert (!reg_operations);
3547 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
3548 is_gimple_reg, fb_rvalue);
3549 ret = MIN (ret, tret);
3551 else if (reg_operations)
3553 tret = gimplify_expr (&TREE_OPERAND (t, 0), pre_p, post_p,
3554 is_gimple_val, fb_rvalue);
3555 ret = MIN (ret, tret);
3558 STRIP_USELESS_TYPE_CONVERSION (TREE_OPERAND (t, 0));
3560 /* The innermost expression P may have originally had
3561 TREE_SIDE_EFFECTS set which would have caused all the outer
3562 expressions in *EXPR_P leading to P to also have had
3563 TREE_SIDE_EFFECTS set. */
3564 recalculate_side_effects (t);
3567 /* If the outermost expression is a COMPONENT_REF, canonicalize its type. */
3568 if ((fallback & fb_rvalue) && TREE_CODE (*expr_p) == COMPONENT_REF)
3570 canonicalize_component_ref (expr_p);
3573 expr_stack.release ();
3575 gcc_assert (*expr_p == expr || ret != GS_ALL_DONE);
3577 return ret;
3580 /* Gimplify the self modifying expression pointed to by EXPR_P
3581 (++, --, +=, -=).
3583 PRE_P points to the list where side effects that must happen before
3584 *EXPR_P should be stored.
3586 POST_P points to the list where side effects that must happen after
3587 *EXPR_P should be stored.
3589 WANT_VALUE is nonzero iff we want to use the value of this expression
3590 in another expression.
3592 ARITH_TYPE is the type the computation should be performed in. */
3594 enum gimplify_status
3595 gimplify_self_mod_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
3596 bool want_value, tree arith_type)
3598 enum tree_code code;
3599 tree lhs, lvalue, rhs, t1;
3600 gimple_seq post = NULL, *orig_post_p = post_p;
3601 bool postfix;
3602 enum tree_code arith_code;
3603 enum gimplify_status ret;
3604 location_t loc = EXPR_LOCATION (*expr_p);
3606 code = TREE_CODE (*expr_p);
3608 gcc_assert (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR
3609 || code == PREINCREMENT_EXPR || code == PREDECREMENT_EXPR);
3611 /* Prefix or postfix? */
3612 if (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR)
3613 /* Faster to treat as prefix if result is not used. */
3614 postfix = want_value;
3615 else
3616 postfix = false;
3618 /* For postfix, make sure the inner expression's post side effects
3619 are executed after side effects from this expression. */
3620 if (postfix)
3621 post_p = &post;
3623 /* Add or subtract? */
3624 if (code == PREINCREMENT_EXPR || code == POSTINCREMENT_EXPR)
3625 arith_code = PLUS_EXPR;
3626 else
3627 arith_code = MINUS_EXPR;
3629 /* Gimplify the LHS into a GIMPLE lvalue. */
3630 lvalue = TREE_OPERAND (*expr_p, 0);
3631 ret = gimplify_expr (&lvalue, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
3632 if (ret == GS_ERROR)
3633 return ret;
3635 /* Extract the operands to the arithmetic operation. */
3636 lhs = lvalue;
3637 rhs = TREE_OPERAND (*expr_p, 1);
3639 /* For postfix operator, we evaluate the LHS to an rvalue and then use
3640 that as the result value and in the postqueue operation. */
3641 if (postfix)
3643 ret = gimplify_expr (&lhs, pre_p, post_p, is_gimple_val, fb_rvalue);
3644 if (ret == GS_ERROR)
3645 return ret;
3647 lhs = get_initialized_tmp_var (lhs, pre_p);
3650 /* For POINTERs increment, use POINTER_PLUS_EXPR. */
3651 if (POINTER_TYPE_P (TREE_TYPE (lhs)))
3653 rhs = convert_to_ptrofftype_loc (loc, rhs);
3654 if (arith_code == MINUS_EXPR)
3655 rhs = fold_build1_loc (loc, NEGATE_EXPR, TREE_TYPE (rhs), rhs);
3656 t1 = fold_build2 (POINTER_PLUS_EXPR, TREE_TYPE (*expr_p), lhs, rhs);
3658 else
3659 t1 = fold_convert (TREE_TYPE (*expr_p),
3660 fold_build2 (arith_code, arith_type,
3661 fold_convert (arith_type, lhs),
3662 fold_convert (arith_type, rhs)));
3664 if (postfix)
3666 gimplify_assign (lvalue, t1, pre_p);
3667 gimplify_seq_add_seq (orig_post_p, post);
3668 *expr_p = lhs;
3669 return GS_ALL_DONE;
3671 else
3673 *expr_p = build2 (MODIFY_EXPR, TREE_TYPE (lvalue), lvalue, t1);
3674 return GS_OK;
3678 /* If *EXPR_P has a variable sized type, wrap it in a WITH_SIZE_EXPR. */
3680 static void
3681 maybe_with_size_expr (tree *expr_p)
3683 tree expr = *expr_p;
3684 tree type = TREE_TYPE (expr);
3685 tree size;
3687 /* If we've already wrapped this or the type is error_mark_node, we can't do
3688 anything. */
3689 if (TREE_CODE (expr) == WITH_SIZE_EXPR
3690 || type == error_mark_node)
3691 return;
3693 /* If the size isn't known or is a constant, we have nothing to do. */
3694 size = TYPE_SIZE_UNIT (type);
3695 if (!size || poly_int_tree_p (size))
3696 return;
3698 /* Otherwise, make a WITH_SIZE_EXPR. */
3699 size = unshare_expr (size);
3700 size = SUBSTITUTE_PLACEHOLDER_IN_EXPR (size, expr);
3701 *expr_p = build2 (WITH_SIZE_EXPR, type, expr, size);
3704 /* Helper for gimplify_call_expr. Gimplify a single argument *ARG_P
3705 Store any side-effects in PRE_P. CALL_LOCATION is the location of
3706 the CALL_EXPR. If ALLOW_SSA is set the actual parameter may be
3707 gimplified to an SSA name. */
3709 enum gimplify_status
3710 gimplify_arg (tree *arg_p, gimple_seq *pre_p, location_t call_location,
3711 bool allow_ssa)
3713 bool (*test) (tree);
3714 fallback_t fb;
3716 /* In general, we allow lvalues for function arguments to avoid
3717 extra overhead of copying large aggregates out of even larger
3718 aggregates into temporaries only to copy the temporaries to
3719 the argument list. Make optimizers happy by pulling out to
3720 temporaries those types that fit in registers. */
3721 if (is_gimple_reg_type (TREE_TYPE (*arg_p)))
3722 test = is_gimple_val, fb = fb_rvalue;
3723 else
3725 test = is_gimple_lvalue, fb = fb_either;
3726 /* Also strip a TARGET_EXPR that would force an extra copy. */
3727 if (TREE_CODE (*arg_p) == TARGET_EXPR)
3729 tree init = TARGET_EXPR_INITIAL (*arg_p);
3730 if (init
3731 && !VOID_TYPE_P (TREE_TYPE (init)))
3732 *arg_p = init;
3736 /* If this is a variable sized type, we must remember the size. */
3737 maybe_with_size_expr (arg_p);
3739 /* FIXME diagnostics: This will mess up gcc.dg/Warray-bounds.c. */
3740 /* Make sure arguments have the same location as the function call
3741 itself. */
3742 protected_set_expr_location (*arg_p, call_location);
3744 /* There is a sequence point before a function call. Side effects in
3745 the argument list must occur before the actual call. So, when
3746 gimplifying arguments, force gimplify_expr to use an internal
3747 post queue which is then appended to the end of PRE_P. */
3748 return gimplify_expr (arg_p, pre_p, NULL, test, fb, allow_ssa);
3751 /* Don't fold inside offloading or taskreg regions: it can break code by
3752 adding decl references that weren't in the source. We'll do it during
3753 omplower pass instead. */
3755 static bool
3756 maybe_fold_stmt (gimple_stmt_iterator *gsi)
3758 struct gimplify_omp_ctx *ctx;
3759 for (ctx = gimplify_omp_ctxp; ctx; ctx = ctx->outer_context)
3760 if ((ctx->region_type & (ORT_TARGET | ORT_PARALLEL | ORT_TASK)) != 0)
3761 return false;
3762 else if ((ctx->region_type & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
3763 return false;
3764 /* Delay folding of builtins until the IL is in consistent state
3765 so the diagnostic machinery can do a better job. */
3766 if (gimple_call_builtin_p (gsi_stmt (*gsi)))
3767 return false;
3768 return fold_stmt (gsi);
3771 /* Gimplify the CALL_EXPR node *EXPR_P into the GIMPLE sequence PRE_P.
3772 WANT_VALUE is true if the result of the call is desired. */
3774 static enum gimplify_status
3775 gimplify_call_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
3777 tree fndecl, parms, p, fnptrtype;
3778 enum gimplify_status ret;
3779 int i, nargs;
3780 gcall *call;
3781 bool builtin_va_start_p = false;
3782 location_t loc = EXPR_LOCATION (*expr_p);
3784 gcc_assert (TREE_CODE (*expr_p) == CALL_EXPR);
3786 /* For reliable diagnostics during inlining, it is necessary that
3787 every call_expr be annotated with file and line. */
3788 if (! EXPR_HAS_LOCATION (*expr_p))
3789 SET_EXPR_LOCATION (*expr_p, input_location);
3791 /* Gimplify internal functions created in the FEs. */
3792 if (CALL_EXPR_FN (*expr_p) == NULL_TREE)
3794 if (want_value)
3795 return GS_ALL_DONE;
3797 nargs = call_expr_nargs (*expr_p);
3798 enum internal_fn ifn = CALL_EXPR_IFN (*expr_p);
3799 auto_vec<tree> vargs (nargs);
3801 if (ifn == IFN_ASSUME)
3803 if (simple_condition_p (CALL_EXPR_ARG (*expr_p, 0)))
3805 /* If the [[assume (cond)]]; condition is simple
3806 enough and can be evaluated unconditionally
3807 without side-effects, expand it as
3808 if (!cond) __builtin_unreachable (); */
3809 tree fndecl = builtin_decl_explicit (BUILT_IN_UNREACHABLE);
3810 *expr_p = build3 (COND_EXPR, void_type_node,
3811 CALL_EXPR_ARG (*expr_p, 0), void_node,
3812 build_call_expr_loc (EXPR_LOCATION (*expr_p),
3813 fndecl, 0));
3814 return GS_OK;
3816 /* If not optimizing, ignore the assumptions. */
3817 if (!optimize || seen_error ())
3819 *expr_p = NULL_TREE;
3820 return GS_ALL_DONE;
3822 /* Temporarily, until gimple lowering, transform
3823 .ASSUME (cond);
3824 into:
3825 [[assume (guard)]]
3827 guard = cond;
3829 such that gimple lowering can outline the condition into
3830 a separate function easily. */
3831 tree guard = create_tmp_var (boolean_type_node);
3832 *expr_p = build2 (MODIFY_EXPR, void_type_node, guard,
3833 gimple_boolify (CALL_EXPR_ARG (*expr_p, 0)));
3834 *expr_p = build3 (BIND_EXPR, void_type_node, NULL, *expr_p, NULL);
3835 push_gimplify_context ();
3836 gimple_seq body = NULL;
3837 gimple *g = gimplify_and_return_first (*expr_p, &body);
3838 pop_gimplify_context (g);
3839 g = gimple_build_assume (guard, body);
3840 gimple_set_location (g, loc);
3841 gimplify_seq_add_stmt (pre_p, g);
3842 *expr_p = NULL_TREE;
3843 return GS_ALL_DONE;
3846 for (i = 0; i < nargs; i++)
3848 gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
3849 EXPR_LOCATION (*expr_p));
3850 vargs.quick_push (CALL_EXPR_ARG (*expr_p, i));
3853 gcall *call = gimple_build_call_internal_vec (ifn, vargs);
3854 gimple_call_set_nothrow (call, TREE_NOTHROW (*expr_p));
3855 gimplify_seq_add_stmt (pre_p, call);
3856 return GS_ALL_DONE;
3859 /* This may be a call to a builtin function.
3861 Builtin function calls may be transformed into different
3862 (and more efficient) builtin function calls under certain
3863 circumstances. Unfortunately, gimplification can muck things
3864 up enough that the builtin expanders are not aware that certain
3865 transformations are still valid.
3867 So we attempt transformation/gimplification of the call before
3868 we gimplify the CALL_EXPR. At this time we do not manage to
3869 transform all calls in the same manner as the expanders do, but
3870 we do transform most of them. */
3871 fndecl = get_callee_fndecl (*expr_p);
3872 if (fndecl && fndecl_built_in_p (fndecl, BUILT_IN_NORMAL))
3873 switch (DECL_FUNCTION_CODE (fndecl))
3875 CASE_BUILT_IN_ALLOCA:
3876 /* If the call has been built for a variable-sized object, then we
3877 want to restore the stack level when the enclosing BIND_EXPR is
3878 exited to reclaim the allocated space; otherwise, we precisely
3879 need to do the opposite and preserve the latest stack level. */
3880 if (CALL_ALLOCA_FOR_VAR_P (*expr_p))
3881 gimplify_ctxp->save_stack = true;
3882 else
3883 gimplify_ctxp->keep_stack = true;
3884 break;
3886 case BUILT_IN_VA_START:
3888 builtin_va_start_p = true;
3889 if (call_expr_nargs (*expr_p) < 2)
3891 error ("too few arguments to function %<va_start%>");
3892 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
3893 return GS_OK;
3896 if (fold_builtin_next_arg (*expr_p, true))
3898 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
3899 return GS_OK;
3901 break;
3904 case BUILT_IN_EH_RETURN:
3905 cfun->calls_eh_return = true;
3906 break;
3908 case BUILT_IN_CLEAR_PADDING:
3909 if (call_expr_nargs (*expr_p) == 1)
3911 /* Remember the original type of the argument in an internal
3912 dummy second argument, as in GIMPLE pointer conversions are
3913 useless. Also mark this call as not for automatic
3914 initialization in the internal dummy third argument. */
3915 p = CALL_EXPR_ARG (*expr_p, 0);
3916 *expr_p
3917 = build_call_expr_loc (EXPR_LOCATION (*expr_p), fndecl, 2, p,
3918 build_zero_cst (TREE_TYPE (p)));
3919 return GS_OK;
3921 break;
3923 default:
3926 if (fndecl && fndecl_built_in_p (fndecl))
3928 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
3929 if (new_tree && new_tree != *expr_p)
3931 /* There was a transformation of this call which computes the
3932 same value, but in a more efficient way. Return and try
3933 again. */
3934 *expr_p = new_tree;
3935 return GS_OK;
3939 /* Remember the original function pointer type. */
3940 fnptrtype = TREE_TYPE (CALL_EXPR_FN (*expr_p));
3942 if (flag_openmp
3943 && fndecl
3944 && cfun
3945 && (cfun->curr_properties & PROP_gimple_any) == 0)
3947 tree variant = omp_resolve_declare_variant (fndecl);
3948 if (variant != fndecl)
3949 CALL_EXPR_FN (*expr_p) = build1 (ADDR_EXPR, fnptrtype, variant);
3952 /* There is a sequence point before the call, so any side effects in
3953 the calling expression must occur before the actual call. Force
3954 gimplify_expr to use an internal post queue. */
3955 ret = gimplify_expr (&CALL_EXPR_FN (*expr_p), pre_p, NULL,
3956 is_gimple_call_addr, fb_rvalue);
3958 if (ret == GS_ERROR)
3959 return GS_ERROR;
3961 nargs = call_expr_nargs (*expr_p);
3963 /* Get argument types for verification. */
3964 fndecl = get_callee_fndecl (*expr_p);
3965 parms = NULL_TREE;
3966 if (fndecl)
3967 parms = TYPE_ARG_TYPES (TREE_TYPE (fndecl));
3968 else
3969 parms = TYPE_ARG_TYPES (TREE_TYPE (fnptrtype));
3971 if (fndecl && DECL_ARGUMENTS (fndecl))
3972 p = DECL_ARGUMENTS (fndecl);
3973 else if (parms)
3974 p = parms;
3975 else
3976 p = NULL_TREE;
3977 for (i = 0; i < nargs && p; i++, p = TREE_CHAIN (p))
3980 /* If the last argument is __builtin_va_arg_pack () and it is not
3981 passed as a named argument, decrease the number of CALL_EXPR
3982 arguments and set instead the CALL_EXPR_VA_ARG_PACK flag. */
3983 if (!p
3984 && i < nargs
3985 && TREE_CODE (CALL_EXPR_ARG (*expr_p, nargs - 1)) == CALL_EXPR)
3987 tree last_arg = CALL_EXPR_ARG (*expr_p, nargs - 1);
3988 tree last_arg_fndecl = get_callee_fndecl (last_arg);
3990 if (last_arg_fndecl
3991 && fndecl_built_in_p (last_arg_fndecl, BUILT_IN_VA_ARG_PACK))
3993 tree call = *expr_p;
3995 --nargs;
3996 *expr_p = build_call_array_loc (loc, TREE_TYPE (call),
3997 CALL_EXPR_FN (call),
3998 nargs, CALL_EXPR_ARGP (call));
4000 /* Copy all CALL_EXPR flags, location and block, except
4001 CALL_EXPR_VA_ARG_PACK flag. */
4002 CALL_EXPR_STATIC_CHAIN (*expr_p) = CALL_EXPR_STATIC_CHAIN (call);
4003 CALL_EXPR_TAILCALL (*expr_p) = CALL_EXPR_TAILCALL (call);
4004 CALL_EXPR_RETURN_SLOT_OPT (*expr_p)
4005 = CALL_EXPR_RETURN_SLOT_OPT (call);
4006 CALL_FROM_THUNK_P (*expr_p) = CALL_FROM_THUNK_P (call);
4007 SET_EXPR_LOCATION (*expr_p, EXPR_LOCATION (call));
4009 /* Set CALL_EXPR_VA_ARG_PACK. */
4010 CALL_EXPR_VA_ARG_PACK (*expr_p) = 1;
4014 /* If the call returns twice then after building the CFG the call
4015 argument computations will no longer dominate the call because
4016 we add an abnormal incoming edge to the call. So do not use SSA
4017 vars there. */
4018 bool returns_twice = call_expr_flags (*expr_p) & ECF_RETURNS_TWICE;
4020 /* Gimplify the function arguments. */
4021 if (nargs > 0)
4023 for (i = (PUSH_ARGS_REVERSED ? nargs - 1 : 0);
4024 PUSH_ARGS_REVERSED ? i >= 0 : i < nargs;
4025 PUSH_ARGS_REVERSED ? i-- : i++)
4027 enum gimplify_status t;
4029 /* Avoid gimplifying the second argument to va_start, which needs to
4030 be the plain PARM_DECL. */
4031 if ((i != 1) || !builtin_va_start_p)
4033 t = gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
4034 EXPR_LOCATION (*expr_p), ! returns_twice);
4036 if (t == GS_ERROR)
4037 ret = GS_ERROR;
4042 /* Gimplify the static chain. */
4043 if (CALL_EXPR_STATIC_CHAIN (*expr_p))
4045 if (fndecl && !DECL_STATIC_CHAIN (fndecl))
4046 CALL_EXPR_STATIC_CHAIN (*expr_p) = NULL;
4047 else
4049 enum gimplify_status t;
4050 t = gimplify_arg (&CALL_EXPR_STATIC_CHAIN (*expr_p), pre_p,
4051 EXPR_LOCATION (*expr_p), ! returns_twice);
4052 if (t == GS_ERROR)
4053 ret = GS_ERROR;
4057 /* Verify the function result. */
4058 if (want_value && fndecl
4059 && VOID_TYPE_P (TREE_TYPE (TREE_TYPE (fnptrtype))))
4061 error_at (loc, "using result of function returning %<void%>");
4062 ret = GS_ERROR;
4065 /* Try this again in case gimplification exposed something. */
4066 if (ret != GS_ERROR)
4068 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
4070 if (new_tree && new_tree != *expr_p)
4072 /* There was a transformation of this call which computes the
4073 same value, but in a more efficient way. Return and try
4074 again. */
4075 *expr_p = new_tree;
4076 return GS_OK;
4079 else
4081 *expr_p = error_mark_node;
4082 return GS_ERROR;
4085 /* If the function is "const" or "pure", then clear TREE_SIDE_EFFECTS on its
4086 decl. This allows us to eliminate redundant or useless
4087 calls to "const" functions. */
4088 if (TREE_CODE (*expr_p) == CALL_EXPR)
4090 int flags = call_expr_flags (*expr_p);
4091 if (flags & (ECF_CONST | ECF_PURE)
4092 /* An infinite loop is considered a side effect. */
4093 && !(flags & (ECF_LOOPING_CONST_OR_PURE)))
4094 TREE_SIDE_EFFECTS (*expr_p) = 0;
4097 /* If the value is not needed by the caller, emit a new GIMPLE_CALL
4098 and clear *EXPR_P. Otherwise, leave *EXPR_P in its gimplified
4099 form and delegate the creation of a GIMPLE_CALL to
4100 gimplify_modify_expr. This is always possible because when
4101 WANT_VALUE is true, the caller wants the result of this call into
4102 a temporary, which means that we will emit an INIT_EXPR in
4103 internal_get_tmp_var which will then be handled by
4104 gimplify_modify_expr. */
4105 if (!want_value)
4107 /* The CALL_EXPR in *EXPR_P is already in GIMPLE form, so all we
4108 have to do is replicate it as a GIMPLE_CALL tuple. */
4109 gimple_stmt_iterator gsi;
4110 call = gimple_build_call_from_tree (*expr_p, fnptrtype);
4111 notice_special_calls (call);
4112 gimplify_seq_add_stmt (pre_p, call);
4113 gsi = gsi_last (*pre_p);
4114 maybe_fold_stmt (&gsi);
4115 *expr_p = NULL_TREE;
4117 else
4118 /* Remember the original function type. */
4119 CALL_EXPR_FN (*expr_p) = build1 (NOP_EXPR, fnptrtype,
4120 CALL_EXPR_FN (*expr_p));
4122 return ret;
4125 /* Handle shortcut semantics in the predicate operand of a COND_EXPR by
4126 rewriting it into multiple COND_EXPRs, and possibly GOTO_EXPRs.
4128 TRUE_LABEL_P and FALSE_LABEL_P point to the labels to jump to if the
4129 condition is true or false, respectively. If null, we should generate
4130 our own to skip over the evaluation of this specific expression.
4132 LOCUS is the source location of the COND_EXPR.
4134 This function is the tree equivalent of do_jump.
4136 shortcut_cond_r should only be called by shortcut_cond_expr. */
4138 static tree
4139 shortcut_cond_r (tree pred, tree *true_label_p, tree *false_label_p,
4140 location_t locus)
4142 tree local_label = NULL_TREE;
4143 tree t, expr = NULL;
4145 /* OK, it's not a simple case; we need to pull apart the COND_EXPR to
4146 retain the shortcut semantics. Just insert the gotos here;
4147 shortcut_cond_expr will append the real blocks later. */
4148 if (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
4150 location_t new_locus;
4152 /* Turn if (a && b) into
4154 if (a); else goto no;
4155 if (b) goto yes; else goto no;
4156 (no:) */
4158 if (false_label_p == NULL)
4159 false_label_p = &local_label;
4161 /* Keep the original source location on the first 'if'. */
4162 t = shortcut_cond_r (TREE_OPERAND (pred, 0), NULL, false_label_p, locus);
4163 append_to_statement_list (t, &expr);
4165 /* Set the source location of the && on the second 'if'. */
4166 new_locus = rexpr_location (pred, locus);
4167 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
4168 new_locus);
4169 append_to_statement_list (t, &expr);
4171 else if (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
4173 location_t new_locus;
4175 /* Turn if (a || b) into
4177 if (a) goto yes;
4178 if (b) goto yes; else goto no;
4179 (yes:) */
4181 if (true_label_p == NULL)
4182 true_label_p = &local_label;
4184 /* Keep the original source location on the first 'if'. */
4185 t = shortcut_cond_r (TREE_OPERAND (pred, 0), true_label_p, NULL, locus);
4186 append_to_statement_list (t, &expr);
4188 /* Set the source location of the || on the second 'if'. */
4189 new_locus = rexpr_location (pred, locus);
4190 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
4191 new_locus);
4192 append_to_statement_list (t, &expr);
4194 else if (TREE_CODE (pred) == COND_EXPR
4195 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 1)))
4196 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 2))))
4198 location_t new_locus;
4200 /* As long as we're messing with gotos, turn if (a ? b : c) into
4201 if (a)
4202 if (b) goto yes; else goto no;
4203 else
4204 if (c) goto yes; else goto no;
4206 Don't do this if one of the arms has void type, which can happen
4207 in C++ when the arm is throw. */
4209 /* Keep the original source location on the first 'if'. Set the source
4210 location of the ? on the second 'if'. */
4211 new_locus = rexpr_location (pred, locus);
4212 expr = build3 (COND_EXPR, void_type_node, TREE_OPERAND (pred, 0),
4213 shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p,
4214 false_label_p, locus),
4215 shortcut_cond_r (TREE_OPERAND (pred, 2), true_label_p,
4216 false_label_p, new_locus));
4218 else
4220 expr = build3 (COND_EXPR, void_type_node, pred,
4221 build_and_jump (true_label_p),
4222 build_and_jump (false_label_p));
4223 SET_EXPR_LOCATION (expr, locus);
4226 if (local_label)
4228 t = build1 (LABEL_EXPR, void_type_node, local_label);
4229 append_to_statement_list (t, &expr);
4232 return expr;
4235 /* If EXPR is a GOTO_EXPR, return it. If it is a STATEMENT_LIST, skip
4236 any of its leading DEBUG_BEGIN_STMTS and recurse on the subsequent
4237 statement, if it is the last one. Otherwise, return NULL. */
4239 static tree
4240 find_goto (tree expr)
4242 if (!expr)
4243 return NULL_TREE;
4245 if (TREE_CODE (expr) == GOTO_EXPR)
4246 return expr;
4248 if (TREE_CODE (expr) != STATEMENT_LIST)
4249 return NULL_TREE;
4251 tree_stmt_iterator i = tsi_start (expr);
4253 while (!tsi_end_p (i) && TREE_CODE (tsi_stmt (i)) == DEBUG_BEGIN_STMT)
4254 tsi_next (&i);
4256 if (!tsi_one_before_end_p (i))
4257 return NULL_TREE;
4259 return find_goto (tsi_stmt (i));
4262 /* Same as find_goto, except that it returns NULL if the destination
4263 is not a LABEL_DECL. */
4265 static inline tree
4266 find_goto_label (tree expr)
4268 tree dest = find_goto (expr);
4269 if (dest && TREE_CODE (GOTO_DESTINATION (dest)) == LABEL_DECL)
4270 return dest;
4271 return NULL_TREE;
4274 /* Given a conditional expression EXPR with short-circuit boolean
4275 predicates using TRUTH_ANDIF_EXPR or TRUTH_ORIF_EXPR, break the
4276 predicate apart into the equivalent sequence of conditionals. */
4278 static tree
4279 shortcut_cond_expr (tree expr)
4281 tree pred = TREE_OPERAND (expr, 0);
4282 tree then_ = TREE_OPERAND (expr, 1);
4283 tree else_ = TREE_OPERAND (expr, 2);
4284 tree true_label, false_label, end_label, t;
4285 tree *true_label_p;
4286 tree *false_label_p;
4287 bool emit_end, emit_false, jump_over_else;
4288 bool then_se = then_ && TREE_SIDE_EFFECTS (then_);
4289 bool else_se = else_ && TREE_SIDE_EFFECTS (else_);
4291 /* First do simple transformations. */
4292 if (!else_se)
4294 /* If there is no 'else', turn
4295 if (a && b) then c
4296 into
4297 if (a) if (b) then c. */
4298 while (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
4300 /* Keep the original source location on the first 'if'. */
4301 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
4302 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
4303 /* Set the source location of the && on the second 'if'. */
4304 if (rexpr_has_location (pred))
4305 SET_EXPR_LOCATION (expr, rexpr_location (pred));
4306 then_ = shortcut_cond_expr (expr);
4307 then_se = then_ && TREE_SIDE_EFFECTS (then_);
4308 pred = TREE_OPERAND (pred, 0);
4309 expr = build3 (COND_EXPR, void_type_node, pred, then_, NULL_TREE);
4310 SET_EXPR_LOCATION (expr, locus);
4314 if (!then_se)
4316 /* If there is no 'then', turn
4317 if (a || b); else d
4318 into
4319 if (a); else if (b); else d. */
4320 while (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
4322 /* Keep the original source location on the first 'if'. */
4323 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
4324 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
4325 /* Set the source location of the || on the second 'if'. */
4326 if (rexpr_has_location (pred))
4327 SET_EXPR_LOCATION (expr, rexpr_location (pred));
4328 else_ = shortcut_cond_expr (expr);
4329 else_se = else_ && TREE_SIDE_EFFECTS (else_);
4330 pred = TREE_OPERAND (pred, 0);
4331 expr = build3 (COND_EXPR, void_type_node, pred, NULL_TREE, else_);
4332 SET_EXPR_LOCATION (expr, locus);
4336 /* If we're done, great. */
4337 if (TREE_CODE (pred) != TRUTH_ANDIF_EXPR
4338 && TREE_CODE (pred) != TRUTH_ORIF_EXPR)
4339 return expr;
4341 /* Otherwise we need to mess with gotos. Change
4342 if (a) c; else d;
4344 if (a); else goto no;
4345 c; goto end;
4346 no: d; end:
4347 and recursively gimplify the condition. */
4349 true_label = false_label = end_label = NULL_TREE;
4351 /* If our arms just jump somewhere, hijack those labels so we don't
4352 generate jumps to jumps. */
4354 if (tree then_goto = find_goto_label (then_))
4356 true_label = GOTO_DESTINATION (then_goto);
4357 then_ = NULL;
4358 then_se = false;
4361 if (tree else_goto = find_goto_label (else_))
4363 false_label = GOTO_DESTINATION (else_goto);
4364 else_ = NULL;
4365 else_se = false;
4368 /* If we aren't hijacking a label for the 'then' branch, it falls through. */
4369 if (true_label)
4370 true_label_p = &true_label;
4371 else
4372 true_label_p = NULL;
4374 /* The 'else' branch also needs a label if it contains interesting code. */
4375 if (false_label || else_se)
4376 false_label_p = &false_label;
4377 else
4378 false_label_p = NULL;
4380 /* If there was nothing else in our arms, just forward the label(s). */
4381 if (!then_se && !else_se)
4382 return shortcut_cond_r (pred, true_label_p, false_label_p,
4383 EXPR_LOC_OR_LOC (expr, input_location));
4385 /* If our last subexpression already has a terminal label, reuse it. */
4386 if (else_se)
4387 t = expr_last (else_);
4388 else if (then_se)
4389 t = expr_last (then_);
4390 else
4391 t = NULL;
4392 if (t && TREE_CODE (t) == LABEL_EXPR)
4393 end_label = LABEL_EXPR_LABEL (t);
4395 /* If we don't care about jumping to the 'else' branch, jump to the end
4396 if the condition is false. */
4397 if (!false_label_p)
4398 false_label_p = &end_label;
4400 /* We only want to emit these labels if we aren't hijacking them. */
4401 emit_end = (end_label == NULL_TREE);
4402 emit_false = (false_label == NULL_TREE);
4404 /* We only emit the jump over the else clause if we have to--if the
4405 then clause may fall through. Otherwise we can wind up with a
4406 useless jump and a useless label at the end of gimplified code,
4407 which will cause us to think that this conditional as a whole
4408 falls through even if it doesn't. If we then inline a function
4409 which ends with such a condition, that can cause us to issue an
4410 inappropriate warning about control reaching the end of a
4411 non-void function. */
4412 jump_over_else = block_may_fallthru (then_);
4414 pred = shortcut_cond_r (pred, true_label_p, false_label_p,
4415 EXPR_LOC_OR_LOC (expr, input_location));
4417 expr = NULL;
4418 append_to_statement_list (pred, &expr);
4420 append_to_statement_list (then_, &expr);
4421 if (else_se)
4423 if (jump_over_else)
4425 tree last = expr_last (expr);
4426 t = build_and_jump (&end_label);
4427 if (rexpr_has_location (last))
4428 SET_EXPR_LOCATION (t, rexpr_location (last));
4429 append_to_statement_list (t, &expr);
4431 if (emit_false)
4433 t = build1 (LABEL_EXPR, void_type_node, false_label);
4434 append_to_statement_list (t, &expr);
4436 append_to_statement_list (else_, &expr);
4438 if (emit_end && end_label)
4440 t = build1 (LABEL_EXPR, void_type_node, end_label);
4441 append_to_statement_list (t, &expr);
4444 return expr;
4447 /* EXPR is used in a boolean context; make sure it has BOOLEAN_TYPE. */
4449 tree
4450 gimple_boolify (tree expr)
4452 tree type = TREE_TYPE (expr);
4453 location_t loc = EXPR_LOCATION (expr);
4455 if (TREE_CODE (expr) == NE_EXPR
4456 && TREE_CODE (TREE_OPERAND (expr, 0)) == CALL_EXPR
4457 && integer_zerop (TREE_OPERAND (expr, 1)))
4459 tree call = TREE_OPERAND (expr, 0);
4460 tree fn = get_callee_fndecl (call);
4462 /* For __builtin_expect ((long) (x), y) recurse into x as well
4463 if x is truth_value_p. */
4464 if (fn
4465 && fndecl_built_in_p (fn, BUILT_IN_EXPECT)
4466 && call_expr_nargs (call) == 2)
4468 tree arg = CALL_EXPR_ARG (call, 0);
4469 if (arg)
4471 if (TREE_CODE (arg) == NOP_EXPR
4472 && TREE_TYPE (arg) == TREE_TYPE (call))
4473 arg = TREE_OPERAND (arg, 0);
4474 if (truth_value_p (TREE_CODE (arg)))
4476 arg = gimple_boolify (arg);
4477 CALL_EXPR_ARG (call, 0)
4478 = fold_convert_loc (loc, TREE_TYPE (call), arg);
4484 switch (TREE_CODE (expr))
4486 case TRUTH_AND_EXPR:
4487 case TRUTH_OR_EXPR:
4488 case TRUTH_XOR_EXPR:
4489 case TRUTH_ANDIF_EXPR:
4490 case TRUTH_ORIF_EXPR:
4491 /* Also boolify the arguments of truth exprs. */
4492 TREE_OPERAND (expr, 1) = gimple_boolify (TREE_OPERAND (expr, 1));
4493 /* FALLTHRU */
4495 case TRUTH_NOT_EXPR:
4496 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
4498 /* These expressions always produce boolean results. */
4499 if (TREE_CODE (type) != BOOLEAN_TYPE)
4500 TREE_TYPE (expr) = boolean_type_node;
4501 return expr;
4503 case ANNOTATE_EXPR:
4504 switch ((enum annot_expr_kind) TREE_INT_CST_LOW (TREE_OPERAND (expr, 1)))
4506 case annot_expr_ivdep_kind:
4507 case annot_expr_unroll_kind:
4508 case annot_expr_no_vector_kind:
4509 case annot_expr_vector_kind:
4510 case annot_expr_parallel_kind:
4511 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
4512 if (TREE_CODE (type) != BOOLEAN_TYPE)
4513 TREE_TYPE (expr) = boolean_type_node;
4514 return expr;
4515 default:
4516 gcc_unreachable ();
4519 default:
4520 if (COMPARISON_CLASS_P (expr))
4522 /* These expressions always produce boolean results. */
4523 if (TREE_CODE (type) != BOOLEAN_TYPE)
4524 TREE_TYPE (expr) = boolean_type_node;
4525 return expr;
4527 /* Other expressions that get here must have boolean values, but
4528 might need to be converted to the appropriate mode. */
4529 if (TREE_CODE (type) == BOOLEAN_TYPE)
4530 return expr;
4531 return fold_convert_loc (loc, boolean_type_node, expr);
4535 /* Given a conditional expression *EXPR_P without side effects, gimplify
4536 its operands. New statements are inserted to PRE_P. */
4538 static enum gimplify_status
4539 gimplify_pure_cond_expr (tree *expr_p, gimple_seq *pre_p)
4541 tree expr = *expr_p, cond;
4542 enum gimplify_status ret, tret;
4543 enum tree_code code;
4545 cond = gimple_boolify (COND_EXPR_COND (expr));
4547 /* We need to handle && and || specially, as their gimplification
4548 creates pure cond_expr, thus leading to an infinite cycle otherwise. */
4549 code = TREE_CODE (cond);
4550 if (code == TRUTH_ANDIF_EXPR)
4551 TREE_SET_CODE (cond, TRUTH_AND_EXPR);
4552 else if (code == TRUTH_ORIF_EXPR)
4553 TREE_SET_CODE (cond, TRUTH_OR_EXPR);
4554 ret = gimplify_expr (&cond, pre_p, NULL, is_gimple_val, fb_rvalue);
4555 COND_EXPR_COND (*expr_p) = cond;
4557 tret = gimplify_expr (&COND_EXPR_THEN (expr), pre_p, NULL,
4558 is_gimple_val, fb_rvalue);
4559 ret = MIN (ret, tret);
4560 tret = gimplify_expr (&COND_EXPR_ELSE (expr), pre_p, NULL,
4561 is_gimple_val, fb_rvalue);
4563 return MIN (ret, tret);
4566 /* Return true if evaluating EXPR could trap.
4567 EXPR is GENERIC, while tree_could_trap_p can be called
4568 only on GIMPLE. */
4570 bool
4571 generic_expr_could_trap_p (tree expr)
4573 unsigned i, n;
4575 if (!expr || is_gimple_val (expr))
4576 return false;
4578 if (!EXPR_P (expr) || tree_could_trap_p (expr))
4579 return true;
4581 n = TREE_OPERAND_LENGTH (expr);
4582 for (i = 0; i < n; i++)
4583 if (generic_expr_could_trap_p (TREE_OPERAND (expr, i)))
4584 return true;
4586 return false;
4589 /* Convert the conditional expression pointed to by EXPR_P '(p) ? a : b;'
4590 into
4592 if (p) if (p)
4593 t1 = a; a;
4594 else or else
4595 t1 = b; b;
4598 The second form is used when *EXPR_P is of type void.
4600 PRE_P points to the list where side effects that must happen before
4601 *EXPR_P should be stored. */
4603 static enum gimplify_status
4604 gimplify_cond_expr (tree *expr_p, gimple_seq *pre_p, fallback_t fallback)
4606 tree expr = *expr_p;
4607 tree type = TREE_TYPE (expr);
4608 location_t loc = EXPR_LOCATION (expr);
4609 tree tmp, arm1, arm2;
4610 enum gimplify_status ret;
4611 tree label_true, label_false, label_cont;
4612 bool have_then_clause_p, have_else_clause_p;
4613 gcond *cond_stmt;
4614 enum tree_code pred_code;
4615 gimple_seq seq = NULL;
4617 /* If this COND_EXPR has a value, copy the values into a temporary within
4618 the arms. */
4619 if (!VOID_TYPE_P (type))
4621 tree then_ = TREE_OPERAND (expr, 1), else_ = TREE_OPERAND (expr, 2);
4622 tree result;
4624 /* If either an rvalue is ok or we do not require an lvalue, create the
4625 temporary. But we cannot do that if the type is addressable. */
4626 if (((fallback & fb_rvalue) || !(fallback & fb_lvalue))
4627 && !TREE_ADDRESSABLE (type))
4629 if (gimplify_ctxp->allow_rhs_cond_expr
4630 /* If either branch has side effects or could trap, it can't be
4631 evaluated unconditionally. */
4632 && !TREE_SIDE_EFFECTS (then_)
4633 && !generic_expr_could_trap_p (then_)
4634 && !TREE_SIDE_EFFECTS (else_)
4635 && !generic_expr_could_trap_p (else_))
4636 return gimplify_pure_cond_expr (expr_p, pre_p);
4638 tmp = create_tmp_var (type, "iftmp");
4639 result = tmp;
4642 /* Otherwise, only create and copy references to the values. */
4643 else
4645 type = build_pointer_type (type);
4647 if (!VOID_TYPE_P (TREE_TYPE (then_)))
4648 then_ = build_fold_addr_expr_loc (loc, then_);
4650 if (!VOID_TYPE_P (TREE_TYPE (else_)))
4651 else_ = build_fold_addr_expr_loc (loc, else_);
4653 expr
4654 = build3 (COND_EXPR, type, TREE_OPERAND (expr, 0), then_, else_);
4656 tmp = create_tmp_var (type, "iftmp");
4657 result = build_simple_mem_ref_loc (loc, tmp);
4660 /* Build the new then clause, `tmp = then_;'. But don't build the
4661 assignment if the value is void; in C++ it can be if it's a throw. */
4662 if (!VOID_TYPE_P (TREE_TYPE (then_)))
4663 TREE_OPERAND (expr, 1) = build2 (INIT_EXPR, type, tmp, then_);
4665 /* Similarly, build the new else clause, `tmp = else_;'. */
4666 if (!VOID_TYPE_P (TREE_TYPE (else_)))
4667 TREE_OPERAND (expr, 2) = build2 (INIT_EXPR, type, tmp, else_);
4669 TREE_TYPE (expr) = void_type_node;
4670 recalculate_side_effects (expr);
4672 /* Move the COND_EXPR to the prequeue. */
4673 gimplify_stmt (&expr, pre_p);
4675 *expr_p = result;
4676 return GS_ALL_DONE;
4679 /* Remove any COMPOUND_EXPR so the following cases will be caught. */
4680 STRIP_TYPE_NOPS (TREE_OPERAND (expr, 0));
4681 if (TREE_CODE (TREE_OPERAND (expr, 0)) == COMPOUND_EXPR)
4682 gimplify_compound_expr (&TREE_OPERAND (expr, 0), pre_p, true);
4684 /* Make sure the condition has BOOLEAN_TYPE. */
4685 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
4687 /* Break apart && and || conditions. */
4688 if (TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ANDIF_EXPR
4689 || TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ORIF_EXPR)
4691 expr = shortcut_cond_expr (expr);
4693 if (expr != *expr_p)
4695 *expr_p = expr;
4697 /* We can't rely on gimplify_expr to re-gimplify the expanded
4698 form properly, as cleanups might cause the target labels to be
4699 wrapped in a TRY_FINALLY_EXPR. To prevent that, we need to
4700 set up a conditional context. */
4701 gimple_push_condition ();
4702 gimplify_stmt (expr_p, &seq);
4703 gimple_pop_condition (pre_p);
4704 gimple_seq_add_seq (pre_p, seq);
4706 return GS_ALL_DONE;
4710 /* Now do the normal gimplification. */
4712 /* Gimplify condition. */
4713 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, NULL,
4714 is_gimple_condexpr_for_cond, fb_rvalue);
4715 if (ret == GS_ERROR)
4716 return GS_ERROR;
4717 gcc_assert (TREE_OPERAND (expr, 0) != NULL_TREE);
4719 gimple_push_condition ();
4721 have_then_clause_p = have_else_clause_p = false;
4722 label_true = find_goto_label (TREE_OPERAND (expr, 1));
4723 if (label_true
4724 && DECL_CONTEXT (GOTO_DESTINATION (label_true)) == current_function_decl
4725 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
4726 have different locations, otherwise we end up with incorrect
4727 location information on the branches. */
4728 && (optimize
4729 || !EXPR_HAS_LOCATION (expr)
4730 || !rexpr_has_location (label_true)
4731 || EXPR_LOCATION (expr) == rexpr_location (label_true)))
4733 have_then_clause_p = true;
4734 label_true = GOTO_DESTINATION (label_true);
4736 else
4737 label_true = create_artificial_label (UNKNOWN_LOCATION);
4738 label_false = find_goto_label (TREE_OPERAND (expr, 2));
4739 if (label_false
4740 && DECL_CONTEXT (GOTO_DESTINATION (label_false)) == current_function_decl
4741 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
4742 have different locations, otherwise we end up with incorrect
4743 location information on the branches. */
4744 && (optimize
4745 || !EXPR_HAS_LOCATION (expr)
4746 || !rexpr_has_location (label_false)
4747 || EXPR_LOCATION (expr) == rexpr_location (label_false)))
4749 have_else_clause_p = true;
4750 label_false = GOTO_DESTINATION (label_false);
4752 else
4753 label_false = create_artificial_label (UNKNOWN_LOCATION);
4755 gimple_cond_get_ops_from_tree (COND_EXPR_COND (expr), &pred_code, &arm1,
4756 &arm2);
4757 cond_stmt = gimple_build_cond (pred_code, arm1, arm2, label_true,
4758 label_false);
4759 gimple_set_location (cond_stmt, EXPR_LOCATION (expr));
4760 copy_warning (cond_stmt, COND_EXPR_COND (expr));
4761 gimplify_seq_add_stmt (&seq, cond_stmt);
4762 gimple_stmt_iterator gsi = gsi_last (seq);
4763 maybe_fold_stmt (&gsi);
4765 label_cont = NULL_TREE;
4766 if (!have_then_clause_p)
4768 /* For if (...) {} else { code; } put label_true after
4769 the else block. */
4770 if (TREE_OPERAND (expr, 1) == NULL_TREE
4771 && !have_else_clause_p
4772 && TREE_OPERAND (expr, 2) != NULL_TREE)
4774 /* For if (0) {} else { code; } tell -Wimplicit-fallthrough
4775 handling that label_cont == label_true can be only reached
4776 through fallthrough from { code; }. */
4777 if (integer_zerop (COND_EXPR_COND (expr)))
4778 UNUSED_LABEL_P (label_true) = 1;
4779 label_cont = label_true;
4781 else
4783 bool then_side_effects
4784 = (TREE_OPERAND (expr, 1)
4785 && TREE_SIDE_EFFECTS (TREE_OPERAND (expr, 1)));
4786 gimplify_seq_add_stmt (&seq, gimple_build_label (label_true));
4787 have_then_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 1), &seq);
4788 /* For if (...) { code; } else {} or
4789 if (...) { code; } else goto label; or
4790 if (...) { code; return; } else { ... }
4791 label_cont isn't needed. */
4792 if (!have_else_clause_p
4793 && TREE_OPERAND (expr, 2) != NULL_TREE
4794 && gimple_seq_may_fallthru (seq))
4796 gimple *g;
4797 label_cont = create_artificial_label (UNKNOWN_LOCATION);
4799 /* For if (0) { non-side-effect-code } else { code }
4800 tell -Wimplicit-fallthrough handling that label_cont can
4801 be only reached through fallthrough from { code }. */
4802 if (integer_zerop (COND_EXPR_COND (expr)))
4804 UNUSED_LABEL_P (label_true) = 1;
4805 if (!then_side_effects)
4806 UNUSED_LABEL_P (label_cont) = 1;
4809 g = gimple_build_goto (label_cont);
4811 /* GIMPLE_COND's are very low level; they have embedded
4812 gotos. This particular embedded goto should not be marked
4813 with the location of the original COND_EXPR, as it would
4814 correspond to the COND_EXPR's condition, not the ELSE or the
4815 THEN arms. To avoid marking it with the wrong location, flag
4816 it as "no location". */
4817 gimple_set_do_not_emit_location (g);
4819 gimplify_seq_add_stmt (&seq, g);
4823 if (!have_else_clause_p)
4825 /* For if (1) { code } or if (1) { code } else { non-side-effect-code }
4826 tell -Wimplicit-fallthrough handling that label_false can be only
4827 reached through fallthrough from { code }. */
4828 if (integer_nonzerop (COND_EXPR_COND (expr))
4829 && (TREE_OPERAND (expr, 2) == NULL_TREE
4830 || !TREE_SIDE_EFFECTS (TREE_OPERAND (expr, 2))))
4831 UNUSED_LABEL_P (label_false) = 1;
4832 gimplify_seq_add_stmt (&seq, gimple_build_label (label_false));
4833 have_else_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 2), &seq);
4835 if (label_cont)
4836 gimplify_seq_add_stmt (&seq, gimple_build_label (label_cont));
4838 gimple_pop_condition (pre_p);
4839 gimple_seq_add_seq (pre_p, seq);
4841 if (ret == GS_ERROR)
4842 ; /* Do nothing. */
4843 else if (have_then_clause_p || have_else_clause_p)
4844 ret = GS_ALL_DONE;
4845 else
4847 /* Both arms are empty; replace the COND_EXPR with its predicate. */
4848 expr = TREE_OPERAND (expr, 0);
4849 gimplify_stmt (&expr, pre_p);
4852 *expr_p = NULL;
4853 return ret;
4856 /* Prepare the node pointed to by EXPR_P, an is_gimple_addressable expression,
4857 to be marked addressable.
4859 We cannot rely on such an expression being directly markable if a temporary
4860 has been created by the gimplification. In this case, we create another
4861 temporary and initialize it with a copy, which will become a store after we
4862 mark it addressable. This can happen if the front-end passed us something
4863 that it could not mark addressable yet, like a Fortran pass-by-reference
4864 parameter (int) floatvar. */
4866 static void
4867 prepare_gimple_addressable (tree *expr_p, gimple_seq *seq_p)
4869 while (handled_component_p (*expr_p))
4870 expr_p = &TREE_OPERAND (*expr_p, 0);
4872 /* Do not allow an SSA name as the temporary. */
4873 if (is_gimple_reg (*expr_p))
4874 *expr_p = internal_get_tmp_var (*expr_p, seq_p, NULL, false, false, true);
4877 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
4878 a call to __builtin_memcpy. */
4880 static enum gimplify_status
4881 gimplify_modify_expr_to_memcpy (tree *expr_p, tree size, bool want_value,
4882 gimple_seq *seq_p)
4884 tree t, to, to_ptr, from, from_ptr;
4885 gcall *gs;
4886 location_t loc = EXPR_LOCATION (*expr_p);
4888 to = TREE_OPERAND (*expr_p, 0);
4889 from = TREE_OPERAND (*expr_p, 1);
4891 /* Mark the RHS addressable. Beware that it may not be possible to do so
4892 directly if a temporary has been created by the gimplification. */
4893 prepare_gimple_addressable (&from, seq_p);
4895 mark_addressable (from);
4896 from_ptr = build_fold_addr_expr_loc (loc, from);
4897 gimplify_arg (&from_ptr, seq_p, loc);
4899 mark_addressable (to);
4900 to_ptr = build_fold_addr_expr_loc (loc, to);
4901 gimplify_arg (&to_ptr, seq_p, loc);
4903 t = builtin_decl_implicit (BUILT_IN_MEMCPY);
4905 gs = gimple_build_call (t, 3, to_ptr, from_ptr, size);
4906 gimple_call_set_alloca_for_var (gs, true);
4908 if (want_value)
4910 /* tmp = memcpy() */
4911 t = create_tmp_var (TREE_TYPE (to_ptr));
4912 gimple_call_set_lhs (gs, t);
4913 gimplify_seq_add_stmt (seq_p, gs);
4915 *expr_p = build_simple_mem_ref (t);
4916 return GS_ALL_DONE;
4919 gimplify_seq_add_stmt (seq_p, gs);
4920 *expr_p = NULL;
4921 return GS_ALL_DONE;
4924 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
4925 a call to __builtin_memset. In this case we know that the RHS is
4926 a CONSTRUCTOR with an empty element list. */
4928 static enum gimplify_status
4929 gimplify_modify_expr_to_memset (tree *expr_p, tree size, bool want_value,
4930 gimple_seq *seq_p)
4932 tree t, from, to, to_ptr;
4933 gcall *gs;
4934 location_t loc = EXPR_LOCATION (*expr_p);
4936 /* Assert our assumptions, to abort instead of producing wrong code
4937 silently if they are not met. Beware that the RHS CONSTRUCTOR might
4938 not be immediately exposed. */
4939 from = TREE_OPERAND (*expr_p, 1);
4940 if (TREE_CODE (from) == WITH_SIZE_EXPR)
4941 from = TREE_OPERAND (from, 0);
4943 gcc_assert (TREE_CODE (from) == CONSTRUCTOR
4944 && vec_safe_is_empty (CONSTRUCTOR_ELTS (from)));
4946 /* Now proceed. */
4947 to = TREE_OPERAND (*expr_p, 0);
4949 to_ptr = build_fold_addr_expr_loc (loc, to);
4950 gimplify_arg (&to_ptr, seq_p, loc);
4951 t = builtin_decl_implicit (BUILT_IN_MEMSET);
4953 gs = gimple_build_call (t, 3, to_ptr, integer_zero_node, size);
4955 if (want_value)
4957 /* tmp = memset() */
4958 t = create_tmp_var (TREE_TYPE (to_ptr));
4959 gimple_call_set_lhs (gs, t);
4960 gimplify_seq_add_stmt (seq_p, gs);
4962 *expr_p = build1 (INDIRECT_REF, TREE_TYPE (to), t);
4963 return GS_ALL_DONE;
4966 gimplify_seq_add_stmt (seq_p, gs);
4967 *expr_p = NULL;
4968 return GS_ALL_DONE;
4971 /* A subroutine of gimplify_init_ctor_preeval. Called via walk_tree,
4972 determine, cautiously, if a CONSTRUCTOR overlaps the lhs of an
4973 assignment. Return non-null if we detect a potential overlap. */
4975 struct gimplify_init_ctor_preeval_data
4977 /* The base decl of the lhs object. May be NULL, in which case we
4978 have to assume the lhs is indirect. */
4979 tree lhs_base_decl;
4981 /* The alias set of the lhs object. */
4982 alias_set_type lhs_alias_set;
4985 static tree
4986 gimplify_init_ctor_preeval_1 (tree *tp, int *walk_subtrees, void *xdata)
4988 struct gimplify_init_ctor_preeval_data *data
4989 = (struct gimplify_init_ctor_preeval_data *) xdata;
4990 tree t = *tp;
4992 /* If we find the base object, obviously we have overlap. */
4993 if (data->lhs_base_decl == t)
4994 return t;
4996 /* If the constructor component is indirect, determine if we have a
4997 potential overlap with the lhs. The only bits of information we
4998 have to go on at this point are addressability and alias sets. */
4999 if ((INDIRECT_REF_P (t)
5000 || TREE_CODE (t) == MEM_REF)
5001 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
5002 && alias_sets_conflict_p (data->lhs_alias_set, get_alias_set (t)))
5003 return t;
5005 /* If the constructor component is a call, determine if it can hide a
5006 potential overlap with the lhs through an INDIRECT_REF like above.
5007 ??? Ugh - this is completely broken. In fact this whole analysis
5008 doesn't look conservative. */
5009 if (TREE_CODE (t) == CALL_EXPR)
5011 tree type, fntype = TREE_TYPE (TREE_TYPE (CALL_EXPR_FN (t)));
5013 for (type = TYPE_ARG_TYPES (fntype); type; type = TREE_CHAIN (type))
5014 if (POINTER_TYPE_P (TREE_VALUE (type))
5015 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
5016 && alias_sets_conflict_p (data->lhs_alias_set,
5017 get_alias_set
5018 (TREE_TYPE (TREE_VALUE (type)))))
5019 return t;
5022 if (IS_TYPE_OR_DECL_P (t))
5023 *walk_subtrees = 0;
5024 return NULL;
5027 /* A subroutine of gimplify_init_constructor. Pre-evaluate EXPR,
5028 force values that overlap with the lhs (as described by *DATA)
5029 into temporaries. */
5031 static void
5032 gimplify_init_ctor_preeval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
5033 struct gimplify_init_ctor_preeval_data *data)
5035 enum gimplify_status one;
5037 /* If the value is constant, then there's nothing to pre-evaluate. */
5038 if (TREE_CONSTANT (*expr_p))
5040 /* Ensure it does not have side effects, it might contain a reference to
5041 the object we're initializing. */
5042 gcc_assert (!TREE_SIDE_EFFECTS (*expr_p));
5043 return;
5046 /* If the type has non-trivial constructors, we can't pre-evaluate. */
5047 if (TREE_ADDRESSABLE (TREE_TYPE (*expr_p)))
5048 return;
5050 /* Recurse for nested constructors. */
5051 if (TREE_CODE (*expr_p) == CONSTRUCTOR)
5053 unsigned HOST_WIDE_INT ix;
5054 constructor_elt *ce;
5055 vec<constructor_elt, va_gc> *v = CONSTRUCTOR_ELTS (*expr_p);
5057 FOR_EACH_VEC_SAFE_ELT (v, ix, ce)
5058 gimplify_init_ctor_preeval (&ce->value, pre_p, post_p, data);
5060 return;
5063 /* If this is a variable sized type, we must remember the size. */
5064 maybe_with_size_expr (expr_p);
5066 /* Gimplify the constructor element to something appropriate for the rhs
5067 of a MODIFY_EXPR. Given that we know the LHS is an aggregate, we know
5068 the gimplifier will consider this a store to memory. Doing this
5069 gimplification now means that we won't have to deal with complicated
5070 language-specific trees, nor trees like SAVE_EXPR that can induce
5071 exponential search behavior. */
5072 one = gimplify_expr (expr_p, pre_p, post_p, is_gimple_mem_rhs, fb_rvalue);
5073 if (one == GS_ERROR)
5075 *expr_p = NULL;
5076 return;
5079 /* If we gimplified to a bare decl, we can be sure that it doesn't overlap
5080 with the lhs, since "a = { .x=a }" doesn't make sense. This will
5081 always be true for all scalars, since is_gimple_mem_rhs insists on a
5082 temporary variable for them. */
5083 if (DECL_P (*expr_p))
5084 return;
5086 /* If this is of variable size, we have no choice but to assume it doesn't
5087 overlap since we can't make a temporary for it. */
5088 if (TREE_CODE (TYPE_SIZE (TREE_TYPE (*expr_p))) != INTEGER_CST)
5089 return;
5091 /* Otherwise, we must search for overlap ... */
5092 if (!walk_tree (expr_p, gimplify_init_ctor_preeval_1, data, NULL))
5093 return;
5095 /* ... and if found, force the value into a temporary. */
5096 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
5099 /* A subroutine of gimplify_init_ctor_eval. Create a loop for
5100 a RANGE_EXPR in a CONSTRUCTOR for an array.
5102 var = lower;
5103 loop_entry:
5104 object[var] = value;
5105 if (var == upper)
5106 goto loop_exit;
5107 var = var + 1;
5108 goto loop_entry;
5109 loop_exit:
5111 We increment var _after_ the loop exit check because we might otherwise
5112 fail if upper == TYPE_MAX_VALUE (type for upper).
5114 Note that we never have to deal with SAVE_EXPRs here, because this has
5115 already been taken care of for us, in gimplify_init_ctor_preeval(). */
5117 static void gimplify_init_ctor_eval (tree, vec<constructor_elt, va_gc> *,
5118 gimple_seq *, bool);
5120 static void
5121 gimplify_init_ctor_eval_range (tree object, tree lower, tree upper,
5122 tree value, tree array_elt_type,
5123 gimple_seq *pre_p, bool cleared)
5125 tree loop_entry_label, loop_exit_label, fall_thru_label;
5126 tree var, var_type, cref, tmp;
5128 loop_entry_label = create_artificial_label (UNKNOWN_LOCATION);
5129 loop_exit_label = create_artificial_label (UNKNOWN_LOCATION);
5130 fall_thru_label = create_artificial_label (UNKNOWN_LOCATION);
5132 /* Create and initialize the index variable. */
5133 var_type = TREE_TYPE (upper);
5134 var = create_tmp_var (var_type);
5135 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, lower));
5137 /* Add the loop entry label. */
5138 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_entry_label));
5140 /* Build the reference. */
5141 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
5142 var, NULL_TREE, NULL_TREE);
5144 /* If we are a constructor, just call gimplify_init_ctor_eval to do
5145 the store. Otherwise just assign value to the reference. */
5147 if (TREE_CODE (value) == CONSTRUCTOR)
5148 /* NB we might have to call ourself recursively through
5149 gimplify_init_ctor_eval if the value is a constructor. */
5150 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
5151 pre_p, cleared);
5152 else
5154 if (gimplify_expr (&value, pre_p, NULL, is_gimple_val, fb_rvalue)
5155 != GS_ERROR)
5156 gimplify_seq_add_stmt (pre_p, gimple_build_assign (cref, value));
5159 /* We exit the loop when the index var is equal to the upper bound. */
5160 gimplify_seq_add_stmt (pre_p,
5161 gimple_build_cond (EQ_EXPR, var, upper,
5162 loop_exit_label, fall_thru_label));
5164 gimplify_seq_add_stmt (pre_p, gimple_build_label (fall_thru_label));
5166 /* Otherwise, increment the index var... */
5167 tmp = build2 (PLUS_EXPR, var_type, var,
5168 fold_convert (var_type, integer_one_node));
5169 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, tmp));
5171 /* ...and jump back to the loop entry. */
5172 gimplify_seq_add_stmt (pre_p, gimple_build_goto (loop_entry_label));
5174 /* Add the loop exit label. */
5175 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_exit_label));
5178 /* A subroutine of gimplify_init_constructor. Generate individual
5179 MODIFY_EXPRs for a CONSTRUCTOR. OBJECT is the LHS against which the
5180 assignments should happen. ELTS is the CONSTRUCTOR_ELTS of the
5181 CONSTRUCTOR. CLEARED is true if the entire LHS object has been
5182 zeroed first. */
5184 static void
5185 gimplify_init_ctor_eval (tree object, vec<constructor_elt, va_gc> *elts,
5186 gimple_seq *pre_p, bool cleared)
5188 tree array_elt_type = NULL;
5189 unsigned HOST_WIDE_INT ix;
5190 tree purpose, value;
5192 if (TREE_CODE (TREE_TYPE (object)) == ARRAY_TYPE)
5193 array_elt_type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (object)));
5195 FOR_EACH_CONSTRUCTOR_ELT (elts, ix, purpose, value)
5197 tree cref;
5199 /* NULL values are created above for gimplification errors. */
5200 if (value == NULL)
5201 continue;
5203 if (cleared && initializer_zerop (value))
5204 continue;
5206 /* ??? Here's to hoping the front end fills in all of the indices,
5207 so we don't have to figure out what's missing ourselves. */
5208 gcc_assert (purpose);
5210 /* Skip zero-sized fields, unless value has side-effects. This can
5211 happen with calls to functions returning a empty type, which
5212 we shouldn't discard. As a number of downstream passes don't
5213 expect sets of empty type fields, we rely on the gimplification of
5214 the MODIFY_EXPR we make below to drop the assignment statement. */
5215 if (!TREE_SIDE_EFFECTS (value)
5216 && TREE_CODE (purpose) == FIELD_DECL
5217 && is_empty_type (TREE_TYPE (purpose)))
5218 continue;
5220 /* If we have a RANGE_EXPR, we have to build a loop to assign the
5221 whole range. */
5222 if (TREE_CODE (purpose) == RANGE_EXPR)
5224 tree lower = TREE_OPERAND (purpose, 0);
5225 tree upper = TREE_OPERAND (purpose, 1);
5227 /* If the lower bound is equal to upper, just treat it as if
5228 upper was the index. */
5229 if (simple_cst_equal (lower, upper))
5230 purpose = upper;
5231 else
5233 gimplify_init_ctor_eval_range (object, lower, upper, value,
5234 array_elt_type, pre_p, cleared);
5235 continue;
5239 if (array_elt_type)
5241 /* Do not use bitsizetype for ARRAY_REF indices. */
5242 if (TYPE_DOMAIN (TREE_TYPE (object)))
5243 purpose
5244 = fold_convert (TREE_TYPE (TYPE_DOMAIN (TREE_TYPE (object))),
5245 purpose);
5246 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
5247 purpose, NULL_TREE, NULL_TREE);
5249 else
5251 gcc_assert (TREE_CODE (purpose) == FIELD_DECL);
5252 cref = build3 (COMPONENT_REF, TREE_TYPE (purpose),
5253 unshare_expr (object), purpose, NULL_TREE);
5256 if (TREE_CODE (value) == CONSTRUCTOR
5257 && TREE_CODE (TREE_TYPE (value)) != VECTOR_TYPE)
5258 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
5259 pre_p, cleared);
5260 else
5262 tree init = build2 (INIT_EXPR, TREE_TYPE (cref), cref, value);
5263 gimplify_and_add (init, pre_p);
5264 ggc_free (init);
5269 /* Return the appropriate RHS predicate for this LHS. */
5271 gimple_predicate
5272 rhs_predicate_for (tree lhs)
5274 if (is_gimple_reg (lhs))
5275 return is_gimple_reg_rhs_or_call;
5276 else
5277 return is_gimple_mem_rhs_or_call;
5280 /* Return the initial guess for an appropriate RHS predicate for this LHS,
5281 before the LHS has been gimplified. */
5283 static gimple_predicate
5284 initial_rhs_predicate_for (tree lhs)
5286 if (is_gimple_reg_type (TREE_TYPE (lhs)))
5287 return is_gimple_reg_rhs_or_call;
5288 else
5289 return is_gimple_mem_rhs_or_call;
5292 /* Gimplify a C99 compound literal expression. This just means adding
5293 the DECL_EXPR before the current statement and using its anonymous
5294 decl instead. */
5296 static enum gimplify_status
5297 gimplify_compound_literal_expr (tree *expr_p, gimple_seq *pre_p,
5298 bool (*gimple_test_f) (tree),
5299 fallback_t fallback)
5301 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (*expr_p);
5302 tree decl = DECL_EXPR_DECL (decl_s);
5303 tree init = DECL_INITIAL (decl);
5304 /* Mark the decl as addressable if the compound literal
5305 expression is addressable now, otherwise it is marked too late
5306 after we gimplify the initialization expression. */
5307 if (TREE_ADDRESSABLE (*expr_p))
5308 TREE_ADDRESSABLE (decl) = 1;
5309 /* Otherwise, if we don't need an lvalue and have a literal directly
5310 substitute it. Check if it matches the gimple predicate, as
5311 otherwise we'd generate a new temporary, and we can as well just
5312 use the decl we already have. */
5313 else if (!TREE_ADDRESSABLE (decl)
5314 && !TREE_THIS_VOLATILE (decl)
5315 && init
5316 && (fallback & fb_lvalue) == 0
5317 && gimple_test_f (init))
5319 *expr_p = init;
5320 return GS_OK;
5323 /* If the decl is not addressable, then it is being used in some
5324 expression or on the right hand side of a statement, and it can
5325 be put into a readonly data section. */
5326 if (!TREE_ADDRESSABLE (decl) && (fallback & fb_lvalue) == 0)
5327 TREE_READONLY (decl) = 1;
5329 /* This decl isn't mentioned in the enclosing block, so add it to the
5330 list of temps. FIXME it seems a bit of a kludge to say that
5331 anonymous artificial vars aren't pushed, but everything else is. */
5332 if (DECL_NAME (decl) == NULL_TREE && !DECL_SEEN_IN_BIND_EXPR_P (decl))
5333 gimple_add_tmp_var (decl);
5335 gimplify_and_add (decl_s, pre_p);
5336 *expr_p = decl;
5337 return GS_OK;
5340 /* Optimize embedded COMPOUND_LITERAL_EXPRs within a CONSTRUCTOR,
5341 return a new CONSTRUCTOR if something changed. */
5343 static tree
5344 optimize_compound_literals_in_ctor (tree orig_ctor)
5346 tree ctor = orig_ctor;
5347 vec<constructor_elt, va_gc> *elts = CONSTRUCTOR_ELTS (ctor);
5348 unsigned int idx, num = vec_safe_length (elts);
5350 for (idx = 0; idx < num; idx++)
5352 tree value = (*elts)[idx].value;
5353 tree newval = value;
5354 if (TREE_CODE (value) == CONSTRUCTOR)
5355 newval = optimize_compound_literals_in_ctor (value);
5356 else if (TREE_CODE (value) == COMPOUND_LITERAL_EXPR)
5358 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (value);
5359 tree decl = DECL_EXPR_DECL (decl_s);
5360 tree init = DECL_INITIAL (decl);
5362 if (!TREE_ADDRESSABLE (value)
5363 && !TREE_ADDRESSABLE (decl)
5364 && init
5365 && TREE_CODE (init) == CONSTRUCTOR)
5366 newval = optimize_compound_literals_in_ctor (init);
5368 if (newval == value)
5369 continue;
5371 if (ctor == orig_ctor)
5373 ctor = copy_node (orig_ctor);
5374 CONSTRUCTOR_ELTS (ctor) = vec_safe_copy (elts);
5375 elts = CONSTRUCTOR_ELTS (ctor);
5377 (*elts)[idx].value = newval;
5379 return ctor;
5382 /* A subroutine of gimplify_modify_expr. Break out elements of a
5383 CONSTRUCTOR used as an initializer into separate MODIFY_EXPRs.
5385 Note that we still need to clear any elements that don't have explicit
5386 initializers, so if not all elements are initialized we keep the
5387 original MODIFY_EXPR, we just remove all of the constructor elements.
5389 If NOTIFY_TEMP_CREATION is true, do not gimplify, just return
5390 GS_ERROR if we would have to create a temporary when gimplifying
5391 this constructor. Otherwise, return GS_OK.
5393 If NOTIFY_TEMP_CREATION is false, just do the gimplification. */
5395 static enum gimplify_status
5396 gimplify_init_constructor (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
5397 bool want_value, bool notify_temp_creation)
5399 tree object, ctor, type;
5400 enum gimplify_status ret;
5401 vec<constructor_elt, va_gc> *elts;
5402 bool cleared = false;
5403 bool is_empty_ctor = false;
5404 bool is_init_expr = (TREE_CODE (*expr_p) == INIT_EXPR);
5406 gcc_assert (TREE_CODE (TREE_OPERAND (*expr_p, 1)) == CONSTRUCTOR);
5408 if (!notify_temp_creation)
5410 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
5411 is_gimple_lvalue, fb_lvalue);
5412 if (ret == GS_ERROR)
5413 return ret;
5416 object = TREE_OPERAND (*expr_p, 0);
5417 ctor = TREE_OPERAND (*expr_p, 1)
5418 = optimize_compound_literals_in_ctor (TREE_OPERAND (*expr_p, 1));
5419 type = TREE_TYPE (ctor);
5420 elts = CONSTRUCTOR_ELTS (ctor);
5421 ret = GS_ALL_DONE;
5423 switch (TREE_CODE (type))
5425 case RECORD_TYPE:
5426 case UNION_TYPE:
5427 case QUAL_UNION_TYPE:
5428 case ARRAY_TYPE:
5430 /* Use readonly data for initializers of this or smaller size
5431 regardless of the num_nonzero_elements / num_unique_nonzero_elements
5432 ratio. */
5433 const HOST_WIDE_INT min_unique_size = 64;
5434 /* If num_nonzero_elements / num_unique_nonzero_elements ratio
5435 is smaller than this, use readonly data. */
5436 const int unique_nonzero_ratio = 8;
5437 /* True if a single access of the object must be ensured. This is the
5438 case if the target is volatile, the type is non-addressable and more
5439 than one field need to be assigned. */
5440 const bool ensure_single_access
5441 = TREE_THIS_VOLATILE (object)
5442 && !TREE_ADDRESSABLE (type)
5443 && vec_safe_length (elts) > 1;
5444 struct gimplify_init_ctor_preeval_data preeval_data;
5445 HOST_WIDE_INT num_ctor_elements, num_nonzero_elements;
5446 HOST_WIDE_INT num_unique_nonzero_elements;
5447 bool complete_p, valid_const_initializer;
5449 /* Aggregate types must lower constructors to initialization of
5450 individual elements. The exception is that a CONSTRUCTOR node
5451 with no elements indicates zero-initialization of the whole. */
5452 if (vec_safe_is_empty (elts))
5454 if (notify_temp_creation)
5455 return GS_OK;
5457 /* The var will be initialized and so appear on lhs of
5458 assignment, it can't be TREE_READONLY anymore. */
5459 if (VAR_P (object))
5460 TREE_READONLY (object) = 0;
5462 is_empty_ctor = true;
5463 break;
5466 /* Fetch information about the constructor to direct later processing.
5467 We might want to make static versions of it in various cases, and
5468 can only do so if it known to be a valid constant initializer. */
5469 valid_const_initializer
5470 = categorize_ctor_elements (ctor, &num_nonzero_elements,
5471 &num_unique_nonzero_elements,
5472 &num_ctor_elements, &complete_p);
5474 /* If a const aggregate variable is being initialized, then it
5475 should never be a lose to promote the variable to be static. */
5476 if (valid_const_initializer
5477 && num_nonzero_elements > 1
5478 && TREE_READONLY (object)
5479 && VAR_P (object)
5480 && !DECL_REGISTER (object)
5481 && (flag_merge_constants >= 2 || !TREE_ADDRESSABLE (object)
5482 || DECL_MERGEABLE (object))
5483 /* For ctors that have many repeated nonzero elements
5484 represented through RANGE_EXPRs, prefer initializing
5485 those through runtime loops over copies of large amounts
5486 of data from readonly data section. */
5487 && (num_unique_nonzero_elements
5488 > num_nonzero_elements / unique_nonzero_ratio
5489 || ((unsigned HOST_WIDE_INT) int_size_in_bytes (type)
5490 <= (unsigned HOST_WIDE_INT) min_unique_size)))
5492 if (notify_temp_creation)
5493 return GS_ERROR;
5495 DECL_INITIAL (object) = ctor;
5496 TREE_STATIC (object) = 1;
5497 if (!DECL_NAME (object))
5498 DECL_NAME (object) = create_tmp_var_name ("C");
5499 walk_tree (&DECL_INITIAL (object), force_labels_r, NULL, NULL);
5501 /* ??? C++ doesn't automatically append a .<number> to the
5502 assembler name, and even when it does, it looks at FE private
5503 data structures to figure out what that number should be,
5504 which are not set for this variable. I suppose this is
5505 important for local statics for inline functions, which aren't
5506 "local" in the object file sense. So in order to get a unique
5507 TU-local symbol, we must invoke the lhd version now. */
5508 lhd_set_decl_assembler_name (object);
5510 *expr_p = NULL_TREE;
5511 break;
5514 /* The var will be initialized and so appear on lhs of
5515 assignment, it can't be TREE_READONLY anymore. */
5516 if (VAR_P (object) && !notify_temp_creation)
5517 TREE_READONLY (object) = 0;
5519 /* If there are "lots" of initialized elements, even discounting
5520 those that are not address constants (and thus *must* be
5521 computed at runtime), then partition the constructor into
5522 constant and non-constant parts. Block copy the constant
5523 parts in, then generate code for the non-constant parts. */
5524 /* TODO. There's code in cp/typeck.cc to do this. */
5526 if (int_size_in_bytes (TREE_TYPE (ctor)) < 0)
5527 /* store_constructor will ignore the clearing of variable-sized
5528 objects. Initializers for such objects must explicitly set
5529 every field that needs to be set. */
5530 cleared = false;
5531 else if (!complete_p)
5532 /* If the constructor isn't complete, clear the whole object
5533 beforehand, unless CONSTRUCTOR_NO_CLEARING is set on it.
5535 ??? This ought not to be needed. For any element not present
5536 in the initializer, we should simply set them to zero. Except
5537 we'd need to *find* the elements that are not present, and that
5538 requires trickery to avoid quadratic compile-time behavior in
5539 large cases or excessive memory use in small cases. */
5540 cleared = !CONSTRUCTOR_NO_CLEARING (ctor);
5541 else if (num_ctor_elements - num_nonzero_elements
5542 > CLEAR_RATIO (optimize_function_for_speed_p (cfun))
5543 && num_nonzero_elements < num_ctor_elements / 4)
5544 /* If there are "lots" of zeros, it's more efficient to clear
5545 the memory and then set the nonzero elements. */
5546 cleared = true;
5547 else if (ensure_single_access && num_nonzero_elements == 0)
5548 /* If a single access to the target must be ensured and all elements
5549 are zero, then it's optimal to clear whatever their number. */
5550 cleared = true;
5551 else
5552 cleared = false;
5554 /* If there are "lots" of initialized elements, and all of them
5555 are valid address constants, then the entire initializer can
5556 be dropped to memory, and then memcpy'd out. Don't do this
5557 for sparse arrays, though, as it's more efficient to follow
5558 the standard CONSTRUCTOR behavior of memset followed by
5559 individual element initialization. Also don't do this for small
5560 all-zero initializers (which aren't big enough to merit
5561 clearing), and don't try to make bitwise copies of
5562 TREE_ADDRESSABLE types. */
5563 if (valid_const_initializer
5564 && complete_p
5565 && !(cleared || num_nonzero_elements == 0)
5566 && !TREE_ADDRESSABLE (type))
5568 HOST_WIDE_INT size = int_size_in_bytes (type);
5569 unsigned int align;
5571 /* ??? We can still get unbounded array types, at least
5572 from the C++ front end. This seems wrong, but attempt
5573 to work around it for now. */
5574 if (size < 0)
5576 size = int_size_in_bytes (TREE_TYPE (object));
5577 if (size >= 0)
5578 TREE_TYPE (ctor) = type = TREE_TYPE (object);
5581 /* Find the maximum alignment we can assume for the object. */
5582 /* ??? Make use of DECL_OFFSET_ALIGN. */
5583 if (DECL_P (object))
5584 align = DECL_ALIGN (object);
5585 else
5586 align = TYPE_ALIGN (type);
5588 /* Do a block move either if the size is so small as to make
5589 each individual move a sub-unit move on average, or if it
5590 is so large as to make individual moves inefficient. */
5591 if (size > 0
5592 && num_nonzero_elements > 1
5593 /* For ctors that have many repeated nonzero elements
5594 represented through RANGE_EXPRs, prefer initializing
5595 those through runtime loops over copies of large amounts
5596 of data from readonly data section. */
5597 && (num_unique_nonzero_elements
5598 > num_nonzero_elements / unique_nonzero_ratio
5599 || size <= min_unique_size)
5600 && (size < num_nonzero_elements
5601 || !can_move_by_pieces (size, align)))
5603 if (notify_temp_creation)
5604 return GS_ERROR;
5606 walk_tree (&ctor, force_labels_r, NULL, NULL);
5607 ctor = tree_output_constant_def (ctor);
5608 if (!useless_type_conversion_p (type, TREE_TYPE (ctor)))
5609 ctor = build1 (VIEW_CONVERT_EXPR, type, ctor);
5610 TREE_OPERAND (*expr_p, 1) = ctor;
5612 /* This is no longer an assignment of a CONSTRUCTOR, but
5613 we still may have processing to do on the LHS. So
5614 pretend we didn't do anything here to let that happen. */
5615 return GS_UNHANDLED;
5619 /* If a single access to the target must be ensured and there are
5620 nonzero elements or the zero elements are not assigned en masse,
5621 initialize the target from a temporary. */
5622 if (ensure_single_access && (num_nonzero_elements > 0 || !cleared))
5624 if (notify_temp_creation)
5625 return GS_ERROR;
5627 tree temp = create_tmp_var (TYPE_MAIN_VARIANT (type));
5628 TREE_OPERAND (*expr_p, 0) = temp;
5629 *expr_p = build2 (COMPOUND_EXPR, TREE_TYPE (*expr_p),
5630 *expr_p,
5631 build2 (MODIFY_EXPR, void_type_node,
5632 object, temp));
5633 return GS_OK;
5636 if (notify_temp_creation)
5637 return GS_OK;
5639 /* If there are nonzero elements and if needed, pre-evaluate to capture
5640 elements overlapping with the lhs into temporaries. We must do this
5641 before clearing to fetch the values before they are zeroed-out. */
5642 if (num_nonzero_elements > 0 && TREE_CODE (*expr_p) != INIT_EXPR)
5644 preeval_data.lhs_base_decl = get_base_address (object);
5645 if (!DECL_P (preeval_data.lhs_base_decl))
5646 preeval_data.lhs_base_decl = NULL;
5647 preeval_data.lhs_alias_set = get_alias_set (object);
5649 gimplify_init_ctor_preeval (&TREE_OPERAND (*expr_p, 1),
5650 pre_p, post_p, &preeval_data);
5653 bool ctor_has_side_effects_p
5654 = TREE_SIDE_EFFECTS (TREE_OPERAND (*expr_p, 1));
5656 if (cleared)
5658 /* Zap the CONSTRUCTOR element list, which simplifies this case.
5659 Note that we still have to gimplify, in order to handle the
5660 case of variable sized types. Avoid shared tree structures. */
5661 CONSTRUCTOR_ELTS (ctor) = NULL;
5662 TREE_SIDE_EFFECTS (ctor) = 0;
5663 object = unshare_expr (object);
5664 gimplify_stmt (expr_p, pre_p);
5667 /* If we have not block cleared the object, or if there are nonzero
5668 elements in the constructor, or if the constructor has side effects,
5669 add assignments to the individual scalar fields of the object. */
5670 if (!cleared
5671 || num_nonzero_elements > 0
5672 || ctor_has_side_effects_p)
5673 gimplify_init_ctor_eval (object, elts, pre_p, cleared);
5675 *expr_p = NULL_TREE;
5677 break;
5679 case COMPLEX_TYPE:
5681 tree r, i;
5683 if (notify_temp_creation)
5684 return GS_OK;
5686 /* Extract the real and imaginary parts out of the ctor. */
5687 gcc_assert (elts->length () == 2);
5688 r = (*elts)[0].value;
5689 i = (*elts)[1].value;
5690 if (r == NULL || i == NULL)
5692 tree zero = build_zero_cst (TREE_TYPE (type));
5693 if (r == NULL)
5694 r = zero;
5695 if (i == NULL)
5696 i = zero;
5699 /* Complex types have either COMPLEX_CST or COMPLEX_EXPR to
5700 represent creation of a complex value. */
5701 if (TREE_CONSTANT (r) && TREE_CONSTANT (i))
5703 ctor = build_complex (type, r, i);
5704 TREE_OPERAND (*expr_p, 1) = ctor;
5706 else
5708 ctor = build2 (COMPLEX_EXPR, type, r, i);
5709 TREE_OPERAND (*expr_p, 1) = ctor;
5710 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 1),
5711 pre_p,
5712 post_p,
5713 rhs_predicate_for (TREE_OPERAND (*expr_p, 0)),
5714 fb_rvalue);
5717 break;
5719 case VECTOR_TYPE:
5721 unsigned HOST_WIDE_INT ix;
5722 constructor_elt *ce;
5724 if (notify_temp_creation)
5725 return GS_OK;
5727 /* Vector types use CONSTRUCTOR all the way through gimple
5728 compilation as a general initializer. */
5729 FOR_EACH_VEC_SAFE_ELT (elts, ix, ce)
5731 enum gimplify_status tret;
5732 tret = gimplify_expr (&ce->value, pre_p, post_p, is_gimple_val,
5733 fb_rvalue);
5734 if (tret == GS_ERROR)
5735 ret = GS_ERROR;
5736 else if (TREE_STATIC (ctor)
5737 && !initializer_constant_valid_p (ce->value,
5738 TREE_TYPE (ce->value)))
5739 TREE_STATIC (ctor) = 0;
5741 recompute_constructor_flags (ctor);
5743 /* Go ahead and simplify constant constructors to VECTOR_CST. */
5744 if (TREE_CONSTANT (ctor))
5746 bool constant_p = true;
5747 tree value;
5749 /* Even when ctor is constant, it might contain non-*_CST
5750 elements, such as addresses or trapping values like
5751 1.0/0.0 - 1.0/0.0. Such expressions don't belong
5752 in VECTOR_CST nodes. */
5753 FOR_EACH_CONSTRUCTOR_VALUE (elts, ix, value)
5754 if (!CONSTANT_CLASS_P (value))
5756 constant_p = false;
5757 break;
5760 if (constant_p)
5762 TREE_OPERAND (*expr_p, 1) = build_vector_from_ctor (type, elts);
5763 break;
5767 if (!is_gimple_reg (TREE_OPERAND (*expr_p, 0)))
5768 TREE_OPERAND (*expr_p, 1) = get_formal_tmp_var (ctor, pre_p);
5770 break;
5772 default:
5773 /* So how did we get a CONSTRUCTOR for a scalar type? */
5774 gcc_unreachable ();
5777 if (ret == GS_ERROR)
5778 return GS_ERROR;
5779 /* If we have gimplified both sides of the initializer but have
5780 not emitted an assignment, do so now. */
5781 if (*expr_p
5782 /* If the type is an empty type, we don't need to emit the
5783 assignment. */
5784 && !is_empty_type (TREE_TYPE (TREE_OPERAND (*expr_p, 0))))
5786 tree lhs = TREE_OPERAND (*expr_p, 0);
5787 tree rhs = TREE_OPERAND (*expr_p, 1);
5788 if (want_value && object == lhs)
5789 lhs = unshare_expr (lhs);
5790 gassign *init = gimple_build_assign (lhs, rhs);
5791 gimplify_seq_add_stmt (pre_p, init);
5793 if (want_value)
5795 *expr_p = object;
5796 ret = GS_OK;
5798 else
5800 *expr_p = NULL;
5801 ret = GS_ALL_DONE;
5804 /* If the user requests to initialize automatic variables, we
5805 should initialize paddings inside the variable. Add a call to
5806 __builtin_clear_pading (&object, 0, for_auto_init = true) to
5807 initialize paddings of object always to zero regardless of
5808 INIT_TYPE. Note, we will not insert this call if the aggregate
5809 variable has be completely cleared already or it's initialized
5810 with an empty constructor. We cannot insert this call if the
5811 variable is a gimple register since __builtin_clear_padding will take
5812 the address of the variable. As a result, if a long double/_Complex long
5813 double variable will be spilled into stack later, its padding cannot
5814 be cleared with __builtin_clear_padding. We should clear its padding
5815 when it is spilled into memory. */
5816 if (is_init_expr
5817 && !is_gimple_reg (object)
5818 && clear_padding_type_may_have_padding_p (type)
5819 && ((AGGREGATE_TYPE_P (type) && !cleared && !is_empty_ctor)
5820 || !AGGREGATE_TYPE_P (type))
5821 && is_var_need_auto_init (object))
5822 gimple_add_padding_init_for_auto_var (object, false, pre_p);
5824 return ret;
5827 /* Given a pointer value OP0, return a simplified version of an
5828 indirection through OP0, or NULL_TREE if no simplification is
5829 possible. This may only be applied to a rhs of an expression.
5830 Note that the resulting type may be different from the type pointed
5831 to in the sense that it is still compatible from the langhooks
5832 point of view. */
5834 static tree
5835 gimple_fold_indirect_ref_rhs (tree t)
5837 return gimple_fold_indirect_ref (t);
5840 /* Subroutine of gimplify_modify_expr to do simplifications of
5841 MODIFY_EXPRs based on the code of the RHS. We loop for as long as
5842 something changes. */
5844 static enum gimplify_status
5845 gimplify_modify_expr_rhs (tree *expr_p, tree *from_p, tree *to_p,
5846 gimple_seq *pre_p, gimple_seq *post_p,
5847 bool want_value)
5849 enum gimplify_status ret = GS_UNHANDLED;
5850 bool changed;
5854 changed = false;
5855 switch (TREE_CODE (*from_p))
5857 case VAR_DECL:
5858 /* If we're assigning from a read-only variable initialized with
5859 a constructor and not volatile, do the direct assignment from
5860 the constructor, but only if the target is not volatile either
5861 since this latter assignment might end up being done on a per
5862 field basis. However, if the target is volatile and the type
5863 is aggregate and non-addressable, gimplify_init_constructor
5864 knows that it needs to ensure a single access to the target
5865 and it will return GS_OK only in this case. */
5866 if (TREE_READONLY (*from_p)
5867 && DECL_INITIAL (*from_p)
5868 && TREE_CODE (DECL_INITIAL (*from_p)) == CONSTRUCTOR
5869 && !TREE_THIS_VOLATILE (*from_p)
5870 && (!TREE_THIS_VOLATILE (*to_p)
5871 || (AGGREGATE_TYPE_P (TREE_TYPE (*to_p))
5872 && !TREE_ADDRESSABLE (TREE_TYPE (*to_p)))))
5874 tree old_from = *from_p;
5875 enum gimplify_status subret;
5877 /* Move the constructor into the RHS. */
5878 *from_p = unshare_expr (DECL_INITIAL (*from_p));
5880 /* Let's see if gimplify_init_constructor will need to put
5881 it in memory. */
5882 subret = gimplify_init_constructor (expr_p, NULL, NULL,
5883 false, true);
5884 if (subret == GS_ERROR)
5886 /* If so, revert the change. */
5887 *from_p = old_from;
5889 else
5891 ret = GS_OK;
5892 changed = true;
5895 break;
5896 case INDIRECT_REF:
5897 if (!TREE_ADDRESSABLE (TREE_TYPE (*from_p)))
5898 /* If we have code like
5900 *(const A*)(A*)&x
5902 where the type of "x" is a (possibly cv-qualified variant
5903 of "A"), treat the entire expression as identical to "x".
5904 This kind of code arises in C++ when an object is bound
5905 to a const reference, and if "x" is a TARGET_EXPR we want
5906 to take advantage of the optimization below. But not if
5907 the type is TREE_ADDRESSABLE; then C++17 says that the
5908 TARGET_EXPR needs to be a temporary. */
5909 if (tree t
5910 = gimple_fold_indirect_ref_rhs (TREE_OPERAND (*from_p, 0)))
5912 bool volatile_p = TREE_THIS_VOLATILE (*from_p);
5913 if (TREE_THIS_VOLATILE (t) != volatile_p)
5915 if (DECL_P (t))
5916 t = build_simple_mem_ref_loc (EXPR_LOCATION (*from_p),
5917 build_fold_addr_expr (t));
5918 if (REFERENCE_CLASS_P (t))
5919 TREE_THIS_VOLATILE (t) = volatile_p;
5921 *from_p = t;
5922 ret = GS_OK;
5923 changed = true;
5925 break;
5927 case TARGET_EXPR:
5929 /* If we are initializing something from a TARGET_EXPR, strip the
5930 TARGET_EXPR and initialize it directly, if possible. This can't
5931 be done if the initializer is void, since that implies that the
5932 temporary is set in some non-trivial way.
5934 ??? What about code that pulls out the temp and uses it
5935 elsewhere? I think that such code never uses the TARGET_EXPR as
5936 an initializer. If I'm wrong, we'll die because the temp won't
5937 have any RTL. In that case, I guess we'll need to replace
5938 references somehow. */
5939 tree init = TARGET_EXPR_INITIAL (*from_p);
5941 if (init
5942 && (TREE_CODE (*expr_p) != MODIFY_EXPR
5943 || !TARGET_EXPR_NO_ELIDE (*from_p))
5944 && !VOID_TYPE_P (TREE_TYPE (init)))
5946 *from_p = init;
5947 ret = GS_OK;
5948 changed = true;
5951 break;
5953 case COMPOUND_EXPR:
5954 /* Remove any COMPOUND_EXPR in the RHS so the following cases will be
5955 caught. */
5956 gimplify_compound_expr (from_p, pre_p, true);
5957 ret = GS_OK;
5958 changed = true;
5959 break;
5961 case CONSTRUCTOR:
5962 /* If we already made some changes, let the front end have a
5963 crack at this before we break it down. */
5964 if (ret != GS_UNHANDLED)
5965 break;
5967 /* If we're initializing from a CONSTRUCTOR, break this into
5968 individual MODIFY_EXPRs. */
5969 ret = gimplify_init_constructor (expr_p, pre_p, post_p, want_value,
5970 false);
5971 return ret;
5973 case COND_EXPR:
5974 /* If we're assigning to a non-register type, push the assignment
5975 down into the branches. This is mandatory for ADDRESSABLE types,
5976 since we cannot generate temporaries for such, but it saves a
5977 copy in other cases as well. */
5978 if (!is_gimple_reg_type (TREE_TYPE (*from_p)))
5980 /* This code should mirror the code in gimplify_cond_expr. */
5981 enum tree_code code = TREE_CODE (*expr_p);
5982 tree cond = *from_p;
5983 tree result = *to_p;
5985 ret = gimplify_expr (&result, pre_p, post_p,
5986 is_gimple_lvalue, fb_lvalue);
5987 if (ret != GS_ERROR)
5988 ret = GS_OK;
5990 /* If we are going to write RESULT more than once, clear
5991 TREE_READONLY flag, otherwise we might incorrectly promote
5992 the variable to static const and initialize it at compile
5993 time in one of the branches. */
5994 if (VAR_P (result)
5995 && TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node
5996 && TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
5997 TREE_READONLY (result) = 0;
5998 if (TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node)
5999 TREE_OPERAND (cond, 1)
6000 = build2 (code, void_type_node, result,
6001 TREE_OPERAND (cond, 1));
6002 if (TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
6003 TREE_OPERAND (cond, 2)
6004 = build2 (code, void_type_node, unshare_expr (result),
6005 TREE_OPERAND (cond, 2));
6007 TREE_TYPE (cond) = void_type_node;
6008 recalculate_side_effects (cond);
6010 if (want_value)
6012 gimplify_and_add (cond, pre_p);
6013 *expr_p = unshare_expr (result);
6015 else
6016 *expr_p = cond;
6017 return ret;
6019 break;
6021 case CALL_EXPR:
6022 /* For calls that return in memory, give *to_p as the CALL_EXPR's
6023 return slot so that we don't generate a temporary. */
6024 if (!CALL_EXPR_RETURN_SLOT_OPT (*from_p)
6025 && aggregate_value_p (*from_p, *from_p))
6027 bool use_target;
6029 if (!(rhs_predicate_for (*to_p))(*from_p))
6030 /* If we need a temporary, *to_p isn't accurate. */
6031 use_target = false;
6032 /* It's OK to use the return slot directly unless it's an NRV. */
6033 else if (TREE_CODE (*to_p) == RESULT_DECL
6034 && DECL_NAME (*to_p) == NULL_TREE
6035 && needs_to_live_in_memory (*to_p))
6036 use_target = true;
6037 else if (is_gimple_reg_type (TREE_TYPE (*to_p))
6038 || (DECL_P (*to_p) && DECL_REGISTER (*to_p)))
6039 /* Don't force regs into memory. */
6040 use_target = false;
6041 else if (TREE_CODE (*expr_p) == INIT_EXPR)
6042 /* It's OK to use the target directly if it's being
6043 initialized. */
6044 use_target = true;
6045 else if (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (*to_p)))
6046 != INTEGER_CST)
6047 /* Always use the target and thus RSO for variable-sized types.
6048 GIMPLE cannot deal with a variable-sized assignment
6049 embedded in a call statement. */
6050 use_target = true;
6051 else if (TREE_CODE (*to_p) != SSA_NAME
6052 && (!is_gimple_variable (*to_p)
6053 || needs_to_live_in_memory (*to_p)))
6054 /* Don't use the original target if it's already addressable;
6055 if its address escapes, and the called function uses the
6056 NRV optimization, a conforming program could see *to_p
6057 change before the called function returns; see c++/19317.
6058 When optimizing, the return_slot pass marks more functions
6059 as safe after we have escape info. */
6060 use_target = false;
6061 else
6062 use_target = true;
6064 if (use_target)
6066 CALL_EXPR_RETURN_SLOT_OPT (*from_p) = 1;
6067 mark_addressable (*to_p);
6070 break;
6072 case WITH_SIZE_EXPR:
6073 /* Likewise for calls that return an aggregate of non-constant size,
6074 since we would not be able to generate a temporary at all. */
6075 if (TREE_CODE (TREE_OPERAND (*from_p, 0)) == CALL_EXPR)
6077 *from_p = TREE_OPERAND (*from_p, 0);
6078 /* We don't change ret in this case because the
6079 WITH_SIZE_EXPR might have been added in
6080 gimplify_modify_expr, so returning GS_OK would lead to an
6081 infinite loop. */
6082 changed = true;
6084 break;
6086 /* If we're initializing from a container, push the initialization
6087 inside it. */
6088 case CLEANUP_POINT_EXPR:
6089 case BIND_EXPR:
6090 case STATEMENT_LIST:
6092 tree wrap = *from_p;
6093 tree t;
6095 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_min_lval,
6096 fb_lvalue);
6097 if (ret != GS_ERROR)
6098 ret = GS_OK;
6100 t = voidify_wrapper_expr (wrap, *expr_p);
6101 gcc_assert (t == *expr_p);
6103 if (want_value)
6105 gimplify_and_add (wrap, pre_p);
6106 *expr_p = unshare_expr (*to_p);
6108 else
6109 *expr_p = wrap;
6110 return GS_OK;
6113 case NOP_EXPR:
6114 /* Pull out compound literal expressions from a NOP_EXPR.
6115 Those are created in the C FE to drop qualifiers during
6116 lvalue conversion. */
6117 if ((TREE_CODE (TREE_OPERAND (*from_p, 0)) == COMPOUND_LITERAL_EXPR)
6118 && tree_ssa_useless_type_conversion (*from_p))
6120 *from_p = TREE_OPERAND (*from_p, 0);
6121 ret = GS_OK;
6122 changed = true;
6124 break;
6126 case COMPOUND_LITERAL_EXPR:
6128 tree complit = TREE_OPERAND (*expr_p, 1);
6129 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (complit);
6130 tree decl = DECL_EXPR_DECL (decl_s);
6131 tree init = DECL_INITIAL (decl);
6133 /* struct T x = (struct T) { 0, 1, 2 } can be optimized
6134 into struct T x = { 0, 1, 2 } if the address of the
6135 compound literal has never been taken. */
6136 if (!TREE_ADDRESSABLE (complit)
6137 && !TREE_ADDRESSABLE (decl)
6138 && init)
6140 *expr_p = copy_node (*expr_p);
6141 TREE_OPERAND (*expr_p, 1) = init;
6142 return GS_OK;
6146 default:
6147 break;
6150 while (changed);
6152 return ret;
6156 /* Return true if T looks like a valid GIMPLE statement. */
6158 static bool
6159 is_gimple_stmt (tree t)
6161 const enum tree_code code = TREE_CODE (t);
6163 switch (code)
6165 case NOP_EXPR:
6166 /* The only valid NOP_EXPR is the empty statement. */
6167 return IS_EMPTY_STMT (t);
6169 case BIND_EXPR:
6170 case COND_EXPR:
6171 /* These are only valid if they're void. */
6172 return TREE_TYPE (t) == NULL || VOID_TYPE_P (TREE_TYPE (t));
6174 case SWITCH_EXPR:
6175 case GOTO_EXPR:
6176 case RETURN_EXPR:
6177 case LABEL_EXPR:
6178 case CASE_LABEL_EXPR:
6179 case TRY_CATCH_EXPR:
6180 case TRY_FINALLY_EXPR:
6181 case EH_FILTER_EXPR:
6182 case CATCH_EXPR:
6183 case ASM_EXPR:
6184 case STATEMENT_LIST:
6185 case OACC_PARALLEL:
6186 case OACC_KERNELS:
6187 case OACC_SERIAL:
6188 case OACC_DATA:
6189 case OACC_HOST_DATA:
6190 case OACC_DECLARE:
6191 case OACC_UPDATE:
6192 case OACC_ENTER_DATA:
6193 case OACC_EXIT_DATA:
6194 case OACC_CACHE:
6195 case OMP_PARALLEL:
6196 case OMP_FOR:
6197 case OMP_SIMD:
6198 case OMP_DISTRIBUTE:
6199 case OMP_LOOP:
6200 case OACC_LOOP:
6201 case OMP_SCAN:
6202 case OMP_SCOPE:
6203 case OMP_SECTIONS:
6204 case OMP_SECTION:
6205 case OMP_STRUCTURED_BLOCK:
6206 case OMP_SINGLE:
6207 case OMP_MASTER:
6208 case OMP_MASKED:
6209 case OMP_TASKGROUP:
6210 case OMP_ORDERED:
6211 case OMP_CRITICAL:
6212 case OMP_TASK:
6213 case OMP_TARGET:
6214 case OMP_TARGET_DATA:
6215 case OMP_TARGET_UPDATE:
6216 case OMP_TARGET_ENTER_DATA:
6217 case OMP_TARGET_EXIT_DATA:
6218 case OMP_TASKLOOP:
6219 case OMP_TEAMS:
6220 /* These are always void. */
6221 return true;
6223 case CALL_EXPR:
6224 case MODIFY_EXPR:
6225 case PREDICT_EXPR:
6226 /* These are valid regardless of their type. */
6227 return true;
6229 default:
6230 return false;
6235 /* Promote partial stores to COMPLEX variables to total stores. *EXPR_P is
6236 a MODIFY_EXPR with a lhs of a REAL/IMAGPART_EXPR of a gimple register.
6238 IMPORTANT NOTE: This promotion is performed by introducing a load of the
6239 other, unmodified part of the complex object just before the total store.
6240 As a consequence, if the object is still uninitialized, an undefined value
6241 will be loaded into a register, which may result in a spurious exception
6242 if the register is floating-point and the value happens to be a signaling
6243 NaN for example. Then the fully-fledged complex operations lowering pass
6244 followed by a DCE pass are necessary in order to fix things up. */
6246 static enum gimplify_status
6247 gimplify_modify_expr_complex_part (tree *expr_p, gimple_seq *pre_p,
6248 bool want_value)
6250 enum tree_code code, ocode;
6251 tree lhs, rhs, new_rhs, other, realpart, imagpart;
6253 lhs = TREE_OPERAND (*expr_p, 0);
6254 rhs = TREE_OPERAND (*expr_p, 1);
6255 code = TREE_CODE (lhs);
6256 lhs = TREE_OPERAND (lhs, 0);
6258 ocode = code == REALPART_EXPR ? IMAGPART_EXPR : REALPART_EXPR;
6259 other = build1 (ocode, TREE_TYPE (rhs), lhs);
6260 suppress_warning (other);
6261 other = get_formal_tmp_var (other, pre_p);
6263 realpart = code == REALPART_EXPR ? rhs : other;
6264 imagpart = code == REALPART_EXPR ? other : rhs;
6266 if (TREE_CONSTANT (realpart) && TREE_CONSTANT (imagpart))
6267 new_rhs = build_complex (TREE_TYPE (lhs), realpart, imagpart);
6268 else
6269 new_rhs = build2 (COMPLEX_EXPR, TREE_TYPE (lhs), realpart, imagpart);
6271 gimplify_seq_add_stmt (pre_p, gimple_build_assign (lhs, new_rhs));
6272 *expr_p = (want_value) ? rhs : NULL_TREE;
6274 return GS_ALL_DONE;
6277 /* Gimplify the MODIFY_EXPR node pointed to by EXPR_P.
6279 modify_expr
6280 : varname '=' rhs
6281 | '*' ID '=' rhs
6283 PRE_P points to the list where side effects that must happen before
6284 *EXPR_P should be stored.
6286 POST_P points to the list where side effects that must happen after
6287 *EXPR_P should be stored.
6289 WANT_VALUE is nonzero iff we want to use the value of this expression
6290 in another expression. */
6292 static enum gimplify_status
6293 gimplify_modify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
6294 bool want_value)
6296 tree *from_p = &TREE_OPERAND (*expr_p, 1);
6297 tree *to_p = &TREE_OPERAND (*expr_p, 0);
6298 enum gimplify_status ret = GS_UNHANDLED;
6299 gimple *assign;
6300 location_t loc = EXPR_LOCATION (*expr_p);
6301 gimple_stmt_iterator gsi;
6303 if (error_operand_p (*from_p) || error_operand_p (*to_p))
6304 return GS_ERROR;
6306 gcc_assert (TREE_CODE (*expr_p) == MODIFY_EXPR
6307 || TREE_CODE (*expr_p) == INIT_EXPR);
6309 /* Trying to simplify a clobber using normal logic doesn't work,
6310 so handle it here. */
6311 if (TREE_CLOBBER_P (*from_p))
6313 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
6314 if (ret == GS_ERROR)
6315 return ret;
6316 gcc_assert (!want_value);
6317 if (!VAR_P (*to_p) && TREE_CODE (*to_p) != MEM_REF)
6319 tree addr = get_initialized_tmp_var (build_fold_addr_expr (*to_p),
6320 pre_p, post_p);
6321 *to_p = build_simple_mem_ref_loc (EXPR_LOCATION (*to_p), addr);
6323 gimplify_seq_add_stmt (pre_p, gimple_build_assign (*to_p, *from_p));
6324 *expr_p = NULL;
6325 return GS_ALL_DONE;
6328 /* Convert initialization from an empty variable-size CONSTRUCTOR to
6329 memset. */
6330 if (TREE_TYPE (*from_p) != error_mark_node
6331 && TYPE_SIZE_UNIT (TREE_TYPE (*from_p))
6332 && !poly_int_tree_p (TYPE_SIZE_UNIT (TREE_TYPE (*from_p)))
6333 && TREE_CODE (*from_p) == CONSTRUCTOR
6334 && CONSTRUCTOR_NELTS (*from_p) == 0)
6336 maybe_with_size_expr (from_p);
6337 gcc_assert (TREE_CODE (*from_p) == WITH_SIZE_EXPR);
6338 return gimplify_modify_expr_to_memset (expr_p,
6339 TREE_OPERAND (*from_p, 1),
6340 want_value, pre_p);
6343 /* Insert pointer conversions required by the middle-end that are not
6344 required by the frontend. This fixes middle-end type checking for
6345 for example gcc.dg/redecl-6.c. */
6346 if (POINTER_TYPE_P (TREE_TYPE (*to_p)))
6348 STRIP_USELESS_TYPE_CONVERSION (*from_p);
6349 if (!useless_type_conversion_p (TREE_TYPE (*to_p), TREE_TYPE (*from_p)))
6350 *from_p = fold_convert_loc (loc, TREE_TYPE (*to_p), *from_p);
6353 /* See if any simplifications can be done based on what the RHS is. */
6354 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
6355 want_value);
6356 if (ret != GS_UNHANDLED)
6357 return ret;
6359 /* For empty types only gimplify the left hand side and right hand
6360 side as statements and throw away the assignment. Do this after
6361 gimplify_modify_expr_rhs so we handle TARGET_EXPRs of addressable
6362 types properly. */
6363 if (is_empty_type (TREE_TYPE (*from_p))
6364 && !want_value
6365 /* Don't do this for calls that return addressable types, expand_call
6366 relies on those having a lhs. */
6367 && !(TREE_ADDRESSABLE (TREE_TYPE (*from_p))
6368 && TREE_CODE (*from_p) == CALL_EXPR))
6370 gimplify_stmt (from_p, pre_p);
6371 gimplify_stmt (to_p, pre_p);
6372 *expr_p = NULL_TREE;
6373 return GS_ALL_DONE;
6376 /* If the value being copied is of variable width, compute the length
6377 of the copy into a WITH_SIZE_EXPR. Note that we need to do this
6378 before gimplifying any of the operands so that we can resolve any
6379 PLACEHOLDER_EXPRs in the size. Also note that the RTL expander uses
6380 the size of the expression to be copied, not of the destination, so
6381 that is what we must do here. */
6382 maybe_with_size_expr (from_p);
6384 /* As a special case, we have to temporarily allow for assignments
6385 with a CALL_EXPR on the RHS. Since in GIMPLE a function call is
6386 a toplevel statement, when gimplifying the GENERIC expression
6387 MODIFY_EXPR <a, CALL_EXPR <foo>>, we cannot create the tuple
6388 GIMPLE_ASSIGN <a, GIMPLE_CALL <foo>>.
6390 Instead, we need to create the tuple GIMPLE_CALL <a, foo>. To
6391 prevent gimplify_expr from trying to create a new temporary for
6392 foo's LHS, we tell it that it should only gimplify until it
6393 reaches the CALL_EXPR. On return from gimplify_expr, the newly
6394 created GIMPLE_CALL <foo> will be the last statement in *PRE_P
6395 and all we need to do here is set 'a' to be its LHS. */
6397 /* Gimplify the RHS first for C++17 and bug 71104. */
6398 gimple_predicate initial_pred = initial_rhs_predicate_for (*to_p);
6399 ret = gimplify_expr (from_p, pre_p, post_p, initial_pred, fb_rvalue);
6400 if (ret == GS_ERROR)
6401 return ret;
6403 /* Then gimplify the LHS. */
6404 /* If we gimplified the RHS to a CALL_EXPR and that call may return
6405 twice we have to make sure to gimplify into non-SSA as otherwise
6406 the abnormal edge added later will make those defs not dominate
6407 their uses.
6408 ??? Technically this applies only to the registers used in the
6409 resulting non-register *TO_P. */
6410 bool saved_into_ssa = gimplify_ctxp->into_ssa;
6411 if (saved_into_ssa
6412 && TREE_CODE (*from_p) == CALL_EXPR
6413 && call_expr_flags (*from_p) & ECF_RETURNS_TWICE)
6414 gimplify_ctxp->into_ssa = false;
6415 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
6416 gimplify_ctxp->into_ssa = saved_into_ssa;
6417 if (ret == GS_ERROR)
6418 return ret;
6420 /* Now that the LHS is gimplified, re-gimplify the RHS if our initial
6421 guess for the predicate was wrong. */
6422 gimple_predicate final_pred = rhs_predicate_for (*to_p);
6423 if (final_pred != initial_pred)
6425 ret = gimplify_expr (from_p, pre_p, post_p, final_pred, fb_rvalue);
6426 if (ret == GS_ERROR)
6427 return ret;
6430 /* In case of va_arg internal fn wrappped in a WITH_SIZE_EXPR, add the type
6431 size as argument to the call. */
6432 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
6434 tree call = TREE_OPERAND (*from_p, 0);
6435 tree vlasize = TREE_OPERAND (*from_p, 1);
6437 if (TREE_CODE (call) == CALL_EXPR
6438 && CALL_EXPR_IFN (call) == IFN_VA_ARG)
6440 int nargs = call_expr_nargs (call);
6441 tree type = TREE_TYPE (call);
6442 tree ap = CALL_EXPR_ARG (call, 0);
6443 tree tag = CALL_EXPR_ARG (call, 1);
6444 tree aptag = CALL_EXPR_ARG (call, 2);
6445 tree newcall = build_call_expr_internal_loc (EXPR_LOCATION (call),
6446 IFN_VA_ARG, type,
6447 nargs + 1, ap, tag,
6448 aptag, vlasize);
6449 TREE_OPERAND (*from_p, 0) = newcall;
6453 /* Now see if the above changed *from_p to something we handle specially. */
6454 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
6455 want_value);
6456 if (ret != GS_UNHANDLED)
6457 return ret;
6459 /* If we've got a variable sized assignment between two lvalues (i.e. does
6460 not involve a call), then we can make things a bit more straightforward
6461 by converting the assignment to memcpy or memset. */
6462 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
6464 tree from = TREE_OPERAND (*from_p, 0);
6465 tree size = TREE_OPERAND (*from_p, 1);
6467 if (TREE_CODE (from) == CONSTRUCTOR)
6468 return gimplify_modify_expr_to_memset (expr_p, size, want_value, pre_p);
6470 if (is_gimple_addressable (from))
6472 *from_p = from;
6473 return gimplify_modify_expr_to_memcpy (expr_p, size, want_value,
6474 pre_p);
6478 /* Transform partial stores to non-addressable complex variables into
6479 total stores. This allows us to use real instead of virtual operands
6480 for these variables, which improves optimization. */
6481 if ((TREE_CODE (*to_p) == REALPART_EXPR
6482 || TREE_CODE (*to_p) == IMAGPART_EXPR)
6483 && is_gimple_reg (TREE_OPERAND (*to_p, 0)))
6484 return gimplify_modify_expr_complex_part (expr_p, pre_p, want_value);
6486 /* Try to alleviate the effects of the gimplification creating artificial
6487 temporaries (see for example is_gimple_reg_rhs) on the debug info, but
6488 make sure not to create DECL_DEBUG_EXPR links across functions. */
6489 if (!gimplify_ctxp->into_ssa
6490 && VAR_P (*from_p)
6491 && DECL_IGNORED_P (*from_p)
6492 && DECL_P (*to_p)
6493 && !DECL_IGNORED_P (*to_p)
6494 && decl_function_context (*to_p) == current_function_decl
6495 && decl_function_context (*from_p) == current_function_decl)
6497 if (!DECL_NAME (*from_p) && DECL_NAME (*to_p))
6498 DECL_NAME (*from_p)
6499 = create_tmp_var_name (IDENTIFIER_POINTER (DECL_NAME (*to_p)));
6500 DECL_HAS_DEBUG_EXPR_P (*from_p) = 1;
6501 SET_DECL_DEBUG_EXPR (*from_p, *to_p);
6504 if (want_value && TREE_THIS_VOLATILE (*to_p))
6505 *from_p = get_initialized_tmp_var (*from_p, pre_p, post_p);
6507 if (TREE_CODE (*from_p) == CALL_EXPR)
6509 /* Since the RHS is a CALL_EXPR, we need to create a GIMPLE_CALL
6510 instead of a GIMPLE_ASSIGN. */
6511 gcall *call_stmt;
6512 if (CALL_EXPR_FN (*from_p) == NULL_TREE)
6514 /* Gimplify internal functions created in the FEs. */
6515 int nargs = call_expr_nargs (*from_p), i;
6516 enum internal_fn ifn = CALL_EXPR_IFN (*from_p);
6517 auto_vec<tree> vargs (nargs);
6519 for (i = 0; i < nargs; i++)
6521 gimplify_arg (&CALL_EXPR_ARG (*from_p, i), pre_p,
6522 EXPR_LOCATION (*from_p));
6523 vargs.quick_push (CALL_EXPR_ARG (*from_p, i));
6525 call_stmt = gimple_build_call_internal_vec (ifn, vargs);
6526 gimple_call_set_nothrow (call_stmt, TREE_NOTHROW (*from_p));
6527 gimple_set_location (call_stmt, EXPR_LOCATION (*expr_p));
6529 else
6531 tree fnptrtype = TREE_TYPE (CALL_EXPR_FN (*from_p));
6532 CALL_EXPR_FN (*from_p) = TREE_OPERAND (CALL_EXPR_FN (*from_p), 0);
6533 STRIP_USELESS_TYPE_CONVERSION (CALL_EXPR_FN (*from_p));
6534 tree fndecl = get_callee_fndecl (*from_p);
6535 if (fndecl
6536 && fndecl_built_in_p (fndecl, BUILT_IN_EXPECT)
6537 && call_expr_nargs (*from_p) == 3)
6538 call_stmt = gimple_build_call_internal (IFN_BUILTIN_EXPECT, 3,
6539 CALL_EXPR_ARG (*from_p, 0),
6540 CALL_EXPR_ARG (*from_p, 1),
6541 CALL_EXPR_ARG (*from_p, 2));
6542 else
6544 call_stmt = gimple_build_call_from_tree (*from_p, fnptrtype);
6547 notice_special_calls (call_stmt);
6548 if (!gimple_call_noreturn_p (call_stmt) || !should_remove_lhs_p (*to_p))
6549 gimple_call_set_lhs (call_stmt, *to_p);
6550 else if (TREE_CODE (*to_p) == SSA_NAME)
6551 /* The above is somewhat premature, avoid ICEing later for a
6552 SSA name w/o a definition. We may have uses in the GIMPLE IL.
6553 ??? This doesn't make it a default-def. */
6554 SSA_NAME_DEF_STMT (*to_p) = gimple_build_nop ();
6556 assign = call_stmt;
6558 else
6560 assign = gimple_build_assign (*to_p, *from_p);
6561 gimple_set_location (assign, EXPR_LOCATION (*expr_p));
6562 if (COMPARISON_CLASS_P (*from_p))
6563 copy_warning (assign, *from_p);
6566 if (gimplify_ctxp->into_ssa && is_gimple_reg (*to_p))
6568 /* We should have got an SSA name from the start. */
6569 gcc_assert (TREE_CODE (*to_p) == SSA_NAME
6570 || ! gimple_in_ssa_p (cfun));
6573 gimplify_seq_add_stmt (pre_p, assign);
6574 gsi = gsi_last (*pre_p);
6575 maybe_fold_stmt (&gsi);
6577 if (want_value)
6579 *expr_p = TREE_THIS_VOLATILE (*to_p) ? *from_p : unshare_expr (*to_p);
6580 return GS_OK;
6582 else
6583 *expr_p = NULL;
6585 return GS_ALL_DONE;
6588 /* Gimplify a comparison between two variable-sized objects. Do this
6589 with a call to BUILT_IN_MEMCMP. */
6591 static enum gimplify_status
6592 gimplify_variable_sized_compare (tree *expr_p)
6594 location_t loc = EXPR_LOCATION (*expr_p);
6595 tree op0 = TREE_OPERAND (*expr_p, 0);
6596 tree op1 = TREE_OPERAND (*expr_p, 1);
6597 tree t, arg, dest, src, expr;
6599 arg = TYPE_SIZE_UNIT (TREE_TYPE (op0));
6600 arg = unshare_expr (arg);
6601 arg = SUBSTITUTE_PLACEHOLDER_IN_EXPR (arg, op0);
6602 src = build_fold_addr_expr_loc (loc, op1);
6603 dest = build_fold_addr_expr_loc (loc, op0);
6604 t = builtin_decl_implicit (BUILT_IN_MEMCMP);
6605 t = build_call_expr_loc (loc, t, 3, dest, src, arg);
6607 expr
6608 = build2 (TREE_CODE (*expr_p), TREE_TYPE (*expr_p), t, integer_zero_node);
6609 SET_EXPR_LOCATION (expr, loc);
6610 *expr_p = expr;
6612 return GS_OK;
6615 /* Gimplify a comparison between two aggregate objects of integral scalar
6616 mode as a comparison between the bitwise equivalent scalar values. */
6618 static enum gimplify_status
6619 gimplify_scalar_mode_aggregate_compare (tree *expr_p)
6621 location_t loc = EXPR_LOCATION (*expr_p);
6622 tree op0 = TREE_OPERAND (*expr_p, 0);
6623 tree op1 = TREE_OPERAND (*expr_p, 1);
6625 tree type = TREE_TYPE (op0);
6626 tree scalar_type = lang_hooks.types.type_for_mode (TYPE_MODE (type), 1);
6628 op0 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op0);
6629 op1 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op1);
6631 *expr_p
6632 = fold_build2_loc (loc, TREE_CODE (*expr_p), TREE_TYPE (*expr_p), op0, op1);
6634 return GS_OK;
6637 /* Gimplify an expression sequence. This function gimplifies each
6638 expression and rewrites the original expression with the last
6639 expression of the sequence in GIMPLE form.
6641 PRE_P points to the list where the side effects for all the
6642 expressions in the sequence will be emitted.
6644 WANT_VALUE is true when the result of the last COMPOUND_EXPR is used. */
6646 static enum gimplify_status
6647 gimplify_compound_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
6649 tree t = *expr_p;
6653 tree *sub_p = &TREE_OPERAND (t, 0);
6655 if (TREE_CODE (*sub_p) == COMPOUND_EXPR)
6656 gimplify_compound_expr (sub_p, pre_p, false);
6657 else
6658 gimplify_stmt (sub_p, pre_p);
6660 t = TREE_OPERAND (t, 1);
6662 while (TREE_CODE (t) == COMPOUND_EXPR);
6664 *expr_p = t;
6665 if (want_value)
6666 return GS_OK;
6667 else
6669 gimplify_stmt (expr_p, pre_p);
6670 return GS_ALL_DONE;
6674 /* Gimplify a SAVE_EXPR node. EXPR_P points to the expression to
6675 gimplify. After gimplification, EXPR_P will point to a new temporary
6676 that holds the original value of the SAVE_EXPR node.
6678 PRE_P points to the list where side effects that must happen before
6679 *EXPR_P should be stored. */
6681 static enum gimplify_status
6682 gimplify_save_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6684 enum gimplify_status ret = GS_ALL_DONE;
6685 tree val;
6687 gcc_assert (TREE_CODE (*expr_p) == SAVE_EXPR);
6688 val = TREE_OPERAND (*expr_p, 0);
6690 if (val && TREE_TYPE (val) == error_mark_node)
6691 return GS_ERROR;
6693 /* If the SAVE_EXPR has not been resolved, then evaluate it once. */
6694 if (!SAVE_EXPR_RESOLVED_P (*expr_p))
6696 /* The operand may be a void-valued expression. It is
6697 being executed only for its side-effects. */
6698 if (TREE_TYPE (val) == void_type_node)
6700 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
6701 is_gimple_stmt, fb_none);
6702 val = NULL;
6704 else
6705 /* The temporary may not be an SSA name as later abnormal and EH
6706 control flow may invalidate use/def domination. When in SSA
6707 form then assume there are no such issues and SAVE_EXPRs only
6708 appear via GENERIC foldings. */
6709 val = get_initialized_tmp_var (val, pre_p, post_p,
6710 gimple_in_ssa_p (cfun));
6712 TREE_OPERAND (*expr_p, 0) = val;
6713 SAVE_EXPR_RESOLVED_P (*expr_p) = 1;
6716 *expr_p = val;
6718 return ret;
6721 /* Rewrite the ADDR_EXPR node pointed to by EXPR_P
6723 unary_expr
6724 : ...
6725 | '&' varname
6728 PRE_P points to the list where side effects that must happen before
6729 *EXPR_P should be stored.
6731 POST_P points to the list where side effects that must happen after
6732 *EXPR_P should be stored. */
6734 static enum gimplify_status
6735 gimplify_addr_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6737 tree expr = *expr_p;
6738 tree op0 = TREE_OPERAND (expr, 0);
6739 enum gimplify_status ret;
6740 location_t loc = EXPR_LOCATION (*expr_p);
6742 switch (TREE_CODE (op0))
6744 case INDIRECT_REF:
6745 do_indirect_ref:
6746 /* Check if we are dealing with an expression of the form '&*ptr'.
6747 While the front end folds away '&*ptr' into 'ptr', these
6748 expressions may be generated internally by the compiler (e.g.,
6749 builtins like __builtin_va_end). */
6750 /* Caution: the silent array decomposition semantics we allow for
6751 ADDR_EXPR means we can't always discard the pair. */
6752 /* Gimplification of the ADDR_EXPR operand may drop
6753 cv-qualification conversions, so make sure we add them if
6754 needed. */
6756 tree op00 = TREE_OPERAND (op0, 0);
6757 tree t_expr = TREE_TYPE (expr);
6758 tree t_op00 = TREE_TYPE (op00);
6760 if (!useless_type_conversion_p (t_expr, t_op00))
6761 op00 = fold_convert_loc (loc, TREE_TYPE (expr), op00);
6762 *expr_p = op00;
6763 ret = GS_OK;
6765 break;
6767 case VIEW_CONVERT_EXPR:
6768 /* Take the address of our operand and then convert it to the type of
6769 this ADDR_EXPR.
6771 ??? The interactions of VIEW_CONVERT_EXPR and aliasing is not at
6772 all clear. The impact of this transformation is even less clear. */
6774 /* If the operand is a useless conversion, look through it. Doing so
6775 guarantees that the ADDR_EXPR and its operand will remain of the
6776 same type. */
6777 if (tree_ssa_useless_type_conversion (TREE_OPERAND (op0, 0)))
6778 op0 = TREE_OPERAND (op0, 0);
6780 *expr_p = fold_convert_loc (loc, TREE_TYPE (expr),
6781 build_fold_addr_expr_loc (loc,
6782 TREE_OPERAND (op0, 0)));
6783 ret = GS_OK;
6784 break;
6786 case MEM_REF:
6787 if (integer_zerop (TREE_OPERAND (op0, 1)))
6788 goto do_indirect_ref;
6790 /* fall through */
6792 default:
6793 /* If we see a call to a declared builtin or see its address
6794 being taken (we can unify those cases here) then we can mark
6795 the builtin for implicit generation by GCC. */
6796 if (TREE_CODE (op0) == FUNCTION_DECL
6797 && fndecl_built_in_p (op0, BUILT_IN_NORMAL)
6798 && builtin_decl_declared_p (DECL_FUNCTION_CODE (op0)))
6799 set_builtin_decl_implicit_p (DECL_FUNCTION_CODE (op0), true);
6801 /* We use fb_either here because the C frontend sometimes takes
6802 the address of a call that returns a struct; see
6803 gcc.dg/c99-array-lval-1.c. The gimplifier will correctly make
6804 the implied temporary explicit. */
6806 /* Make the operand addressable. */
6807 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, post_p,
6808 is_gimple_addressable, fb_either);
6809 if (ret == GS_ERROR)
6810 break;
6812 /* Then mark it. Beware that it may not be possible to do so directly
6813 if a temporary has been created by the gimplification. */
6814 prepare_gimple_addressable (&TREE_OPERAND (expr, 0), pre_p);
6816 op0 = TREE_OPERAND (expr, 0);
6818 /* For various reasons, the gimplification of the expression
6819 may have made a new INDIRECT_REF. */
6820 if (INDIRECT_REF_P (op0)
6821 || (TREE_CODE (op0) == MEM_REF
6822 && integer_zerop (TREE_OPERAND (op0, 1))))
6823 goto do_indirect_ref;
6825 mark_addressable (TREE_OPERAND (expr, 0));
6827 /* The FEs may end up building ADDR_EXPRs early on a decl with
6828 an incomplete type. Re-build ADDR_EXPRs in canonical form
6829 here. */
6830 if (!types_compatible_p (TREE_TYPE (op0), TREE_TYPE (TREE_TYPE (expr))))
6831 *expr_p = build_fold_addr_expr (op0);
6833 /* Make sure TREE_CONSTANT and TREE_SIDE_EFFECTS are set properly. */
6834 recompute_tree_invariant_for_addr_expr (*expr_p);
6836 /* If we re-built the ADDR_EXPR add a conversion to the original type
6837 if required. */
6838 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
6839 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
6841 break;
6844 return ret;
6847 /* Gimplify the operands of an ASM_EXPR. Input operands should be a gimple
6848 value; output operands should be a gimple lvalue. */
6850 static enum gimplify_status
6851 gimplify_asm_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6853 tree expr;
6854 int noutputs;
6855 const char **oconstraints;
6856 int i;
6857 tree link;
6858 const char *constraint;
6859 bool allows_mem, allows_reg, is_inout;
6860 enum gimplify_status ret, tret;
6861 gasm *stmt;
6862 vec<tree, va_gc> *inputs;
6863 vec<tree, va_gc> *outputs;
6864 vec<tree, va_gc> *clobbers;
6865 vec<tree, va_gc> *labels;
6866 tree link_next;
6868 expr = *expr_p;
6869 noutputs = list_length (ASM_OUTPUTS (expr));
6870 oconstraints = (const char **) alloca ((noutputs) * sizeof (const char *));
6872 inputs = NULL;
6873 outputs = NULL;
6874 clobbers = NULL;
6875 labels = NULL;
6877 ret = GS_ALL_DONE;
6878 link_next = NULL_TREE;
6879 for (i = 0, link = ASM_OUTPUTS (expr); link; ++i, link = link_next)
6881 bool ok;
6882 size_t constraint_len;
6884 link_next = TREE_CHAIN (link);
6886 oconstraints[i]
6887 = constraint
6888 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
6889 constraint_len = strlen (constraint);
6890 if (constraint_len == 0)
6891 continue;
6893 ok = parse_output_constraint (&constraint, i, 0, 0,
6894 &allows_mem, &allows_reg, &is_inout);
6895 if (!ok)
6897 ret = GS_ERROR;
6898 is_inout = false;
6901 /* If we can't make copies, we can only accept memory.
6902 Similarly for VLAs. */
6903 tree outtype = TREE_TYPE (TREE_VALUE (link));
6904 if (outtype != error_mark_node
6905 && (TREE_ADDRESSABLE (outtype)
6906 || !COMPLETE_TYPE_P (outtype)
6907 || !tree_fits_poly_uint64_p (TYPE_SIZE_UNIT (outtype))))
6909 if (allows_mem)
6910 allows_reg = 0;
6911 else
6913 error ("impossible constraint in %<asm%>");
6914 error ("non-memory output %d must stay in memory", i);
6915 return GS_ERROR;
6919 if (!allows_reg && allows_mem)
6920 mark_addressable (TREE_VALUE (link));
6922 tree orig = TREE_VALUE (link);
6923 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6924 is_inout ? is_gimple_min_lval : is_gimple_lvalue,
6925 fb_lvalue | fb_mayfail);
6926 if (tret == GS_ERROR)
6928 if (orig != error_mark_node)
6929 error ("invalid lvalue in %<asm%> output %d", i);
6930 ret = tret;
6933 /* If the constraint does not allow memory make sure we gimplify
6934 it to a register if it is not already but its base is. This
6935 happens for complex and vector components. */
6936 if (!allows_mem)
6938 tree op = TREE_VALUE (link);
6939 if (! is_gimple_val (op)
6940 && is_gimple_reg_type (TREE_TYPE (op))
6941 && is_gimple_reg (get_base_address (op)))
6943 tree tem = create_tmp_reg (TREE_TYPE (op));
6944 tree ass;
6945 if (is_inout)
6947 ass = build2 (MODIFY_EXPR, TREE_TYPE (tem),
6948 tem, unshare_expr (op));
6949 gimplify_and_add (ass, pre_p);
6951 ass = build2 (MODIFY_EXPR, TREE_TYPE (tem), op, tem);
6952 gimplify_and_add (ass, post_p);
6954 TREE_VALUE (link) = tem;
6955 tret = GS_OK;
6959 vec_safe_push (outputs, link);
6960 TREE_CHAIN (link) = NULL_TREE;
6962 if (is_inout)
6964 /* An input/output operand. To give the optimizers more
6965 flexibility, split it into separate input and output
6966 operands. */
6967 tree input;
6968 /* Buffer big enough to format a 32-bit UINT_MAX into. */
6969 char buf[11];
6971 /* Turn the in/out constraint into an output constraint. */
6972 char *p = xstrdup (constraint);
6973 p[0] = '=';
6974 TREE_VALUE (TREE_PURPOSE (link)) = build_string (constraint_len, p);
6976 /* And add a matching input constraint. */
6977 if (allows_reg)
6979 sprintf (buf, "%u", i);
6981 /* If there are multiple alternatives in the constraint,
6982 handle each of them individually. Those that allow register
6983 will be replaced with operand number, the others will stay
6984 unchanged. */
6985 if (strchr (p, ',') != NULL)
6987 size_t len = 0, buflen = strlen (buf);
6988 char *beg, *end, *str, *dst;
6990 for (beg = p + 1;;)
6992 end = strchr (beg, ',');
6993 if (end == NULL)
6994 end = strchr (beg, '\0');
6995 if ((size_t) (end - beg) < buflen)
6996 len += buflen + 1;
6997 else
6998 len += end - beg + 1;
6999 if (*end)
7000 beg = end + 1;
7001 else
7002 break;
7005 str = (char *) alloca (len);
7006 for (beg = p + 1, dst = str;;)
7008 const char *tem;
7009 bool mem_p, reg_p, inout_p;
7011 end = strchr (beg, ',');
7012 if (end)
7013 *end = '\0';
7014 beg[-1] = '=';
7015 tem = beg - 1;
7016 parse_output_constraint (&tem, i, 0, 0,
7017 &mem_p, &reg_p, &inout_p);
7018 if (dst != str)
7019 *dst++ = ',';
7020 if (reg_p)
7022 memcpy (dst, buf, buflen);
7023 dst += buflen;
7025 else
7027 if (end)
7028 len = end - beg;
7029 else
7030 len = strlen (beg);
7031 memcpy (dst, beg, len);
7032 dst += len;
7034 if (end)
7035 beg = end + 1;
7036 else
7037 break;
7039 *dst = '\0';
7040 input = build_string (dst - str, str);
7042 else
7043 input = build_string (strlen (buf), buf);
7045 else
7046 input = build_string (constraint_len - 1, constraint + 1);
7048 free (p);
7050 input = build_tree_list (build_tree_list (NULL_TREE, input),
7051 unshare_expr (TREE_VALUE (link)));
7052 ASM_INPUTS (expr) = chainon (ASM_INPUTS (expr), input);
7056 link_next = NULL_TREE;
7057 for (link = ASM_INPUTS (expr); link; ++i, link = link_next)
7059 link_next = TREE_CHAIN (link);
7060 constraint = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
7061 parse_input_constraint (&constraint, 0, 0, noutputs, 0,
7062 oconstraints, &allows_mem, &allows_reg);
7064 /* If we can't make copies, we can only accept memory. */
7065 tree intype = TREE_TYPE (TREE_VALUE (link));
7066 if (intype != error_mark_node
7067 && (TREE_ADDRESSABLE (intype)
7068 || !COMPLETE_TYPE_P (intype)
7069 || !tree_fits_poly_uint64_p (TYPE_SIZE_UNIT (intype))))
7071 if (allows_mem)
7072 allows_reg = 0;
7073 else
7075 error ("impossible constraint in %<asm%>");
7076 error ("non-memory input %d must stay in memory", i);
7077 return GS_ERROR;
7081 /* If the operand is a memory input, it should be an lvalue. */
7082 if (!allows_reg && allows_mem)
7084 tree inputv = TREE_VALUE (link);
7085 STRIP_NOPS (inputv);
7086 if (TREE_CODE (inputv) == PREDECREMENT_EXPR
7087 || TREE_CODE (inputv) == PREINCREMENT_EXPR
7088 || TREE_CODE (inputv) == POSTDECREMENT_EXPR
7089 || TREE_CODE (inputv) == POSTINCREMENT_EXPR
7090 || TREE_CODE (inputv) == MODIFY_EXPR)
7091 TREE_VALUE (link) = error_mark_node;
7092 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
7093 is_gimple_lvalue, fb_lvalue | fb_mayfail);
7094 if (tret != GS_ERROR)
7096 /* Unlike output operands, memory inputs are not guaranteed
7097 to be lvalues by the FE, and while the expressions are
7098 marked addressable there, if it is e.g. a statement
7099 expression, temporaries in it might not end up being
7100 addressable. They might be already used in the IL and thus
7101 it is too late to make them addressable now though. */
7102 tree x = TREE_VALUE (link);
7103 while (handled_component_p (x))
7104 x = TREE_OPERAND (x, 0);
7105 if (TREE_CODE (x) == MEM_REF
7106 && TREE_CODE (TREE_OPERAND (x, 0)) == ADDR_EXPR)
7107 x = TREE_OPERAND (TREE_OPERAND (x, 0), 0);
7108 if ((VAR_P (x)
7109 || TREE_CODE (x) == PARM_DECL
7110 || TREE_CODE (x) == RESULT_DECL)
7111 && !TREE_ADDRESSABLE (x)
7112 && is_gimple_reg (x))
7114 warning_at (EXPR_LOC_OR_LOC (TREE_VALUE (link),
7115 input_location), 0,
7116 "memory input %d is not directly addressable",
7118 prepare_gimple_addressable (&TREE_VALUE (link), pre_p);
7121 mark_addressable (TREE_VALUE (link));
7122 if (tret == GS_ERROR)
7124 if (inputv != error_mark_node)
7125 error_at (EXPR_LOC_OR_LOC (TREE_VALUE (link), input_location),
7126 "memory input %d is not directly addressable", i);
7127 ret = tret;
7130 else
7132 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
7133 is_gimple_asm_val, fb_rvalue);
7134 if (tret == GS_ERROR)
7135 ret = tret;
7138 TREE_CHAIN (link) = NULL_TREE;
7139 vec_safe_push (inputs, link);
7142 link_next = NULL_TREE;
7143 for (link = ASM_CLOBBERS (expr); link; ++i, link = link_next)
7145 link_next = TREE_CHAIN (link);
7146 TREE_CHAIN (link) = NULL_TREE;
7147 vec_safe_push (clobbers, link);
7150 link_next = NULL_TREE;
7151 for (link = ASM_LABELS (expr); link; ++i, link = link_next)
7153 link_next = TREE_CHAIN (link);
7154 TREE_CHAIN (link) = NULL_TREE;
7155 vec_safe_push (labels, link);
7158 /* Do not add ASMs with errors to the gimple IL stream. */
7159 if (ret != GS_ERROR)
7161 stmt = gimple_build_asm_vec (TREE_STRING_POINTER (ASM_STRING (expr)),
7162 inputs, outputs, clobbers, labels);
7164 /* asm is volatile if it was marked by the user as volatile or
7165 there are no outputs or this is an asm goto. */
7166 gimple_asm_set_volatile (stmt,
7167 ASM_VOLATILE_P (expr)
7168 || noutputs == 0
7169 || labels);
7170 gimple_asm_set_input (stmt, ASM_INPUT_P (expr));
7171 gimple_asm_set_inline (stmt, ASM_INLINE_P (expr));
7173 gimplify_seq_add_stmt (pre_p, stmt);
7176 return ret;
7179 /* Gimplify a CLEANUP_POINT_EXPR. Currently this works by adding
7180 GIMPLE_WITH_CLEANUP_EXPRs to the prequeue as we encounter cleanups while
7181 gimplifying the body, and converting them to TRY_FINALLY_EXPRs when we
7182 return to this function.
7184 FIXME should we complexify the prequeue handling instead? Or use flags
7185 for all the cleanups and let the optimizer tighten them up? The current
7186 code seems pretty fragile; it will break on a cleanup within any
7187 non-conditional nesting. But any such nesting would be broken, anyway;
7188 we can't write a TRY_FINALLY_EXPR that starts inside a nesting construct
7189 and continues out of it. We can do that at the RTL level, though, so
7190 having an optimizer to tighten up try/finally regions would be a Good
7191 Thing. */
7193 static enum gimplify_status
7194 gimplify_cleanup_point_expr (tree *expr_p, gimple_seq *pre_p)
7196 gimple_stmt_iterator iter;
7197 gimple_seq body_sequence = NULL;
7199 tree temp = voidify_wrapper_expr (*expr_p, NULL);
7201 /* We only care about the number of conditions between the innermost
7202 CLEANUP_POINT_EXPR and the cleanup. So save and reset the count and
7203 any cleanups collected outside the CLEANUP_POINT_EXPR. */
7204 int old_conds = gimplify_ctxp->conditions;
7205 gimple_seq old_cleanups = gimplify_ctxp->conditional_cleanups;
7206 bool old_in_cleanup_point_expr = gimplify_ctxp->in_cleanup_point_expr;
7207 gimplify_ctxp->conditions = 0;
7208 gimplify_ctxp->conditional_cleanups = NULL;
7209 gimplify_ctxp->in_cleanup_point_expr = true;
7211 gimplify_stmt (&TREE_OPERAND (*expr_p, 0), &body_sequence);
7213 gimplify_ctxp->conditions = old_conds;
7214 gimplify_ctxp->conditional_cleanups = old_cleanups;
7215 gimplify_ctxp->in_cleanup_point_expr = old_in_cleanup_point_expr;
7217 for (iter = gsi_start (body_sequence); !gsi_end_p (iter); )
7219 gimple *wce = gsi_stmt (iter);
7221 if (gimple_code (wce) == GIMPLE_WITH_CLEANUP_EXPR)
7223 if (gsi_one_before_end_p (iter))
7225 /* Note that gsi_insert_seq_before and gsi_remove do not
7226 scan operands, unlike some other sequence mutators. */
7227 if (!gimple_wce_cleanup_eh_only (wce))
7228 gsi_insert_seq_before_without_update (&iter,
7229 gimple_wce_cleanup (wce),
7230 GSI_SAME_STMT);
7231 gsi_remove (&iter, true);
7232 break;
7234 else
7236 gtry *gtry;
7237 gimple_seq seq;
7238 enum gimple_try_flags kind;
7240 if (gimple_wce_cleanup_eh_only (wce))
7241 kind = GIMPLE_TRY_CATCH;
7242 else
7243 kind = GIMPLE_TRY_FINALLY;
7244 seq = gsi_split_seq_after (iter);
7246 gtry = gimple_build_try (seq, gimple_wce_cleanup (wce), kind);
7247 /* Do not use gsi_replace here, as it may scan operands.
7248 We want to do a simple structural modification only. */
7249 gsi_set_stmt (&iter, gtry);
7250 iter = gsi_start (gtry->eval);
7253 else
7254 gsi_next (&iter);
7257 gimplify_seq_add_seq (pre_p, body_sequence);
7258 if (temp)
7260 *expr_p = temp;
7261 return GS_OK;
7263 else
7265 *expr_p = NULL;
7266 return GS_ALL_DONE;
7270 /* Insert a cleanup marker for gimplify_cleanup_point_expr. CLEANUP
7271 is the cleanup action required. EH_ONLY is true if the cleanup should
7272 only be executed if an exception is thrown, not on normal exit.
7273 If FORCE_UNCOND is true perform the cleanup unconditionally; this is
7274 only valid for clobbers. */
7276 static void
7277 gimple_push_cleanup (tree var, tree cleanup, bool eh_only, gimple_seq *pre_p,
7278 bool force_uncond = false)
7280 gimple *wce;
7281 gimple_seq cleanup_stmts = NULL;
7283 /* Errors can result in improperly nested cleanups. Which results in
7284 confusion when trying to resolve the GIMPLE_WITH_CLEANUP_EXPR. */
7285 if (seen_error ())
7286 return;
7288 if (gimple_conditional_context ())
7290 /* If we're in a conditional context, this is more complex. We only
7291 want to run the cleanup if we actually ran the initialization that
7292 necessitates it, but we want to run it after the end of the
7293 conditional context. So we wrap the try/finally around the
7294 condition and use a flag to determine whether or not to actually
7295 run the destructor. Thus
7297 test ? f(A()) : 0
7299 becomes (approximately)
7301 flag = 0;
7302 try {
7303 if (test) { A::A(temp); flag = 1; val = f(temp); }
7304 else { val = 0; }
7305 } finally {
7306 if (flag) A::~A(temp);
7310 if (force_uncond)
7312 gimplify_stmt (&cleanup, &cleanup_stmts);
7313 wce = gimple_build_wce (cleanup_stmts);
7314 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, wce);
7316 else
7318 tree flag = create_tmp_var (boolean_type_node, "cleanup");
7319 gassign *ffalse = gimple_build_assign (flag, boolean_false_node);
7320 gassign *ftrue = gimple_build_assign (flag, boolean_true_node);
7322 cleanup = build3 (COND_EXPR, void_type_node, flag, cleanup, NULL);
7323 gimplify_stmt (&cleanup, &cleanup_stmts);
7324 wce = gimple_build_wce (cleanup_stmts);
7325 gimple_wce_set_cleanup_eh_only (wce, eh_only);
7327 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, ffalse);
7328 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, wce);
7329 gimplify_seq_add_stmt (pre_p, ftrue);
7331 /* Because of this manipulation, and the EH edges that jump
7332 threading cannot redirect, the temporary (VAR) will appear
7333 to be used uninitialized. Don't warn. */
7334 suppress_warning (var, OPT_Wuninitialized);
7337 else
7339 gimplify_stmt (&cleanup, &cleanup_stmts);
7340 wce = gimple_build_wce (cleanup_stmts);
7341 gimple_wce_set_cleanup_eh_only (wce, eh_only);
7342 gimplify_seq_add_stmt (pre_p, wce);
7346 /* Gimplify a TARGET_EXPR which doesn't appear on the rhs of an INIT_EXPR. */
7348 static enum gimplify_status
7349 gimplify_target_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
7351 tree targ = *expr_p;
7352 tree temp = TARGET_EXPR_SLOT (targ);
7353 tree init = TARGET_EXPR_INITIAL (targ);
7354 enum gimplify_status ret;
7356 bool unpoison_empty_seq = false;
7357 gimple_stmt_iterator unpoison_it;
7359 if (init)
7361 gimple_seq init_pre_p = NULL;
7363 /* TARGET_EXPR temps aren't part of the enclosing block, so add it
7364 to the temps list. Handle also variable length TARGET_EXPRs. */
7365 if (!poly_int_tree_p (DECL_SIZE (temp)))
7367 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (temp)))
7368 gimplify_type_sizes (TREE_TYPE (temp), &init_pre_p);
7369 /* FIXME: this is correct only when the size of the type does
7370 not depend on expressions evaluated in init. */
7371 gimplify_vla_decl (temp, &init_pre_p);
7373 else
7375 /* Save location where we need to place unpoisoning. It's possible
7376 that a variable will be converted to needs_to_live_in_memory. */
7377 unpoison_it = gsi_last (*pre_p);
7378 unpoison_empty_seq = gsi_end_p (unpoison_it);
7380 gimple_add_tmp_var (temp);
7383 /* If TARGET_EXPR_INITIAL is void, then the mere evaluation of the
7384 expression is supposed to initialize the slot. */
7385 if (VOID_TYPE_P (TREE_TYPE (init)))
7386 ret = gimplify_expr (&init, &init_pre_p, post_p, is_gimple_stmt,
7387 fb_none);
7388 else
7390 tree init_expr = build2 (INIT_EXPR, void_type_node, temp, init);
7391 init = init_expr;
7392 ret = gimplify_expr (&init, &init_pre_p, post_p, is_gimple_stmt,
7393 fb_none);
7394 init = NULL;
7395 ggc_free (init_expr);
7397 if (ret == GS_ERROR)
7399 /* PR c++/28266 Make sure this is expanded only once. */
7400 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
7401 return GS_ERROR;
7404 if (init)
7405 gimplify_and_add (init, &init_pre_p);
7407 /* Add a clobber for the temporary going out of scope, like
7408 gimplify_bind_expr. But only if we did not promote the
7409 temporary to static storage. */
7410 if (gimplify_ctxp->in_cleanup_point_expr
7411 && !TREE_STATIC (temp)
7412 && needs_to_live_in_memory (temp))
7414 if (flag_stack_reuse == SR_ALL)
7416 tree clobber = build_clobber (TREE_TYPE (temp), CLOBBER_EOL);
7417 clobber = build2 (MODIFY_EXPR, TREE_TYPE (temp), temp, clobber);
7418 gimple_push_cleanup (temp, clobber, false, pre_p, true);
7420 if (asan_poisoned_variables
7421 && DECL_ALIGN (temp) <= MAX_SUPPORTED_STACK_ALIGNMENT
7422 && !TREE_STATIC (temp)
7423 && dbg_cnt (asan_use_after_scope)
7424 && !gimplify_omp_ctxp)
7426 tree asan_cleanup = build_asan_poison_call_expr (temp);
7427 if (asan_cleanup)
7429 if (unpoison_empty_seq)
7430 unpoison_it = gsi_start (*pre_p);
7432 asan_poison_variable (temp, false, &unpoison_it,
7433 unpoison_empty_seq);
7434 gimple_push_cleanup (temp, asan_cleanup, false, pre_p);
7439 gimple_seq_add_seq (pre_p, init_pre_p);
7441 /* If needed, push the cleanup for the temp. */
7442 if (TARGET_EXPR_CLEANUP (targ))
7443 gimple_push_cleanup (temp, TARGET_EXPR_CLEANUP (targ),
7444 CLEANUP_EH_ONLY (targ), pre_p);
7446 /* Only expand this once. */
7447 TREE_OPERAND (targ, 3) = init;
7448 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
7450 else
7451 /* We should have expanded this before. */
7452 gcc_assert (DECL_SEEN_IN_BIND_EXPR_P (temp));
7454 *expr_p = temp;
7455 return GS_OK;
7458 /* Gimplification of expression trees. */
7460 /* Gimplify an expression which appears at statement context. The
7461 corresponding GIMPLE statements are added to *SEQ_P. If *SEQ_P is
7462 NULL, a new sequence is allocated.
7464 Return true if we actually added a statement to the queue. */
7466 bool
7467 gimplify_stmt (tree *stmt_p, gimple_seq *seq_p)
7469 gimple_seq_node last;
7471 last = gimple_seq_last (*seq_p);
7472 gimplify_expr (stmt_p, seq_p, NULL, is_gimple_stmt, fb_none);
7473 return last != gimple_seq_last (*seq_p);
7476 /* Add FIRSTPRIVATE entries for DECL in the OpenMP the surrounding parallels
7477 to CTX. If entries already exist, force them to be some flavor of private.
7478 If there is no enclosing parallel, do nothing. */
7480 void
7481 omp_firstprivatize_variable (struct gimplify_omp_ctx *ctx, tree decl)
7483 splay_tree_node n;
7485 if (decl == NULL || !DECL_P (decl) || ctx->region_type == ORT_NONE)
7486 return;
7490 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7491 if (n != NULL)
7493 if (n->value & GOVD_SHARED)
7494 n->value = GOVD_FIRSTPRIVATE | (n->value & GOVD_SEEN);
7495 else if (n->value & GOVD_MAP)
7496 n->value |= GOVD_MAP_TO_ONLY;
7497 else
7498 return;
7500 else if ((ctx->region_type & ORT_TARGET) != 0)
7502 if (ctx->defaultmap[GDMK_SCALAR] & GOVD_FIRSTPRIVATE)
7503 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
7504 else
7505 omp_add_variable (ctx, decl, GOVD_MAP | GOVD_MAP_TO_ONLY);
7507 else if (ctx->region_type != ORT_WORKSHARE
7508 && ctx->region_type != ORT_TASKGROUP
7509 && ctx->region_type != ORT_SIMD
7510 && ctx->region_type != ORT_ACC
7511 && !(ctx->region_type & ORT_TARGET_DATA))
7512 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
7514 ctx = ctx->outer_context;
7516 while (ctx);
7519 /* Similarly for each of the type sizes of TYPE. */
7521 static void
7522 omp_firstprivatize_type_sizes (struct gimplify_omp_ctx *ctx, tree type)
7524 if (type == NULL || type == error_mark_node)
7525 return;
7526 type = TYPE_MAIN_VARIANT (type);
7528 if (ctx->privatized_types->add (type))
7529 return;
7531 switch (TREE_CODE (type))
7533 case INTEGER_TYPE:
7534 case ENUMERAL_TYPE:
7535 case BOOLEAN_TYPE:
7536 case REAL_TYPE:
7537 case FIXED_POINT_TYPE:
7538 omp_firstprivatize_variable (ctx, TYPE_MIN_VALUE (type));
7539 omp_firstprivatize_variable (ctx, TYPE_MAX_VALUE (type));
7540 break;
7542 case ARRAY_TYPE:
7543 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
7544 omp_firstprivatize_type_sizes (ctx, TYPE_DOMAIN (type));
7545 break;
7547 case RECORD_TYPE:
7548 case UNION_TYPE:
7549 case QUAL_UNION_TYPE:
7551 tree field;
7552 for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
7553 if (TREE_CODE (field) == FIELD_DECL)
7555 omp_firstprivatize_variable (ctx, DECL_FIELD_OFFSET (field));
7556 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (field));
7559 break;
7561 case POINTER_TYPE:
7562 case REFERENCE_TYPE:
7563 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
7564 break;
7566 default:
7567 break;
7570 omp_firstprivatize_variable (ctx, TYPE_SIZE (type));
7571 omp_firstprivatize_variable (ctx, TYPE_SIZE_UNIT (type));
7572 lang_hooks.types.omp_firstprivatize_type_sizes (ctx, type);
7575 /* Add an entry for DECL in the OMP context CTX with FLAGS. */
7577 static void
7578 omp_add_variable (struct gimplify_omp_ctx *ctx, tree decl, unsigned int flags)
7580 splay_tree_node n;
7581 unsigned int nflags;
7582 tree t;
7584 if (error_operand_p (decl) || ctx->region_type == ORT_NONE)
7585 return;
7587 /* Never elide decls whose type has TREE_ADDRESSABLE set. This means
7588 there are constructors involved somewhere. Exception is a shared clause,
7589 there is nothing privatized in that case. */
7590 if ((flags & GOVD_SHARED) == 0
7591 && (TREE_ADDRESSABLE (TREE_TYPE (decl))
7592 || TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (decl))))
7593 flags |= GOVD_SEEN;
7595 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7596 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
7598 /* We shouldn't be re-adding the decl with the same data
7599 sharing class. */
7600 gcc_assert ((n->value & GOVD_DATA_SHARE_CLASS & flags) == 0);
7601 nflags = n->value | flags;
7602 /* The only combination of data sharing classes we should see is
7603 FIRSTPRIVATE and LASTPRIVATE. However, OpenACC permits
7604 reduction variables to be used in data sharing clauses. */
7605 gcc_assert ((ctx->region_type & ORT_ACC) != 0
7606 || ((nflags & GOVD_DATA_SHARE_CLASS)
7607 == (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE))
7608 || (flags & GOVD_DATA_SHARE_CLASS) == 0);
7609 n->value = nflags;
7610 return;
7613 /* When adding a variable-sized variable, we have to handle all sorts
7614 of additional bits of data: the pointer replacement variable, and
7615 the parameters of the type. */
7616 if (DECL_SIZE (decl) && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
7618 /* Add the pointer replacement variable as PRIVATE if the variable
7619 replacement is private, else FIRSTPRIVATE since we'll need the
7620 address of the original variable either for SHARED, or for the
7621 copy into or out of the context. */
7622 if (!(flags & GOVD_LOCAL) && ctx->region_type != ORT_TASKGROUP)
7624 if (flags & GOVD_MAP)
7625 nflags = GOVD_MAP | GOVD_MAP_TO_ONLY | GOVD_EXPLICIT;
7626 else if (flags & GOVD_PRIVATE)
7627 nflags = GOVD_PRIVATE;
7628 else if (((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0
7629 && (flags & GOVD_FIRSTPRIVATE))
7630 || (ctx->region_type == ORT_TARGET_DATA
7631 && (flags & GOVD_DATA_SHARE_CLASS) == 0))
7632 nflags = GOVD_PRIVATE | GOVD_EXPLICIT;
7633 else
7634 nflags = GOVD_FIRSTPRIVATE;
7635 nflags |= flags & GOVD_SEEN;
7636 t = DECL_VALUE_EXPR (decl);
7637 gcc_assert (INDIRECT_REF_P (t));
7638 t = TREE_OPERAND (t, 0);
7639 gcc_assert (DECL_P (t));
7640 omp_add_variable (ctx, t, nflags);
7643 /* Add all of the variable and type parameters (which should have
7644 been gimplified to a formal temporary) as FIRSTPRIVATE. */
7645 omp_firstprivatize_variable (ctx, DECL_SIZE_UNIT (decl));
7646 omp_firstprivatize_variable (ctx, DECL_SIZE (decl));
7647 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
7649 /* The variable-sized variable itself is never SHARED, only some form
7650 of PRIVATE. The sharing would take place via the pointer variable
7651 which we remapped above. */
7652 if (flags & GOVD_SHARED)
7653 flags = GOVD_SHARED | GOVD_DEBUG_PRIVATE
7654 | (flags & (GOVD_SEEN | GOVD_EXPLICIT));
7656 /* We're going to make use of the TYPE_SIZE_UNIT at least in the
7657 alloca statement we generate for the variable, so make sure it
7658 is available. This isn't automatically needed for the SHARED
7659 case, since we won't be allocating local storage then.
7660 For local variables TYPE_SIZE_UNIT might not be gimplified yet,
7661 in this case omp_notice_variable will be called later
7662 on when it is gimplified. */
7663 else if (! (flags & (GOVD_LOCAL | GOVD_MAP))
7664 && DECL_P (TYPE_SIZE_UNIT (TREE_TYPE (decl))))
7665 omp_notice_variable (ctx, TYPE_SIZE_UNIT (TREE_TYPE (decl)), true);
7667 else if ((flags & (GOVD_MAP | GOVD_LOCAL)) == 0
7668 && omp_privatize_by_reference (decl))
7670 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
7672 /* Similar to the direct variable sized case above, we'll need the
7673 size of references being privatized. */
7674 if ((flags & GOVD_SHARED) == 0)
7676 t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
7677 if (t && DECL_P (t))
7678 omp_notice_variable (ctx, t, true);
7682 if (n != NULL)
7683 n->value |= flags;
7684 else
7685 splay_tree_insert (ctx->variables, (splay_tree_key)decl, flags);
7687 /* For reductions clauses in OpenACC loop directives, by default create a
7688 copy clause on the enclosing parallel construct for carrying back the
7689 results. */
7690 if (ctx->region_type == ORT_ACC && (flags & GOVD_REDUCTION))
7692 struct gimplify_omp_ctx *outer_ctx = ctx->outer_context;
7693 while (outer_ctx)
7695 n = splay_tree_lookup (outer_ctx->variables, (splay_tree_key)decl);
7696 if (n != NULL)
7698 /* Ignore local variables and explicitly declared clauses. */
7699 if (n->value & (GOVD_LOCAL | GOVD_EXPLICIT))
7700 break;
7701 else if (outer_ctx->region_type == ORT_ACC_KERNELS)
7703 /* According to the OpenACC spec, such a reduction variable
7704 should already have a copy map on a kernels construct,
7705 verify that here. */
7706 gcc_assert (!(n->value & GOVD_FIRSTPRIVATE)
7707 && (n->value & GOVD_MAP));
7709 else if (outer_ctx->region_type == ORT_ACC_PARALLEL)
7711 /* Remove firstprivate and make it a copy map. */
7712 n->value &= ~GOVD_FIRSTPRIVATE;
7713 n->value |= GOVD_MAP;
7716 else if (outer_ctx->region_type == ORT_ACC_PARALLEL)
7718 splay_tree_insert (outer_ctx->variables, (splay_tree_key)decl,
7719 GOVD_MAP | GOVD_SEEN);
7720 break;
7722 outer_ctx = outer_ctx->outer_context;
7727 /* Notice a threadprivate variable DECL used in OMP context CTX.
7728 This just prints out diagnostics about threadprivate variable uses
7729 in untied tasks. If DECL2 is non-NULL, prevent this warning
7730 on that variable. */
7732 static bool
7733 omp_notice_threadprivate_variable (struct gimplify_omp_ctx *ctx, tree decl,
7734 tree decl2)
7736 splay_tree_node n;
7737 struct gimplify_omp_ctx *octx;
7739 for (octx = ctx; octx; octx = octx->outer_context)
7740 if ((octx->region_type & ORT_TARGET) != 0
7741 || octx->order_concurrent)
7743 n = splay_tree_lookup (octx->variables, (splay_tree_key)decl);
7744 if (n == NULL)
7746 if (octx->order_concurrent)
7748 error ("threadprivate variable %qE used in a region with"
7749 " %<order(concurrent)%> clause", DECL_NAME (decl));
7750 inform (octx->location, "enclosing region");
7752 else
7754 error ("threadprivate variable %qE used in target region",
7755 DECL_NAME (decl));
7756 inform (octx->location, "enclosing target region");
7758 splay_tree_insert (octx->variables, (splay_tree_key)decl, 0);
7760 if (decl2)
7761 splay_tree_insert (octx->variables, (splay_tree_key)decl2, 0);
7764 if (ctx->region_type != ORT_UNTIED_TASK)
7765 return false;
7766 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7767 if (n == NULL)
7769 error ("threadprivate variable %qE used in untied task",
7770 DECL_NAME (decl));
7771 inform (ctx->location, "enclosing task");
7772 splay_tree_insert (ctx->variables, (splay_tree_key)decl, 0);
7774 if (decl2)
7775 splay_tree_insert (ctx->variables, (splay_tree_key)decl2, 0);
7776 return false;
7779 /* Return true if global var DECL is device resident. */
7781 static bool
7782 device_resident_p (tree decl)
7784 tree attr = lookup_attribute ("oacc declare target", DECL_ATTRIBUTES (decl));
7786 if (!attr)
7787 return false;
7789 for (tree t = TREE_VALUE (attr); t; t = TREE_PURPOSE (t))
7791 tree c = TREE_VALUE (t);
7792 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_DEVICE_RESIDENT)
7793 return true;
7796 return false;
7799 /* Return true if DECL has an ACC DECLARE attribute. */
7801 static bool
7802 is_oacc_declared (tree decl)
7804 tree t = TREE_CODE (decl) == MEM_REF ? TREE_OPERAND (decl, 0) : decl;
7805 tree declared = lookup_attribute ("oacc declare target", DECL_ATTRIBUTES (t));
7806 return declared != NULL_TREE;
7809 /* Determine outer default flags for DECL mentioned in an OMP region
7810 but not declared in an enclosing clause.
7812 ??? Some compiler-generated variables (like SAVE_EXPRs) could be
7813 remapped firstprivate instead of shared. To some extent this is
7814 addressed in omp_firstprivatize_type_sizes, but not
7815 effectively. */
7817 static unsigned
7818 omp_default_clause (struct gimplify_omp_ctx *ctx, tree decl,
7819 bool in_code, unsigned flags)
7821 enum omp_clause_default_kind default_kind = ctx->default_kind;
7822 enum omp_clause_default_kind kind;
7824 kind = lang_hooks.decls.omp_predetermined_sharing (decl);
7825 if (ctx->region_type & ORT_TASK)
7827 tree detach_clause = omp_find_clause (ctx->clauses, OMP_CLAUSE_DETACH);
7829 /* The event-handle specified by a detach clause should always be firstprivate,
7830 regardless of the current default. */
7831 if (detach_clause && OMP_CLAUSE_DECL (detach_clause) == decl)
7832 kind = OMP_CLAUSE_DEFAULT_FIRSTPRIVATE;
7834 if (kind != OMP_CLAUSE_DEFAULT_UNSPECIFIED)
7835 default_kind = kind;
7836 else if (VAR_P (decl) && TREE_STATIC (decl) && DECL_IN_CONSTANT_POOL (decl))
7837 default_kind = OMP_CLAUSE_DEFAULT_SHARED;
7838 /* For C/C++ default({,first}private), variables with static storage duration
7839 declared in a namespace or global scope and referenced in construct
7840 must be explicitly specified, i.e. acts as default(none). */
7841 else if ((default_kind == OMP_CLAUSE_DEFAULT_PRIVATE
7842 || default_kind == OMP_CLAUSE_DEFAULT_FIRSTPRIVATE)
7843 && VAR_P (decl)
7844 && is_global_var (decl)
7845 && (DECL_FILE_SCOPE_P (decl)
7846 || (DECL_CONTEXT (decl)
7847 && TREE_CODE (DECL_CONTEXT (decl)) == NAMESPACE_DECL))
7848 && !lang_GNU_Fortran ())
7849 default_kind = OMP_CLAUSE_DEFAULT_NONE;
7851 switch (default_kind)
7853 case OMP_CLAUSE_DEFAULT_NONE:
7855 const char *rtype;
7857 if (ctx->region_type & ORT_PARALLEL)
7858 rtype = "parallel";
7859 else if ((ctx->region_type & ORT_TASKLOOP) == ORT_TASKLOOP)
7860 rtype = "taskloop";
7861 else if (ctx->region_type & ORT_TASK)
7862 rtype = "task";
7863 else if (ctx->region_type & ORT_TEAMS)
7864 rtype = "teams";
7865 else
7866 gcc_unreachable ();
7868 error ("%qE not specified in enclosing %qs",
7869 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)), rtype);
7870 inform (ctx->location, "enclosing %qs", rtype);
7872 /* FALLTHRU */
7873 case OMP_CLAUSE_DEFAULT_SHARED:
7874 flags |= GOVD_SHARED;
7875 break;
7876 case OMP_CLAUSE_DEFAULT_PRIVATE:
7877 flags |= GOVD_PRIVATE;
7878 break;
7879 case OMP_CLAUSE_DEFAULT_FIRSTPRIVATE:
7880 flags |= GOVD_FIRSTPRIVATE;
7881 break;
7882 case OMP_CLAUSE_DEFAULT_UNSPECIFIED:
7883 /* decl will be either GOVD_FIRSTPRIVATE or GOVD_SHARED. */
7884 gcc_assert ((ctx->region_type & ORT_TASK) != 0);
7885 if (struct gimplify_omp_ctx *octx = ctx->outer_context)
7887 omp_notice_variable (octx, decl, in_code);
7888 for (; octx; octx = octx->outer_context)
7890 splay_tree_node n2;
7892 n2 = splay_tree_lookup (octx->variables, (splay_tree_key) decl);
7893 if ((octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)) != 0
7894 && (n2 == NULL || (n2->value & GOVD_DATA_SHARE_CLASS) == 0))
7895 continue;
7896 if (n2 && (n2->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED)
7898 flags |= GOVD_FIRSTPRIVATE;
7899 goto found_outer;
7901 if ((octx->region_type & (ORT_PARALLEL | ORT_TEAMS)) != 0)
7903 flags |= GOVD_SHARED;
7904 goto found_outer;
7909 if (TREE_CODE (decl) == PARM_DECL
7910 || (!is_global_var (decl)
7911 && DECL_CONTEXT (decl) == current_function_decl))
7912 flags |= GOVD_FIRSTPRIVATE;
7913 else
7914 flags |= GOVD_SHARED;
7915 found_outer:
7916 break;
7918 default:
7919 gcc_unreachable ();
7922 return flags;
7925 /* Return string name for types of OpenACC constructs from ORT_* values. */
7927 static const char *
7928 oacc_region_type_name (enum omp_region_type region_type)
7930 switch (region_type)
7932 case ORT_ACC_DATA:
7933 return "data";
7934 case ORT_ACC_PARALLEL:
7935 return "parallel";
7936 case ORT_ACC_KERNELS:
7937 return "kernels";
7938 case ORT_ACC_SERIAL:
7939 return "serial";
7940 default:
7941 gcc_unreachable ();
7945 /* Determine outer default flags for DECL mentioned in an OACC region
7946 but not declared in an enclosing clause. */
7948 static unsigned
7949 oacc_default_clause (struct gimplify_omp_ctx *ctx, tree decl, unsigned flags)
7951 struct gimplify_omp_ctx *ctx_default = ctx;
7952 /* If no 'default' clause appears on this compute construct... */
7953 if (ctx_default->default_kind == OMP_CLAUSE_DEFAULT_SHARED)
7955 /* ..., see if one appears on a lexically containing 'data'
7956 construct. */
7957 while ((ctx_default = ctx_default->outer_context))
7959 if (ctx_default->region_type == ORT_ACC_DATA
7960 && ctx_default->default_kind != OMP_CLAUSE_DEFAULT_SHARED)
7961 break;
7963 /* If not, reset. */
7964 if (!ctx_default)
7965 ctx_default = ctx;
7968 bool on_device = false;
7969 bool is_private = false;
7970 bool declared = is_oacc_declared (decl);
7971 tree type = TREE_TYPE (decl);
7973 if (omp_privatize_by_reference (decl))
7974 type = TREE_TYPE (type);
7976 /* For Fortran COMMON blocks, only used variables in those blocks are
7977 transfered and remapped. The block itself will have a private clause to
7978 avoid transfering the data twice.
7979 The hook evaluates to false by default. For a variable in Fortran's COMMON
7980 or EQUIVALENCE block, returns 'true' (as we have shared=false) - as only
7981 the variables in such a COMMON/EQUIVALENCE block shall be privatized not
7982 the whole block. For C++ and Fortran, it can also be true under certain
7983 other conditions, if DECL_HAS_VALUE_EXPR. */
7984 if (RECORD_OR_UNION_TYPE_P (type))
7985 is_private = lang_hooks.decls.omp_disregard_value_expr (decl, false);
7987 if ((ctx->region_type & (ORT_ACC_PARALLEL | ORT_ACC_KERNELS)) != 0
7988 && is_global_var (decl)
7989 && device_resident_p (decl)
7990 && !is_private)
7992 on_device = true;
7993 flags |= GOVD_MAP_TO_ONLY;
7996 switch (ctx->region_type)
7998 case ORT_ACC_KERNELS:
7999 if (is_private)
8000 flags |= GOVD_FIRSTPRIVATE;
8001 else if (AGGREGATE_TYPE_P (type))
8003 /* Aggregates default to 'present_or_copy', or 'present'. */
8004 if (ctx_default->default_kind != OMP_CLAUSE_DEFAULT_PRESENT)
8005 flags |= GOVD_MAP;
8006 else
8007 flags |= GOVD_MAP | GOVD_MAP_FORCE_PRESENT;
8009 else
8010 /* Scalars default to 'copy'. */
8011 flags |= GOVD_MAP | GOVD_MAP_FORCE;
8013 break;
8015 case ORT_ACC_PARALLEL:
8016 case ORT_ACC_SERIAL:
8017 if (is_private)
8018 flags |= GOVD_FIRSTPRIVATE;
8019 else if (on_device || declared)
8020 flags |= GOVD_MAP;
8021 else if (AGGREGATE_TYPE_P (type))
8023 /* Aggregates default to 'present_or_copy', or 'present'. */
8024 if (ctx_default->default_kind != OMP_CLAUSE_DEFAULT_PRESENT)
8025 flags |= GOVD_MAP;
8026 else
8027 flags |= GOVD_MAP | GOVD_MAP_FORCE_PRESENT;
8029 else
8030 /* Scalars default to 'firstprivate'. */
8031 flags |= GOVD_FIRSTPRIVATE;
8033 break;
8035 default:
8036 gcc_unreachable ();
8039 if (DECL_ARTIFICIAL (decl))
8040 ; /* We can get compiler-generated decls, and should not complain
8041 about them. */
8042 else if (ctx_default->default_kind == OMP_CLAUSE_DEFAULT_NONE)
8044 error ("%qE not specified in enclosing OpenACC %qs construct",
8045 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)),
8046 oacc_region_type_name (ctx->region_type));
8047 if (ctx_default != ctx)
8048 inform (ctx->location, "enclosing OpenACC %qs construct and",
8049 oacc_region_type_name (ctx->region_type));
8050 inform (ctx_default->location,
8051 "enclosing OpenACC %qs construct with %qs clause",
8052 oacc_region_type_name (ctx_default->region_type),
8053 "default(none)");
8055 else if (ctx_default->default_kind == OMP_CLAUSE_DEFAULT_PRESENT)
8056 ; /* Handled above. */
8057 else
8058 gcc_checking_assert (ctx_default->default_kind == OMP_CLAUSE_DEFAULT_SHARED);
8060 return flags;
8063 /* Record the fact that DECL was used within the OMP context CTX.
8064 IN_CODE is true when real code uses DECL, and false when we should
8065 merely emit default(none) errors. Return true if DECL is going to
8066 be remapped and thus DECL shouldn't be gimplified into its
8067 DECL_VALUE_EXPR (if any). */
8069 static bool
8070 omp_notice_variable (struct gimplify_omp_ctx *ctx, tree decl, bool in_code)
8072 splay_tree_node n;
8073 unsigned flags = in_code ? GOVD_SEEN : 0;
8074 bool ret = false, shared;
8076 if (error_operand_p (decl))
8077 return false;
8079 if (DECL_ARTIFICIAL (decl))
8081 tree attr = lookup_attribute ("omp allocate var", DECL_ATTRIBUTES (decl));
8082 if (attr)
8083 decl = TREE_VALUE (TREE_VALUE (attr));
8086 if (ctx->region_type == ORT_NONE)
8087 return lang_hooks.decls.omp_disregard_value_expr (decl, false);
8089 if (is_global_var (decl))
8091 /* Threadprivate variables are predetermined. */
8092 if (DECL_THREAD_LOCAL_P (decl))
8093 return omp_notice_threadprivate_variable (ctx, decl, NULL_TREE);
8095 if (DECL_HAS_VALUE_EXPR_P (decl))
8097 if (ctx->region_type & ORT_ACC)
8098 /* For OpenACC, defer expansion of value to avoid transfering
8099 privatized common block data instead of im-/explicitly transfered
8100 variables which are in common blocks. */
8102 else
8104 tree value = get_base_address (DECL_VALUE_EXPR (decl));
8106 if (value && DECL_P (value) && DECL_THREAD_LOCAL_P (value))
8107 return omp_notice_threadprivate_variable (ctx, decl, value);
8111 if (gimplify_omp_ctxp->outer_context == NULL
8112 && VAR_P (decl)
8113 && oacc_get_fn_attrib (current_function_decl))
8115 location_t loc = DECL_SOURCE_LOCATION (decl);
8117 if (lookup_attribute ("omp declare target link",
8118 DECL_ATTRIBUTES (decl)))
8120 error_at (loc,
8121 "%qE with %<link%> clause used in %<routine%> function",
8122 DECL_NAME (decl));
8123 return false;
8125 else if (!lookup_attribute ("omp declare target",
8126 DECL_ATTRIBUTES (decl)))
8128 error_at (loc,
8129 "%qE requires a %<declare%> directive for use "
8130 "in a %<routine%> function", DECL_NAME (decl));
8131 return false;
8136 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
8137 if ((ctx->region_type & ORT_TARGET) != 0)
8139 if (ctx->region_type & ORT_ACC)
8140 /* For OpenACC, as remarked above, defer expansion. */
8141 shared = false;
8142 else
8143 shared = true;
8145 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
8146 if (n == NULL)
8148 unsigned nflags = flags;
8149 if ((ctx->region_type & ORT_ACC) == 0)
8151 bool is_declare_target = false;
8152 if (is_global_var (decl)
8153 && varpool_node::get_create (decl)->offloadable)
8155 struct gimplify_omp_ctx *octx;
8156 for (octx = ctx->outer_context;
8157 octx; octx = octx->outer_context)
8159 n = splay_tree_lookup (octx->variables,
8160 (splay_tree_key)decl);
8161 if (n
8162 && (n->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED
8163 && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
8164 break;
8166 is_declare_target = octx == NULL;
8168 if (!is_declare_target)
8170 int gdmk;
8171 enum omp_clause_defaultmap_kind kind;
8172 if (lang_hooks.decls.omp_allocatable_p (decl))
8173 gdmk = GDMK_ALLOCATABLE;
8174 else if (lang_hooks.decls.omp_scalar_target_p (decl))
8175 gdmk = GDMK_SCALAR_TARGET;
8176 else if (lang_hooks.decls.omp_scalar_p (decl, false))
8177 gdmk = GDMK_SCALAR;
8178 else if (TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE
8179 || (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
8180 && (TREE_CODE (TREE_TYPE (TREE_TYPE (decl)))
8181 == POINTER_TYPE)))
8182 gdmk = GDMK_POINTER;
8183 else
8184 gdmk = GDMK_AGGREGATE;
8185 kind = lang_hooks.decls.omp_predetermined_mapping (decl);
8186 if (kind != OMP_CLAUSE_DEFAULTMAP_CATEGORY_UNSPECIFIED)
8188 if (kind == OMP_CLAUSE_DEFAULTMAP_FIRSTPRIVATE)
8189 nflags |= GOVD_FIRSTPRIVATE;
8190 else if (kind == OMP_CLAUSE_DEFAULTMAP_TO)
8191 nflags |= GOVD_MAP | GOVD_MAP_TO_ONLY;
8192 else
8193 gcc_unreachable ();
8195 else if (ctx->defaultmap[gdmk] == 0)
8197 tree d = lang_hooks.decls.omp_report_decl (decl);
8198 error ("%qE not specified in enclosing %<target%>",
8199 DECL_NAME (d));
8200 inform (ctx->location, "enclosing %<target%>");
8202 else if (ctx->defaultmap[gdmk]
8203 & (GOVD_MAP_0LEN_ARRAY | GOVD_FIRSTPRIVATE))
8204 nflags |= ctx->defaultmap[gdmk];
8205 else if (ctx->defaultmap[gdmk] & GOVD_MAP_FORCE_PRESENT)
8207 gcc_assert (ctx->defaultmap[gdmk] & GOVD_MAP);
8208 nflags |= ctx->defaultmap[gdmk] | GOVD_MAP_ALLOC_ONLY;
8210 else
8212 gcc_assert (ctx->defaultmap[gdmk] & GOVD_MAP);
8213 nflags |= ctx->defaultmap[gdmk] & ~GOVD_MAP;
8218 struct gimplify_omp_ctx *octx = ctx->outer_context;
8219 if ((ctx->region_type & ORT_ACC) && octx)
8221 /* Look in outer OpenACC contexts, to see if there's a
8222 data attribute for this variable. */
8223 omp_notice_variable (octx, decl, in_code);
8225 for (; octx; octx = octx->outer_context)
8227 if (!(octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)))
8228 break;
8229 splay_tree_node n2
8230 = splay_tree_lookup (octx->variables,
8231 (splay_tree_key) decl);
8232 if (n2)
8234 if (octx->region_type == ORT_ACC_HOST_DATA)
8235 error ("variable %qE declared in enclosing "
8236 "%<host_data%> region", DECL_NAME (decl));
8237 nflags |= GOVD_MAP;
8238 if (octx->region_type == ORT_ACC_DATA
8239 && (n2->value & GOVD_MAP_0LEN_ARRAY))
8240 nflags |= GOVD_MAP_0LEN_ARRAY;
8241 goto found_outer;
8246 if ((nflags & ~(GOVD_MAP_TO_ONLY | GOVD_MAP_FROM_ONLY
8247 | GOVD_MAP_ALLOC_ONLY)) == flags)
8249 tree type = TREE_TYPE (decl);
8251 if (gimplify_omp_ctxp->target_firstprivatize_array_bases
8252 && omp_privatize_by_reference (decl))
8253 type = TREE_TYPE (type);
8254 if (!omp_mappable_type (type))
8256 error ("%qD referenced in target region does not have "
8257 "a mappable type", decl);
8258 nflags |= GOVD_MAP | GOVD_EXPLICIT;
8260 else
8262 if ((ctx->region_type & ORT_ACC) != 0)
8263 nflags = oacc_default_clause (ctx, decl, flags);
8264 else
8265 nflags |= GOVD_MAP;
8268 found_outer:
8269 omp_add_variable (ctx, decl, nflags);
8271 else
8273 /* If nothing changed, there's nothing left to do. */
8274 if ((n->value & flags) == flags)
8275 return ret;
8276 flags |= n->value;
8277 n->value = flags;
8279 goto do_outer;
8282 if (n == NULL)
8284 if (ctx->region_type == ORT_WORKSHARE
8285 || ctx->region_type == ORT_TASKGROUP
8286 || ctx->region_type == ORT_SIMD
8287 || ctx->region_type == ORT_ACC
8288 || (ctx->region_type & ORT_TARGET_DATA) != 0)
8289 goto do_outer;
8291 flags = omp_default_clause (ctx, decl, in_code, flags);
8293 if ((flags & GOVD_PRIVATE)
8294 && lang_hooks.decls.omp_private_outer_ref (decl))
8295 flags |= GOVD_PRIVATE_OUTER_REF;
8297 omp_add_variable (ctx, decl, flags);
8299 shared = (flags & GOVD_SHARED) != 0;
8300 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
8301 goto do_outer;
8304 /* Don't mark as GOVD_SEEN addressable temporaries seen only in simd
8305 lb, b or incr expressions, those shouldn't be turned into simd arrays. */
8306 if (ctx->region_type == ORT_SIMD
8307 && ctx->in_for_exprs
8308 && ((n->value & (GOVD_PRIVATE | GOVD_SEEN | GOVD_EXPLICIT))
8309 == GOVD_PRIVATE))
8310 flags &= ~GOVD_SEEN;
8312 if ((n->value & (GOVD_SEEN | GOVD_LOCAL)) == 0
8313 && (flags & (GOVD_SEEN | GOVD_LOCAL)) == GOVD_SEEN
8314 && DECL_SIZE (decl))
8316 if (TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
8318 splay_tree_node n2;
8319 tree t = DECL_VALUE_EXPR (decl);
8320 gcc_assert (INDIRECT_REF_P (t));
8321 t = TREE_OPERAND (t, 0);
8322 gcc_assert (DECL_P (t));
8323 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
8324 n2->value |= GOVD_SEEN;
8326 else if (omp_privatize_by_reference (decl)
8327 && TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)))
8328 && (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl))))
8329 != INTEGER_CST))
8331 splay_tree_node n2;
8332 tree t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
8333 gcc_assert (DECL_P (t));
8334 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
8335 if (n2)
8336 omp_notice_variable (ctx, t, true);
8340 if (ctx->region_type & ORT_ACC)
8341 /* For OpenACC, as remarked above, defer expansion. */
8342 shared = false;
8343 else
8344 shared = ((flags | n->value) & GOVD_SHARED) != 0;
8345 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
8347 /* If nothing changed, there's nothing left to do. */
8348 if ((n->value & flags) == flags)
8349 return ret;
8350 flags |= n->value;
8351 n->value = flags;
8353 do_outer:
8354 /* If the variable is private in the current context, then we don't
8355 need to propagate anything to an outer context. */
8356 if ((flags & GOVD_PRIVATE) && !(flags & GOVD_PRIVATE_OUTER_REF))
8357 return ret;
8358 if ((flags & (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
8359 == (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
8360 return ret;
8361 if ((flags & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
8362 | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
8363 == (GOVD_LASTPRIVATE | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
8364 return ret;
8365 if (ctx->outer_context
8366 && omp_notice_variable (ctx->outer_context, decl, in_code))
8367 return true;
8368 return ret;
8371 /* Verify that DECL is private within CTX. If there's specific information
8372 to the contrary in the innermost scope, generate an error. */
8374 static bool
8375 omp_is_private (struct gimplify_omp_ctx *ctx, tree decl, int simd)
8377 splay_tree_node n;
8379 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
8380 if (n != NULL)
8382 if (n->value & GOVD_SHARED)
8384 if (ctx == gimplify_omp_ctxp)
8386 if (simd)
8387 error ("iteration variable %qE is predetermined linear",
8388 DECL_NAME (decl));
8389 else
8390 error ("iteration variable %qE should be private",
8391 DECL_NAME (decl));
8392 n->value = GOVD_PRIVATE;
8393 return true;
8395 else
8396 return false;
8398 else if ((n->value & GOVD_EXPLICIT) != 0
8399 && (ctx == gimplify_omp_ctxp
8400 || (ctx->region_type == ORT_COMBINED_PARALLEL
8401 && gimplify_omp_ctxp->outer_context == ctx)))
8403 if ((n->value & GOVD_FIRSTPRIVATE) != 0)
8404 error ("iteration variable %qE should not be firstprivate",
8405 DECL_NAME (decl));
8406 else if ((n->value & GOVD_REDUCTION) != 0)
8407 error ("iteration variable %qE should not be reduction",
8408 DECL_NAME (decl));
8409 else if (simd != 1 && (n->value & GOVD_LINEAR) != 0)
8410 error ("iteration variable %qE should not be linear",
8411 DECL_NAME (decl));
8413 return (ctx == gimplify_omp_ctxp
8414 || (ctx->region_type == ORT_COMBINED_PARALLEL
8415 && gimplify_omp_ctxp->outer_context == ctx));
8418 if (ctx->region_type != ORT_WORKSHARE
8419 && ctx->region_type != ORT_TASKGROUP
8420 && ctx->region_type != ORT_SIMD
8421 && ctx->region_type != ORT_ACC)
8422 return false;
8423 else if (ctx->outer_context)
8424 return omp_is_private (ctx->outer_context, decl, simd);
8425 return false;
8428 /* Return true if DECL is private within a parallel region
8429 that binds to the current construct's context or in parallel
8430 region's REDUCTION clause. */
8432 static bool
8433 omp_check_private (struct gimplify_omp_ctx *ctx, tree decl, bool copyprivate)
8435 splay_tree_node n;
8439 ctx = ctx->outer_context;
8440 if (ctx == NULL)
8442 if (is_global_var (decl))
8443 return false;
8445 /* References might be private, but might be shared too,
8446 when checking for copyprivate, assume they might be
8447 private, otherwise assume they might be shared. */
8448 if (copyprivate)
8449 return true;
8451 if (omp_privatize_by_reference (decl))
8452 return false;
8454 /* Treat C++ privatized non-static data members outside
8455 of the privatization the same. */
8456 if (omp_member_access_dummy_var (decl))
8457 return false;
8459 return true;
8462 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8464 if ((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0
8465 && (n == NULL || (n->value & GOVD_DATA_SHARE_CLASS) == 0))
8467 if ((ctx->region_type & ORT_TARGET_DATA) != 0
8468 || n == NULL
8469 || (n->value & GOVD_MAP) == 0)
8470 continue;
8471 return false;
8474 if (n != NULL)
8476 if ((n->value & GOVD_LOCAL) != 0
8477 && omp_member_access_dummy_var (decl))
8478 return false;
8479 return (n->value & GOVD_SHARED) == 0;
8482 if (ctx->region_type == ORT_WORKSHARE
8483 || ctx->region_type == ORT_TASKGROUP
8484 || ctx->region_type == ORT_SIMD
8485 || ctx->region_type == ORT_ACC)
8486 continue;
8488 break;
8490 while (1);
8491 return false;
8494 /* Callback for walk_tree to find a DECL_EXPR for the given DECL. */
8496 static tree
8497 find_decl_expr (tree *tp, int *walk_subtrees, void *data)
8499 tree t = *tp;
8501 /* If this node has been visited, unmark it and keep looking. */
8502 if (TREE_CODE (t) == DECL_EXPR && DECL_EXPR_DECL (t) == (tree) data)
8503 return t;
8505 if (IS_TYPE_OR_DECL_P (t))
8506 *walk_subtrees = 0;
8507 return NULL_TREE;
8511 /* Gimplify the affinity clause but effectively ignore it.
8512 Generate:
8513 var = begin;
8514 if ((step > 1) ? var <= end : var > end)
8515 locatator_var_expr; */
8517 static void
8518 gimplify_omp_affinity (tree *list_p, gimple_seq *pre_p)
8520 tree last_iter = NULL_TREE;
8521 tree last_bind = NULL_TREE;
8522 tree label = NULL_TREE;
8523 tree *last_body = NULL;
8524 for (tree c = *list_p; c; c = OMP_CLAUSE_CHAIN (c))
8525 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_AFFINITY)
8527 tree t = OMP_CLAUSE_DECL (c);
8528 if (TREE_CODE (t) == TREE_LIST
8529 && TREE_PURPOSE (t)
8530 && TREE_CODE (TREE_PURPOSE (t)) == TREE_VEC)
8532 if (TREE_VALUE (t) == null_pointer_node)
8533 continue;
8534 if (TREE_PURPOSE (t) != last_iter)
8536 if (last_bind)
8538 append_to_statement_list (label, last_body);
8539 gimplify_and_add (last_bind, pre_p);
8540 last_bind = NULL_TREE;
8542 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8544 if (gimplify_expr (&TREE_VEC_ELT (it, 1), pre_p, NULL,
8545 is_gimple_val, fb_rvalue) == GS_ERROR
8546 || gimplify_expr (&TREE_VEC_ELT (it, 2), pre_p, NULL,
8547 is_gimple_val, fb_rvalue) == GS_ERROR
8548 || gimplify_expr (&TREE_VEC_ELT (it, 3), pre_p, NULL,
8549 is_gimple_val, fb_rvalue) == GS_ERROR
8550 || (gimplify_expr (&TREE_VEC_ELT (it, 4), pre_p, NULL,
8551 is_gimple_val, fb_rvalue)
8552 == GS_ERROR))
8553 return;
8555 last_iter = TREE_PURPOSE (t);
8556 tree block = TREE_VEC_ELT (TREE_PURPOSE (t), 5);
8557 last_bind = build3 (BIND_EXPR, void_type_node, BLOCK_VARS (block),
8558 NULL, block);
8559 last_body = &BIND_EXPR_BODY (last_bind);
8560 tree cond = NULL_TREE;
8561 location_t loc = OMP_CLAUSE_LOCATION (c);
8562 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8564 tree var = TREE_VEC_ELT (it, 0);
8565 tree begin = TREE_VEC_ELT (it, 1);
8566 tree end = TREE_VEC_ELT (it, 2);
8567 tree step = TREE_VEC_ELT (it, 3);
8568 loc = DECL_SOURCE_LOCATION (var);
8569 tree tem = build2_loc (loc, MODIFY_EXPR, void_type_node,
8570 var, begin);
8571 append_to_statement_list_force (tem, last_body);
8573 tree cond1 = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8574 step, build_zero_cst (TREE_TYPE (step)));
8575 tree cond2 = fold_build2_loc (loc, LE_EXPR, boolean_type_node,
8576 var, end);
8577 tree cond3 = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8578 var, end);
8579 cond1 = fold_build3_loc (loc, COND_EXPR, boolean_type_node,
8580 cond1, cond2, cond3);
8581 if (cond)
8582 cond = fold_build2_loc (loc, TRUTH_AND_EXPR,
8583 boolean_type_node, cond, cond1);
8584 else
8585 cond = cond1;
8587 tree cont_label = create_artificial_label (loc);
8588 label = build1 (LABEL_EXPR, void_type_node, cont_label);
8589 tree tem = fold_build3_loc (loc, COND_EXPR, void_type_node, cond,
8590 void_node,
8591 build_and_jump (&cont_label));
8592 append_to_statement_list_force (tem, last_body);
8594 if (TREE_CODE (TREE_VALUE (t)) == COMPOUND_EXPR)
8596 append_to_statement_list (TREE_OPERAND (TREE_VALUE (t), 0),
8597 last_body);
8598 TREE_VALUE (t) = TREE_OPERAND (TREE_VALUE (t), 1);
8600 if (error_operand_p (TREE_VALUE (t)))
8601 return;
8602 append_to_statement_list_force (TREE_VALUE (t), last_body);
8603 TREE_VALUE (t) = null_pointer_node;
8605 else
8607 if (last_bind)
8609 append_to_statement_list (label, last_body);
8610 gimplify_and_add (last_bind, pre_p);
8611 last_bind = NULL_TREE;
8613 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
8615 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
8616 NULL, is_gimple_val, fb_rvalue);
8617 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
8619 if (error_operand_p (OMP_CLAUSE_DECL (c)))
8620 return;
8621 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
8622 is_gimple_lvalue, fb_lvalue) == GS_ERROR)
8623 return;
8624 gimplify_and_add (OMP_CLAUSE_DECL (c), pre_p);
8627 if (last_bind)
8629 append_to_statement_list (label, last_body);
8630 gimplify_and_add (last_bind, pre_p);
8632 return;
8635 /* If *LIST_P contains any OpenMP depend clauses with iterators,
8636 lower all the depend clauses by populating corresponding depend
8637 array. Returns 0 if there are no such depend clauses, or
8638 2 if all depend clauses should be removed, 1 otherwise. */
8640 static int
8641 gimplify_omp_depend (tree *list_p, gimple_seq *pre_p)
8643 tree c;
8644 gimple *g;
8645 size_t n[5] = { 0, 0, 0, 0, 0 };
8646 bool unused[5];
8647 tree counts[5] = { NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE };
8648 tree last_iter = NULL_TREE, last_count = NULL_TREE;
8649 size_t i, j;
8650 location_t first_loc = UNKNOWN_LOCATION;
8652 for (c = *list_p; c; c = OMP_CLAUSE_CHAIN (c))
8653 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND)
8655 switch (OMP_CLAUSE_DEPEND_KIND (c))
8657 case OMP_CLAUSE_DEPEND_IN:
8658 i = 2;
8659 break;
8660 case OMP_CLAUSE_DEPEND_OUT:
8661 case OMP_CLAUSE_DEPEND_INOUT:
8662 i = 0;
8663 break;
8664 case OMP_CLAUSE_DEPEND_MUTEXINOUTSET:
8665 i = 1;
8666 break;
8667 case OMP_CLAUSE_DEPEND_DEPOBJ:
8668 i = 3;
8669 break;
8670 case OMP_CLAUSE_DEPEND_INOUTSET:
8671 i = 4;
8672 break;
8673 default:
8674 gcc_unreachable ();
8676 tree t = OMP_CLAUSE_DECL (c);
8677 if (first_loc == UNKNOWN_LOCATION)
8678 first_loc = OMP_CLAUSE_LOCATION (c);
8679 if (TREE_CODE (t) == TREE_LIST
8680 && TREE_PURPOSE (t)
8681 && TREE_CODE (TREE_PURPOSE (t)) == TREE_VEC)
8683 if (TREE_PURPOSE (t) != last_iter)
8685 tree tcnt = size_one_node;
8686 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8688 if (gimplify_expr (&TREE_VEC_ELT (it, 1), pre_p, NULL,
8689 is_gimple_val, fb_rvalue) == GS_ERROR
8690 || gimplify_expr (&TREE_VEC_ELT (it, 2), pre_p, NULL,
8691 is_gimple_val, fb_rvalue) == GS_ERROR
8692 || gimplify_expr (&TREE_VEC_ELT (it, 3), pre_p, NULL,
8693 is_gimple_val, fb_rvalue) == GS_ERROR
8694 || (gimplify_expr (&TREE_VEC_ELT (it, 4), pre_p, NULL,
8695 is_gimple_val, fb_rvalue)
8696 == GS_ERROR))
8697 return 2;
8698 tree var = TREE_VEC_ELT (it, 0);
8699 tree begin = TREE_VEC_ELT (it, 1);
8700 tree end = TREE_VEC_ELT (it, 2);
8701 tree step = TREE_VEC_ELT (it, 3);
8702 tree orig_step = TREE_VEC_ELT (it, 4);
8703 tree type = TREE_TYPE (var);
8704 tree stype = TREE_TYPE (step);
8705 location_t loc = DECL_SOURCE_LOCATION (var);
8706 tree endmbegin;
8707 /* Compute count for this iterator as
8708 orig_step > 0
8709 ? (begin < end ? (end - begin + (step - 1)) / step : 0)
8710 : (begin > end ? (end - begin + (step + 1)) / step : 0)
8711 and compute product of those for the entire depend
8712 clause. */
8713 if (POINTER_TYPE_P (type))
8714 endmbegin = fold_build2_loc (loc, POINTER_DIFF_EXPR,
8715 stype, end, begin);
8716 else
8717 endmbegin = fold_build2_loc (loc, MINUS_EXPR, type,
8718 end, begin);
8719 tree stepm1 = fold_build2_loc (loc, MINUS_EXPR, stype,
8720 step,
8721 build_int_cst (stype, 1));
8722 tree stepp1 = fold_build2_loc (loc, PLUS_EXPR, stype, step,
8723 build_int_cst (stype, 1));
8724 tree pos = fold_build2_loc (loc, PLUS_EXPR, stype,
8725 unshare_expr (endmbegin),
8726 stepm1);
8727 pos = fold_build2_loc (loc, TRUNC_DIV_EXPR, stype,
8728 pos, step);
8729 tree neg = fold_build2_loc (loc, PLUS_EXPR, stype,
8730 endmbegin, stepp1);
8731 if (TYPE_UNSIGNED (stype))
8733 neg = fold_build1_loc (loc, NEGATE_EXPR, stype, neg);
8734 step = fold_build1_loc (loc, NEGATE_EXPR, stype, step);
8736 neg = fold_build2_loc (loc, TRUNC_DIV_EXPR, stype,
8737 neg, step);
8738 step = NULL_TREE;
8739 tree cond = fold_build2_loc (loc, LT_EXPR,
8740 boolean_type_node,
8741 begin, end);
8742 pos = fold_build3_loc (loc, COND_EXPR, stype, cond, pos,
8743 build_int_cst (stype, 0));
8744 cond = fold_build2_loc (loc, LT_EXPR, boolean_type_node,
8745 end, begin);
8746 neg = fold_build3_loc (loc, COND_EXPR, stype, cond, neg,
8747 build_int_cst (stype, 0));
8748 tree osteptype = TREE_TYPE (orig_step);
8749 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8750 orig_step,
8751 build_int_cst (osteptype, 0));
8752 tree cnt = fold_build3_loc (loc, COND_EXPR, stype,
8753 cond, pos, neg);
8754 cnt = fold_convert_loc (loc, sizetype, cnt);
8755 if (gimplify_expr (&cnt, pre_p, NULL, is_gimple_val,
8756 fb_rvalue) == GS_ERROR)
8757 return 2;
8758 tcnt = size_binop_loc (loc, MULT_EXPR, tcnt, cnt);
8760 if (gimplify_expr (&tcnt, pre_p, NULL, is_gimple_val,
8761 fb_rvalue) == GS_ERROR)
8762 return 2;
8763 last_iter = TREE_PURPOSE (t);
8764 last_count = tcnt;
8766 if (counts[i] == NULL_TREE)
8767 counts[i] = last_count;
8768 else
8769 counts[i] = size_binop_loc (OMP_CLAUSE_LOCATION (c),
8770 PLUS_EXPR, counts[i], last_count);
8772 else
8773 n[i]++;
8775 for (i = 0; i < 5; i++)
8776 if (counts[i])
8777 break;
8778 if (i == 5)
8779 return 0;
8781 tree total = size_zero_node;
8782 for (i = 0; i < 5; i++)
8784 unused[i] = counts[i] == NULL_TREE && n[i] == 0;
8785 if (counts[i] == NULL_TREE)
8786 counts[i] = size_zero_node;
8787 if (n[i])
8788 counts[i] = size_binop (PLUS_EXPR, counts[i], size_int (n[i]));
8789 if (gimplify_expr (&counts[i], pre_p, NULL, is_gimple_val,
8790 fb_rvalue) == GS_ERROR)
8791 return 2;
8792 total = size_binop (PLUS_EXPR, total, counts[i]);
8795 if (gimplify_expr (&total, pre_p, NULL, is_gimple_val, fb_rvalue)
8796 == GS_ERROR)
8797 return 2;
8798 bool is_old = unused[1] && unused[3] && unused[4];
8799 tree totalpx = size_binop (PLUS_EXPR, unshare_expr (total),
8800 size_int (is_old ? 1 : 4));
8801 if (!unused[4])
8802 totalpx = size_binop (PLUS_EXPR, totalpx,
8803 size_binop (MULT_EXPR, counts[4], size_int (2)));
8804 tree type = build_array_type (ptr_type_node, build_index_type (totalpx));
8805 tree array = create_tmp_var_raw (type);
8806 TREE_ADDRESSABLE (array) = 1;
8807 if (!poly_int_tree_p (totalpx))
8809 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (array)))
8810 gimplify_type_sizes (TREE_TYPE (array), pre_p);
8811 if (gimplify_omp_ctxp)
8813 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8814 while (ctx
8815 && (ctx->region_type == ORT_WORKSHARE
8816 || ctx->region_type == ORT_TASKGROUP
8817 || ctx->region_type == ORT_SIMD
8818 || ctx->region_type == ORT_ACC))
8819 ctx = ctx->outer_context;
8820 if (ctx)
8821 omp_add_variable (ctx, array, GOVD_LOCAL | GOVD_SEEN);
8823 gimplify_vla_decl (array, pre_p);
8825 else
8826 gimple_add_tmp_var (array);
8827 tree r = build4 (ARRAY_REF, ptr_type_node, array, size_int (0), NULL_TREE,
8828 NULL_TREE);
8829 tree tem;
8830 if (!is_old)
8832 tem = build2 (MODIFY_EXPR, void_type_node, r,
8833 build_int_cst (ptr_type_node, 0));
8834 gimplify_and_add (tem, pre_p);
8835 r = build4 (ARRAY_REF, ptr_type_node, array, size_int (1), NULL_TREE,
8836 NULL_TREE);
8838 tem = build2 (MODIFY_EXPR, void_type_node, r,
8839 fold_convert (ptr_type_node, total));
8840 gimplify_and_add (tem, pre_p);
8841 for (i = 1; i < (is_old ? 2 : 4); i++)
8843 r = build4 (ARRAY_REF, ptr_type_node, array, size_int (i + !is_old),
8844 NULL_TREE, NULL_TREE);
8845 tem = build2 (MODIFY_EXPR, void_type_node, r, counts[i - 1]);
8846 gimplify_and_add (tem, pre_p);
8849 tree cnts[6];
8850 for (j = 5; j; j--)
8851 if (!unused[j - 1])
8852 break;
8853 for (i = 0; i < 5; i++)
8855 if (i && (i >= j || unused[i - 1]))
8857 cnts[i] = cnts[i - 1];
8858 continue;
8860 cnts[i] = create_tmp_var (sizetype);
8861 if (i == 0)
8862 g = gimple_build_assign (cnts[i], size_int (is_old ? 2 : 5));
8863 else
8865 tree t;
8866 if (is_old)
8867 t = size_binop (PLUS_EXPR, counts[0], size_int (2));
8868 else
8869 t = size_binop (PLUS_EXPR, cnts[i - 1], counts[i - 1]);
8870 if (gimplify_expr (&t, pre_p, NULL, is_gimple_val, fb_rvalue)
8871 == GS_ERROR)
8872 return 2;
8873 g = gimple_build_assign (cnts[i], t);
8875 gimple_seq_add_stmt (pre_p, g);
8877 if (unused[4])
8878 cnts[5] = NULL_TREE;
8879 else
8881 tree t = size_binop (PLUS_EXPR, total, size_int (5));
8882 cnts[5] = create_tmp_var (sizetype);
8883 g = gimple_build_assign (cnts[i], t);
8884 gimple_seq_add_stmt (pre_p, g);
8887 last_iter = NULL_TREE;
8888 tree last_bind = NULL_TREE;
8889 tree *last_body = NULL;
8890 for (c = *list_p; c; c = OMP_CLAUSE_CHAIN (c))
8891 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND)
8893 switch (OMP_CLAUSE_DEPEND_KIND (c))
8895 case OMP_CLAUSE_DEPEND_IN:
8896 i = 2;
8897 break;
8898 case OMP_CLAUSE_DEPEND_OUT:
8899 case OMP_CLAUSE_DEPEND_INOUT:
8900 i = 0;
8901 break;
8902 case OMP_CLAUSE_DEPEND_MUTEXINOUTSET:
8903 i = 1;
8904 break;
8905 case OMP_CLAUSE_DEPEND_DEPOBJ:
8906 i = 3;
8907 break;
8908 case OMP_CLAUSE_DEPEND_INOUTSET:
8909 i = 4;
8910 break;
8911 default:
8912 gcc_unreachable ();
8914 tree t = OMP_CLAUSE_DECL (c);
8915 if (TREE_CODE (t) == TREE_LIST
8916 && TREE_PURPOSE (t)
8917 && TREE_CODE (TREE_PURPOSE (t)) == TREE_VEC)
8919 if (TREE_PURPOSE (t) != last_iter)
8921 if (last_bind)
8922 gimplify_and_add (last_bind, pre_p);
8923 tree block = TREE_VEC_ELT (TREE_PURPOSE (t), 5);
8924 last_bind = build3 (BIND_EXPR, void_type_node,
8925 BLOCK_VARS (block), NULL, block);
8926 TREE_SIDE_EFFECTS (last_bind) = 1;
8927 SET_EXPR_LOCATION (last_bind, OMP_CLAUSE_LOCATION (c));
8928 tree *p = &BIND_EXPR_BODY (last_bind);
8929 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8931 tree var = TREE_VEC_ELT (it, 0);
8932 tree begin = TREE_VEC_ELT (it, 1);
8933 tree end = TREE_VEC_ELT (it, 2);
8934 tree step = TREE_VEC_ELT (it, 3);
8935 tree orig_step = TREE_VEC_ELT (it, 4);
8936 tree type = TREE_TYPE (var);
8937 location_t loc = DECL_SOURCE_LOCATION (var);
8938 /* Emit:
8939 var = begin;
8940 goto cond_label;
8941 beg_label:
8943 var = var + step;
8944 cond_label:
8945 if (orig_step > 0) {
8946 if (var < end) goto beg_label;
8947 } else {
8948 if (var > end) goto beg_label;
8950 for each iterator, with inner iterators added to
8951 the ... above. */
8952 tree beg_label = create_artificial_label (loc);
8953 tree cond_label = NULL_TREE;
8954 tem = build2_loc (loc, MODIFY_EXPR, void_type_node,
8955 var, begin);
8956 append_to_statement_list_force (tem, p);
8957 tem = build_and_jump (&cond_label);
8958 append_to_statement_list_force (tem, p);
8959 tem = build1 (LABEL_EXPR, void_type_node, beg_label);
8960 append_to_statement_list (tem, p);
8961 tree bind = build3 (BIND_EXPR, void_type_node, NULL_TREE,
8962 NULL_TREE, NULL_TREE);
8963 TREE_SIDE_EFFECTS (bind) = 1;
8964 SET_EXPR_LOCATION (bind, loc);
8965 append_to_statement_list_force (bind, p);
8966 if (POINTER_TYPE_P (type))
8967 tem = build2_loc (loc, POINTER_PLUS_EXPR, type,
8968 var, fold_convert_loc (loc, sizetype,
8969 step));
8970 else
8971 tem = build2_loc (loc, PLUS_EXPR, type, var, step);
8972 tem = build2_loc (loc, MODIFY_EXPR, void_type_node,
8973 var, tem);
8974 append_to_statement_list_force (tem, p);
8975 tem = build1 (LABEL_EXPR, void_type_node, cond_label);
8976 append_to_statement_list (tem, p);
8977 tree cond = fold_build2_loc (loc, LT_EXPR,
8978 boolean_type_node,
8979 var, end);
8980 tree pos
8981 = fold_build3_loc (loc, COND_EXPR, void_type_node,
8982 cond, build_and_jump (&beg_label),
8983 void_node);
8984 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8985 var, end);
8986 tree neg
8987 = fold_build3_loc (loc, COND_EXPR, void_type_node,
8988 cond, build_and_jump (&beg_label),
8989 void_node);
8990 tree osteptype = TREE_TYPE (orig_step);
8991 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8992 orig_step,
8993 build_int_cst (osteptype, 0));
8994 tem = fold_build3_loc (loc, COND_EXPR, void_type_node,
8995 cond, pos, neg);
8996 append_to_statement_list_force (tem, p);
8997 p = &BIND_EXPR_BODY (bind);
8999 last_body = p;
9001 last_iter = TREE_PURPOSE (t);
9002 if (TREE_CODE (TREE_VALUE (t)) == COMPOUND_EXPR)
9004 append_to_statement_list (TREE_OPERAND (TREE_VALUE (t),
9005 0), last_body);
9006 TREE_VALUE (t) = TREE_OPERAND (TREE_VALUE (t), 1);
9008 if (error_operand_p (TREE_VALUE (t)))
9009 return 2;
9010 if (TREE_VALUE (t) != null_pointer_node)
9011 TREE_VALUE (t) = build_fold_addr_expr (TREE_VALUE (t));
9012 if (i == 4)
9014 r = build4 (ARRAY_REF, ptr_type_node, array, cnts[i],
9015 NULL_TREE, NULL_TREE);
9016 tree r2 = build4 (ARRAY_REF, ptr_type_node, array, cnts[5],
9017 NULL_TREE, NULL_TREE);
9018 r2 = build_fold_addr_expr_with_type (r2, ptr_type_node);
9019 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
9020 void_type_node, r, r2);
9021 append_to_statement_list_force (tem, last_body);
9022 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
9023 void_type_node, cnts[i],
9024 size_binop (PLUS_EXPR, cnts[i],
9025 size_int (1)));
9026 append_to_statement_list_force (tem, last_body);
9027 i = 5;
9029 r = build4 (ARRAY_REF, ptr_type_node, array, cnts[i],
9030 NULL_TREE, NULL_TREE);
9031 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
9032 void_type_node, r, TREE_VALUE (t));
9033 append_to_statement_list_force (tem, last_body);
9034 if (i == 5)
9036 r = build4 (ARRAY_REF, ptr_type_node, array,
9037 size_binop (PLUS_EXPR, cnts[i], size_int (1)),
9038 NULL_TREE, NULL_TREE);
9039 tem = build_int_cst (ptr_type_node, GOMP_DEPEND_INOUTSET);
9040 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
9041 void_type_node, r, tem);
9042 append_to_statement_list_force (tem, last_body);
9044 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
9045 void_type_node, cnts[i],
9046 size_binop (PLUS_EXPR, cnts[i],
9047 size_int (1 + (i == 5))));
9048 append_to_statement_list_force (tem, last_body);
9049 TREE_VALUE (t) = null_pointer_node;
9051 else
9053 if (last_bind)
9055 gimplify_and_add (last_bind, pre_p);
9056 last_bind = NULL_TREE;
9058 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
9060 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
9061 NULL, is_gimple_val, fb_rvalue);
9062 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
9064 if (error_operand_p (OMP_CLAUSE_DECL (c)))
9065 return 2;
9066 if (OMP_CLAUSE_DECL (c) != null_pointer_node)
9067 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (OMP_CLAUSE_DECL (c));
9068 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
9069 is_gimple_val, fb_rvalue) == GS_ERROR)
9070 return 2;
9071 if (i == 4)
9073 r = build4 (ARRAY_REF, ptr_type_node, array, cnts[i],
9074 NULL_TREE, NULL_TREE);
9075 tree r2 = build4 (ARRAY_REF, ptr_type_node, array, cnts[5],
9076 NULL_TREE, NULL_TREE);
9077 r2 = build_fold_addr_expr_with_type (r2, ptr_type_node);
9078 tem = build2 (MODIFY_EXPR, void_type_node, r, r2);
9079 gimplify_and_add (tem, pre_p);
9080 g = gimple_build_assign (cnts[i], size_binop (PLUS_EXPR,
9081 cnts[i],
9082 size_int (1)));
9083 gimple_seq_add_stmt (pre_p, g);
9084 i = 5;
9086 r = build4 (ARRAY_REF, ptr_type_node, array, cnts[i],
9087 NULL_TREE, NULL_TREE);
9088 tem = build2 (MODIFY_EXPR, void_type_node, r, OMP_CLAUSE_DECL (c));
9089 gimplify_and_add (tem, pre_p);
9090 if (i == 5)
9092 r = build4 (ARRAY_REF, ptr_type_node, array,
9093 size_binop (PLUS_EXPR, cnts[i], size_int (1)),
9094 NULL_TREE, NULL_TREE);
9095 tem = build_int_cst (ptr_type_node, GOMP_DEPEND_INOUTSET);
9096 tem = build2 (MODIFY_EXPR, void_type_node, r, tem);
9097 append_to_statement_list_force (tem, last_body);
9098 gimplify_and_add (tem, pre_p);
9100 g = gimple_build_assign (cnts[i],
9101 size_binop (PLUS_EXPR, cnts[i],
9102 size_int (1 + (i == 5))));
9103 gimple_seq_add_stmt (pre_p, g);
9106 if (last_bind)
9107 gimplify_and_add (last_bind, pre_p);
9108 tree cond = boolean_false_node;
9109 if (is_old)
9111 if (!unused[0])
9112 cond = build2_loc (first_loc, NE_EXPR, boolean_type_node, cnts[0],
9113 size_binop_loc (first_loc, PLUS_EXPR, counts[0],
9114 size_int (2)));
9115 if (!unused[2])
9116 cond = build2_loc (first_loc, TRUTH_OR_EXPR, boolean_type_node, cond,
9117 build2_loc (first_loc, NE_EXPR, boolean_type_node,
9118 cnts[2],
9119 size_binop_loc (first_loc, PLUS_EXPR,
9120 totalpx,
9121 size_int (1))));
9123 else
9125 tree prev = size_int (5);
9126 for (i = 0; i < 5; i++)
9128 if (unused[i])
9129 continue;
9130 prev = size_binop_loc (first_loc, PLUS_EXPR, counts[i], prev);
9131 cond = build2_loc (first_loc, TRUTH_OR_EXPR, boolean_type_node, cond,
9132 build2_loc (first_loc, NE_EXPR, boolean_type_node,
9133 cnts[i], unshare_expr (prev)));
9136 tem = build3_loc (first_loc, COND_EXPR, void_type_node, cond,
9137 build_call_expr_loc (first_loc,
9138 builtin_decl_explicit (BUILT_IN_TRAP),
9139 0), void_node);
9140 gimplify_and_add (tem, pre_p);
9141 c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_DEPEND);
9142 OMP_CLAUSE_DEPEND_KIND (c) = OMP_CLAUSE_DEPEND_LAST;
9143 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (array);
9144 OMP_CLAUSE_CHAIN (c) = *list_p;
9145 *list_p = c;
9146 return 1;
9149 /* For a set of mappings describing an array section pointed to by a struct
9150 (or derived type, etc.) component, create an "alloc" or "release" node to
9151 insert into a list following a GOMP_MAP_STRUCT node. For some types of
9152 mapping (e.g. Fortran arrays with descriptors), an additional mapping may
9153 be created that is inserted into the list of mapping nodes attached to the
9154 directive being processed -- not part of the sorted list of nodes after
9155 GOMP_MAP_STRUCT.
9157 CODE is the code of the directive being processed. GRP_START and GRP_END
9158 are the first and last of two or three nodes representing this array section
9159 mapping (e.g. a data movement node like GOMP_MAP_{TO,FROM}, optionally a
9160 GOMP_MAP_TO_PSET, and finally a GOMP_MAP_ALWAYS_POINTER). EXTRA_NODE is
9161 filled with the additional node described above, if needed.
9163 This function does not add the new nodes to any lists itself. It is the
9164 responsibility of the caller to do that. */
9166 static tree
9167 build_omp_struct_comp_nodes (enum tree_code code, tree grp_start, tree grp_end,
9168 tree *extra_node)
9170 enum gomp_map_kind mkind
9171 = (code == OMP_TARGET_EXIT_DATA || code == OACC_EXIT_DATA)
9172 ? GOMP_MAP_RELEASE : GOMP_MAP_ALLOC;
9174 gcc_assert (grp_start != grp_end);
9176 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (grp_end), OMP_CLAUSE_MAP);
9177 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
9178 OMP_CLAUSE_DECL (c2) = unshare_expr (OMP_CLAUSE_DECL (grp_end));
9179 OMP_CLAUSE_CHAIN (c2) = NULL_TREE;
9180 tree grp_mid = NULL_TREE;
9181 if (OMP_CLAUSE_CHAIN (grp_start) != grp_end)
9182 grp_mid = OMP_CLAUSE_CHAIN (grp_start);
9184 if (grp_mid
9185 && OMP_CLAUSE_CODE (grp_mid) == OMP_CLAUSE_MAP
9186 && OMP_CLAUSE_MAP_KIND (grp_mid) == GOMP_MAP_TO_PSET)
9187 OMP_CLAUSE_SIZE (c2) = OMP_CLAUSE_SIZE (grp_mid);
9188 else
9189 OMP_CLAUSE_SIZE (c2) = TYPE_SIZE_UNIT (ptr_type_node);
9191 if (grp_mid
9192 && OMP_CLAUSE_CODE (grp_mid) == OMP_CLAUSE_MAP
9193 && (OMP_CLAUSE_MAP_KIND (grp_mid) == GOMP_MAP_ALWAYS_POINTER
9194 || OMP_CLAUSE_MAP_KIND (grp_mid) == GOMP_MAP_ATTACH_DETACH))
9196 tree c3
9197 = build_omp_clause (OMP_CLAUSE_LOCATION (grp_end), OMP_CLAUSE_MAP);
9198 OMP_CLAUSE_SET_MAP_KIND (c3, mkind);
9199 OMP_CLAUSE_DECL (c3) = unshare_expr (OMP_CLAUSE_DECL (grp_mid));
9200 OMP_CLAUSE_SIZE (c3) = TYPE_SIZE_UNIT (ptr_type_node);
9201 OMP_CLAUSE_CHAIN (c3) = NULL_TREE;
9203 *extra_node = c3;
9205 else
9206 *extra_node = NULL_TREE;
9208 return c2;
9211 /* Strip ARRAY_REFS or an indirect ref off BASE, find the containing object,
9212 and set *BITPOSP and *POFFSETP to the bit offset of the access.
9213 If BASE_REF is non-NULL and the containing object is a reference, set
9214 *BASE_REF to that reference before dereferencing the object.
9215 If BASE_REF is NULL, check that the containing object is a COMPONENT_REF or
9216 has array type, else return NULL. */
9218 static tree
9219 extract_base_bit_offset (tree base, poly_int64 *bitposp,
9220 poly_offset_int *poffsetp)
9222 tree offset;
9223 poly_int64 bitsize, bitpos;
9224 machine_mode mode;
9225 int unsignedp, reversep, volatilep = 0;
9226 poly_offset_int poffset;
9228 STRIP_NOPS (base);
9230 base = get_inner_reference (base, &bitsize, &bitpos, &offset, &mode,
9231 &unsignedp, &reversep, &volatilep);
9233 STRIP_NOPS (base);
9235 if (offset && poly_int_tree_p (offset))
9237 poffset = wi::to_poly_offset (offset);
9238 offset = NULL_TREE;
9240 else
9241 poffset = 0;
9243 if (maybe_ne (bitpos, 0))
9244 poffset += bits_to_bytes_round_down (bitpos);
9246 *bitposp = bitpos;
9247 *poffsetp = poffset;
9249 return base;
9252 /* Used for topological sorting of mapping groups. UNVISITED means we haven't
9253 started processing the group yet. The TEMPORARY mark is used when we first
9254 encounter a group on a depth-first traversal, and the PERMANENT mark is used
9255 when we have processed all the group's children (i.e. all the base pointers
9256 referred to by the group's mapping nodes, recursively). */
9258 enum omp_tsort_mark {
9259 UNVISITED,
9260 TEMPORARY,
9261 PERMANENT
9264 /* Hash for trees based on operand_equal_p. Like tree_operand_hash
9265 but ignores side effects in the equality comparisons. */
9267 struct tree_operand_hash_no_se : tree_operand_hash
9269 static inline bool equal (const value_type &,
9270 const compare_type &);
9273 inline bool
9274 tree_operand_hash_no_se::equal (const value_type &t1,
9275 const compare_type &t2)
9277 return operand_equal_p (t1, t2, OEP_MATCH_SIDE_EFFECTS);
9280 /* A group of OMP_CLAUSE_MAP nodes that correspond to a single "map"
9281 clause. */
9283 struct omp_mapping_group {
9284 tree *grp_start;
9285 tree grp_end;
9286 omp_tsort_mark mark;
9287 /* If we've removed the group but need to reindex, mark the group as
9288 deleted. */
9289 bool deleted;
9290 struct omp_mapping_group *sibling;
9291 struct omp_mapping_group *next;
9294 DEBUG_FUNCTION void
9295 debug_mapping_group (omp_mapping_group *grp)
9297 tree tmp = OMP_CLAUSE_CHAIN (grp->grp_end);
9298 OMP_CLAUSE_CHAIN (grp->grp_end) = NULL;
9299 debug_generic_expr (*grp->grp_start);
9300 OMP_CLAUSE_CHAIN (grp->grp_end) = tmp;
9303 /* Return the OpenMP "base pointer" of an expression EXPR, or NULL if there
9304 isn't one. */
9306 static tree
9307 omp_get_base_pointer (tree expr)
9309 while (TREE_CODE (expr) == ARRAY_REF
9310 || TREE_CODE (expr) == COMPONENT_REF)
9311 expr = TREE_OPERAND (expr, 0);
9313 if (INDIRECT_REF_P (expr)
9314 || (TREE_CODE (expr) == MEM_REF
9315 && integer_zerop (TREE_OPERAND (expr, 1))))
9317 expr = TREE_OPERAND (expr, 0);
9318 while (TREE_CODE (expr) == COMPOUND_EXPR)
9319 expr = TREE_OPERAND (expr, 1);
9320 if (TREE_CODE (expr) == POINTER_PLUS_EXPR)
9321 expr = TREE_OPERAND (expr, 0);
9322 if (TREE_CODE (expr) == SAVE_EXPR)
9323 expr = TREE_OPERAND (expr, 0);
9324 STRIP_NOPS (expr);
9325 return expr;
9328 return NULL_TREE;
9331 /* Remove COMPONENT_REFS and indirections from EXPR. */
9333 static tree
9334 omp_strip_components_and_deref (tree expr)
9336 while (TREE_CODE (expr) == COMPONENT_REF
9337 || INDIRECT_REF_P (expr)
9338 || (TREE_CODE (expr) == MEM_REF
9339 && integer_zerop (TREE_OPERAND (expr, 1)))
9340 || TREE_CODE (expr) == POINTER_PLUS_EXPR
9341 || TREE_CODE (expr) == COMPOUND_EXPR)
9342 if (TREE_CODE (expr) == COMPOUND_EXPR)
9343 expr = TREE_OPERAND (expr, 1);
9344 else
9345 expr = TREE_OPERAND (expr, 0);
9347 STRIP_NOPS (expr);
9349 return expr;
9352 static tree
9353 omp_strip_indirections (tree expr)
9355 while (INDIRECT_REF_P (expr)
9356 || (TREE_CODE (expr) == MEM_REF
9357 && integer_zerop (TREE_OPERAND (expr, 1))))
9358 expr = TREE_OPERAND (expr, 0);
9360 return expr;
9363 /* An attach or detach operation depends directly on the address being
9364 attached/detached. Return that address, or none if there are no
9365 attachments/detachments. */
9367 static tree
9368 omp_get_attachment (omp_mapping_group *grp)
9370 tree node = *grp->grp_start;
9372 switch (OMP_CLAUSE_MAP_KIND (node))
9374 case GOMP_MAP_TO:
9375 case GOMP_MAP_FROM:
9376 case GOMP_MAP_TOFROM:
9377 case GOMP_MAP_ALWAYS_FROM:
9378 case GOMP_MAP_ALWAYS_TO:
9379 case GOMP_MAP_ALWAYS_TOFROM:
9380 case GOMP_MAP_FORCE_FROM:
9381 case GOMP_MAP_FORCE_TO:
9382 case GOMP_MAP_FORCE_TOFROM:
9383 case GOMP_MAP_FORCE_PRESENT:
9384 case GOMP_MAP_PRESENT_ALLOC:
9385 case GOMP_MAP_PRESENT_FROM:
9386 case GOMP_MAP_PRESENT_TO:
9387 case GOMP_MAP_PRESENT_TOFROM:
9388 case GOMP_MAP_ALWAYS_PRESENT_FROM:
9389 case GOMP_MAP_ALWAYS_PRESENT_TO:
9390 case GOMP_MAP_ALWAYS_PRESENT_TOFROM:
9391 case GOMP_MAP_ALLOC:
9392 case GOMP_MAP_RELEASE:
9393 case GOMP_MAP_DELETE:
9394 case GOMP_MAP_FORCE_ALLOC:
9395 if (node == grp->grp_end)
9396 return NULL_TREE;
9398 node = OMP_CLAUSE_CHAIN (node);
9399 if (node && OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_TO_PSET)
9401 gcc_assert (node != grp->grp_end);
9402 node = OMP_CLAUSE_CHAIN (node);
9404 if (node)
9405 switch (OMP_CLAUSE_MAP_KIND (node))
9407 case GOMP_MAP_POINTER:
9408 case GOMP_MAP_ALWAYS_POINTER:
9409 case GOMP_MAP_FIRSTPRIVATE_POINTER:
9410 case GOMP_MAP_FIRSTPRIVATE_REFERENCE:
9411 case GOMP_MAP_POINTER_TO_ZERO_LENGTH_ARRAY_SECTION:
9412 return NULL_TREE;
9414 case GOMP_MAP_ATTACH_DETACH:
9415 case GOMP_MAP_ATTACH_ZERO_LENGTH_ARRAY_SECTION:
9416 return OMP_CLAUSE_DECL (node);
9418 default:
9419 internal_error ("unexpected mapping node");
9421 return error_mark_node;
9423 case GOMP_MAP_TO_PSET:
9424 gcc_assert (node != grp->grp_end);
9425 node = OMP_CLAUSE_CHAIN (node);
9426 if (OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_ATTACH
9427 || OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_DETACH)
9428 return OMP_CLAUSE_DECL (node);
9429 else
9430 internal_error ("unexpected mapping node");
9431 return error_mark_node;
9433 case GOMP_MAP_ATTACH:
9434 case GOMP_MAP_DETACH:
9435 node = OMP_CLAUSE_CHAIN (node);
9436 if (!node || *grp->grp_start == grp->grp_end)
9437 return OMP_CLAUSE_DECL (*grp->grp_start);
9438 if (OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_FIRSTPRIVATE_POINTER
9439 || OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_FIRSTPRIVATE_REFERENCE)
9440 return OMP_CLAUSE_DECL (*grp->grp_start);
9441 else
9442 internal_error ("unexpected mapping node");
9443 return error_mark_node;
9445 case GOMP_MAP_STRUCT:
9446 case GOMP_MAP_FORCE_DEVICEPTR:
9447 case GOMP_MAP_DEVICE_RESIDENT:
9448 case GOMP_MAP_LINK:
9449 case GOMP_MAP_IF_PRESENT:
9450 case GOMP_MAP_FIRSTPRIVATE:
9451 case GOMP_MAP_FIRSTPRIVATE_INT:
9452 case GOMP_MAP_USE_DEVICE_PTR:
9453 case GOMP_MAP_ATTACH_ZERO_LENGTH_ARRAY_SECTION:
9454 return NULL_TREE;
9456 default:
9457 internal_error ("unexpected mapping node");
9460 return error_mark_node;
9463 /* Given a pointer START_P to the start of a group of related (e.g. pointer)
9464 mappings, return the chain pointer to the end of that group in the list. */
9466 static tree *
9467 omp_group_last (tree *start_p)
9469 tree c = *start_p, nc, *grp_last_p = start_p;
9471 gcc_assert (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP);
9473 nc = OMP_CLAUSE_CHAIN (c);
9475 if (!nc || OMP_CLAUSE_CODE (nc) != OMP_CLAUSE_MAP)
9476 return grp_last_p;
9478 switch (OMP_CLAUSE_MAP_KIND (c))
9480 default:
9481 while (nc
9482 && OMP_CLAUSE_CODE (nc) == OMP_CLAUSE_MAP
9483 && (OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_FIRSTPRIVATE_REFERENCE
9484 || OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_FIRSTPRIVATE_POINTER
9485 || OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_ATTACH_DETACH
9486 || OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_POINTER
9487 || (OMP_CLAUSE_MAP_KIND (nc)
9488 == GOMP_MAP_POINTER_TO_ZERO_LENGTH_ARRAY_SECTION)
9489 || (OMP_CLAUSE_MAP_KIND (nc)
9490 == GOMP_MAP_ATTACH_ZERO_LENGTH_ARRAY_SECTION)
9491 || OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_ALWAYS_POINTER
9492 || OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_TO_PSET))
9494 grp_last_p = &OMP_CLAUSE_CHAIN (c);
9495 c = nc;
9496 tree nc2 = OMP_CLAUSE_CHAIN (nc);
9497 if (nc2
9498 && OMP_CLAUSE_CODE (nc2) == OMP_CLAUSE_MAP
9499 && (OMP_CLAUSE_MAP_KIND (nc)
9500 == GOMP_MAP_POINTER_TO_ZERO_LENGTH_ARRAY_SECTION)
9501 && OMP_CLAUSE_MAP_KIND (nc2) == GOMP_MAP_ATTACH)
9503 grp_last_p = &OMP_CLAUSE_CHAIN (nc);
9504 c = nc2;
9505 nc2 = OMP_CLAUSE_CHAIN (nc2);
9507 nc = nc2;
9509 break;
9511 case GOMP_MAP_ATTACH:
9512 case GOMP_MAP_DETACH:
9513 /* This is a weird artifact of how directives are parsed: bare attach or
9514 detach clauses get a subsequent (meaningless) FIRSTPRIVATE_POINTER or
9515 FIRSTPRIVATE_REFERENCE node. FIXME. */
9516 if (nc
9517 && OMP_CLAUSE_CODE (nc) == OMP_CLAUSE_MAP
9518 && (OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_FIRSTPRIVATE_REFERENCE
9519 || OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_FIRSTPRIVATE_POINTER))
9520 grp_last_p = &OMP_CLAUSE_CHAIN (c);
9521 break;
9523 case GOMP_MAP_TO_PSET:
9524 if (OMP_CLAUSE_CODE (nc) == OMP_CLAUSE_MAP
9525 && (OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_ATTACH
9526 || OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_DETACH))
9527 grp_last_p = &OMP_CLAUSE_CHAIN (c);
9528 break;
9530 case GOMP_MAP_STRUCT:
9532 unsigned HOST_WIDE_INT num_mappings
9533 = tree_to_uhwi (OMP_CLAUSE_SIZE (c));
9534 if (OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_FIRSTPRIVATE_POINTER
9535 || OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_FIRSTPRIVATE_REFERENCE
9536 || OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_ATTACH_DETACH)
9537 grp_last_p = &OMP_CLAUSE_CHAIN (*grp_last_p);
9538 for (unsigned i = 0; i < num_mappings; i++)
9539 grp_last_p = &OMP_CLAUSE_CHAIN (*grp_last_p);
9541 break;
9544 return grp_last_p;
9547 /* Walk through LIST_P, and return a list of groups of mappings found (e.g.
9548 OMP_CLAUSE_MAP with GOMP_MAP_{TO/FROM/TOFROM} followed by one or two
9549 associated GOMP_MAP_POINTER mappings). Return a vector of omp_mapping_group
9550 if we have more than one such group, else return NULL. */
9552 static void
9553 omp_gather_mapping_groups_1 (tree *list_p, vec<omp_mapping_group> *groups,
9554 tree gather_sentinel)
9556 for (tree *cp = list_p;
9557 *cp && *cp != gather_sentinel;
9558 cp = &OMP_CLAUSE_CHAIN (*cp))
9560 if (OMP_CLAUSE_CODE (*cp) != OMP_CLAUSE_MAP)
9561 continue;
9563 tree *grp_last_p = omp_group_last (cp);
9564 omp_mapping_group grp;
9566 grp.grp_start = cp;
9567 grp.grp_end = *grp_last_p;
9568 grp.mark = UNVISITED;
9569 grp.sibling = NULL;
9570 grp.deleted = false;
9571 grp.next = NULL;
9572 groups->safe_push (grp);
9574 cp = grp_last_p;
9578 static vec<omp_mapping_group> *
9579 omp_gather_mapping_groups (tree *list_p)
9581 vec<omp_mapping_group> *groups = new vec<omp_mapping_group> ();
9583 omp_gather_mapping_groups_1 (list_p, groups, NULL_TREE);
9585 if (groups->length () > 0)
9586 return groups;
9587 else
9589 delete groups;
9590 return NULL;
9594 /* A pointer mapping group GRP may define a block of memory starting at some
9595 base address, and maybe also define a firstprivate pointer or firstprivate
9596 reference that points to that block. The return value is a node containing
9597 the former, and the *FIRSTPRIVATE pointer is set if we have the latter.
9598 If we define several base pointers, i.e. for a GOMP_MAP_STRUCT mapping,
9599 return the number of consecutive chained nodes in CHAINED. */
9601 static tree
9602 omp_group_base (omp_mapping_group *grp, unsigned int *chained,
9603 tree *firstprivate)
9605 tree node = *grp->grp_start;
9607 *firstprivate = NULL_TREE;
9608 *chained = 1;
9610 switch (OMP_CLAUSE_MAP_KIND (node))
9612 case GOMP_MAP_TO:
9613 case GOMP_MAP_FROM:
9614 case GOMP_MAP_TOFROM:
9615 case GOMP_MAP_ALWAYS_FROM:
9616 case GOMP_MAP_ALWAYS_TO:
9617 case GOMP_MAP_ALWAYS_TOFROM:
9618 case GOMP_MAP_FORCE_FROM:
9619 case GOMP_MAP_FORCE_TO:
9620 case GOMP_MAP_FORCE_TOFROM:
9621 case GOMP_MAP_FORCE_PRESENT:
9622 case GOMP_MAP_PRESENT_ALLOC:
9623 case GOMP_MAP_PRESENT_FROM:
9624 case GOMP_MAP_PRESENT_TO:
9625 case GOMP_MAP_PRESENT_TOFROM:
9626 case GOMP_MAP_ALWAYS_PRESENT_FROM:
9627 case GOMP_MAP_ALWAYS_PRESENT_TO:
9628 case GOMP_MAP_ALWAYS_PRESENT_TOFROM:
9629 case GOMP_MAP_ALLOC:
9630 case GOMP_MAP_RELEASE:
9631 case GOMP_MAP_DELETE:
9632 case GOMP_MAP_FORCE_ALLOC:
9633 case GOMP_MAP_IF_PRESENT:
9634 if (node == grp->grp_end)
9635 return node;
9637 node = OMP_CLAUSE_CHAIN (node);
9638 if (node && OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_TO_PSET)
9640 if (node == grp->grp_end)
9641 return *grp->grp_start;
9642 node = OMP_CLAUSE_CHAIN (node);
9644 if (node)
9645 switch (OMP_CLAUSE_MAP_KIND (node))
9647 case GOMP_MAP_POINTER:
9648 case GOMP_MAP_FIRSTPRIVATE_POINTER:
9649 case GOMP_MAP_FIRSTPRIVATE_REFERENCE:
9650 case GOMP_MAP_POINTER_TO_ZERO_LENGTH_ARRAY_SECTION:
9651 *firstprivate = OMP_CLAUSE_DECL (node);
9652 return *grp->grp_start;
9654 case GOMP_MAP_ALWAYS_POINTER:
9655 case GOMP_MAP_ATTACH_DETACH:
9656 case GOMP_MAP_ATTACH_ZERO_LENGTH_ARRAY_SECTION:
9657 return *grp->grp_start;
9659 default:
9660 internal_error ("unexpected mapping node");
9662 else
9663 internal_error ("unexpected mapping node");
9664 return error_mark_node;
9666 case GOMP_MAP_TO_PSET:
9667 gcc_assert (node != grp->grp_end);
9668 node = OMP_CLAUSE_CHAIN (node);
9669 if (OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_ATTACH
9670 || OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_DETACH)
9671 return NULL_TREE;
9672 else
9673 internal_error ("unexpected mapping node");
9674 return error_mark_node;
9676 case GOMP_MAP_ATTACH:
9677 case GOMP_MAP_DETACH:
9678 node = OMP_CLAUSE_CHAIN (node);
9679 if (!node || *grp->grp_start == grp->grp_end)
9680 return NULL_TREE;
9681 if (OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_FIRSTPRIVATE_POINTER
9682 || OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_FIRSTPRIVATE_REFERENCE)
9684 /* We're mapping the base pointer itself in a bare attach or detach
9685 node. This is a side effect of how parsing works, and the mapping
9686 will be removed anyway (at least for enter/exit data directives).
9687 We should ignore the mapping here. FIXME. */
9688 return NULL_TREE;
9690 else
9691 internal_error ("unexpected mapping node");
9692 return error_mark_node;
9694 case GOMP_MAP_STRUCT:
9696 unsigned HOST_WIDE_INT num_mappings
9697 = tree_to_uhwi (OMP_CLAUSE_SIZE (node));
9698 node = OMP_CLAUSE_CHAIN (node);
9699 if (OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_FIRSTPRIVATE_POINTER
9700 || OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_FIRSTPRIVATE_REFERENCE)
9702 *firstprivate = OMP_CLAUSE_DECL (node);
9703 node = OMP_CLAUSE_CHAIN (node);
9705 *chained = num_mappings;
9706 return node;
9709 case GOMP_MAP_FORCE_DEVICEPTR:
9710 case GOMP_MAP_DEVICE_RESIDENT:
9711 case GOMP_MAP_LINK:
9712 case GOMP_MAP_FIRSTPRIVATE:
9713 case GOMP_MAP_FIRSTPRIVATE_INT:
9714 case GOMP_MAP_USE_DEVICE_PTR:
9715 case GOMP_MAP_ATTACH_ZERO_LENGTH_ARRAY_SECTION:
9716 return NULL_TREE;
9718 case GOMP_MAP_FIRSTPRIVATE_POINTER:
9719 case GOMP_MAP_FIRSTPRIVATE_REFERENCE:
9720 case GOMP_MAP_POINTER:
9721 case GOMP_MAP_ALWAYS_POINTER:
9722 case GOMP_MAP_POINTER_TO_ZERO_LENGTH_ARRAY_SECTION:
9723 /* These shouldn't appear by themselves. */
9724 if (!seen_error ())
9725 internal_error ("unexpected pointer mapping node");
9726 return error_mark_node;
9728 default:
9729 gcc_unreachable ();
9732 return error_mark_node;
9735 /* Given a vector of omp_mapping_groups, build a hash table so we can look up
9736 nodes by tree_operand_hash_no_se. */
9738 static void
9739 omp_index_mapping_groups_1 (hash_map<tree_operand_hash_no_se,
9740 omp_mapping_group *> *grpmap,
9741 vec<omp_mapping_group> *groups,
9742 tree reindex_sentinel)
9744 omp_mapping_group *grp;
9745 unsigned int i;
9746 bool reindexing = reindex_sentinel != NULL_TREE, above_hwm = false;
9748 FOR_EACH_VEC_ELT (*groups, i, grp)
9750 if (reindexing && *grp->grp_start == reindex_sentinel)
9751 above_hwm = true;
9753 if (reindexing && !above_hwm)
9754 continue;
9756 tree fpp;
9757 unsigned int chained;
9758 tree node = omp_group_base (grp, &chained, &fpp);
9760 if (node == error_mark_node || (!node && !fpp))
9761 continue;
9763 for (unsigned j = 0;
9764 node && j < chained;
9765 node = OMP_CLAUSE_CHAIN (node), j++)
9767 tree decl = OMP_CLAUSE_DECL (node);
9768 /* Sometimes we see zero-offset MEM_REF instead of INDIRECT_REF,
9769 meaning node-hash lookups don't work. This is a workaround for
9770 that, but ideally we should just create the INDIRECT_REF at
9771 source instead. FIXME. */
9772 if (TREE_CODE (decl) == MEM_REF
9773 && integer_zerop (TREE_OPERAND (decl, 1)))
9774 decl = build_fold_indirect_ref (TREE_OPERAND (decl, 0));
9776 omp_mapping_group **prev = grpmap->get (decl);
9778 if (prev && *prev == grp)
9779 /* Empty. */;
9780 else if (prev)
9782 /* Mapping the same thing twice is normally diagnosed as an error,
9783 but can happen under some circumstances, e.g. in pr99928-16.c,
9784 the directive:
9786 #pragma omp target simd reduction(+:a[:3]) \
9787 map(always, tofrom: a[:6])
9790 will result in two "a[0]" mappings (of different sizes). */
9792 grp->sibling = (*prev)->sibling;
9793 (*prev)->sibling = grp;
9795 else
9796 grpmap->put (decl, grp);
9799 if (!fpp)
9800 continue;
9802 omp_mapping_group **prev = grpmap->get (fpp);
9803 if (prev && *prev != grp)
9805 grp->sibling = (*prev)->sibling;
9806 (*prev)->sibling = grp;
9808 else
9809 grpmap->put (fpp, grp);
9813 static hash_map<tree_operand_hash_no_se, omp_mapping_group *> *
9814 omp_index_mapping_groups (vec<omp_mapping_group> *groups)
9816 hash_map<tree_operand_hash_no_se, omp_mapping_group *> *grpmap
9817 = new hash_map<tree_operand_hash_no_se, omp_mapping_group *>;
9819 omp_index_mapping_groups_1 (grpmap, groups, NULL_TREE);
9821 return grpmap;
9824 /* Rebuild group map from partially-processed clause list (during
9825 omp_build_struct_sibling_lists). We have already processed nodes up until
9826 a high-water mark (HWM). This is a bit tricky because the list is being
9827 reordered as it is scanned, but we know:
9829 1. The list after HWM has not been touched yet, so we can reindex it safely.
9831 2. The list before and including HWM has been altered, but remains
9832 well-formed throughout the sibling-list building operation.
9834 so, we can do the reindex operation in two parts, on the processed and
9835 then the unprocessed halves of the list. */
9837 static hash_map<tree_operand_hash_no_se, omp_mapping_group *> *
9838 omp_reindex_mapping_groups (tree *list_p,
9839 vec<omp_mapping_group> *groups,
9840 vec<omp_mapping_group> *processed_groups,
9841 tree sentinel)
9843 hash_map<tree_operand_hash_no_se, omp_mapping_group *> *grpmap
9844 = new hash_map<tree_operand_hash_no_se, omp_mapping_group *>;
9846 processed_groups->truncate (0);
9848 omp_gather_mapping_groups_1 (list_p, processed_groups, sentinel);
9849 omp_index_mapping_groups_1 (grpmap, processed_groups, NULL_TREE);
9850 if (sentinel)
9851 omp_index_mapping_groups_1 (grpmap, groups, sentinel);
9853 return grpmap;
9856 /* Find the immediately-containing struct for a component ref (etc.)
9857 expression EXPR. */
9859 static tree
9860 omp_containing_struct (tree expr)
9862 tree expr0 = expr;
9864 STRIP_NOPS (expr);
9866 /* Note: don't strip NOPs unless we're also stripping off array refs or a
9867 component ref. */
9868 if (TREE_CODE (expr) != ARRAY_REF && TREE_CODE (expr) != COMPONENT_REF)
9869 return expr0;
9871 while (TREE_CODE (expr) == ARRAY_REF)
9872 expr = TREE_OPERAND (expr, 0);
9874 if (TREE_CODE (expr) == COMPONENT_REF)
9875 expr = TREE_OPERAND (expr, 0);
9877 return expr;
9880 /* Return TRUE if DECL describes a component that is part of a whole structure
9881 that is mapped elsewhere in GRPMAP. *MAPPED_BY_GROUP is set to the group
9882 that maps that structure, if present. */
9884 static bool
9885 omp_mapped_by_containing_struct (hash_map<tree_operand_hash_no_se,
9886 omp_mapping_group *> *grpmap,
9887 tree decl,
9888 omp_mapping_group **mapped_by_group)
9890 tree wsdecl = NULL_TREE;
9892 *mapped_by_group = NULL;
9894 while (true)
9896 wsdecl = omp_containing_struct (decl);
9897 if (wsdecl == decl)
9898 break;
9899 omp_mapping_group **wholestruct = grpmap->get (wsdecl);
9900 if (!wholestruct
9901 && TREE_CODE (wsdecl) == MEM_REF
9902 && integer_zerop (TREE_OPERAND (wsdecl, 1)))
9904 tree deref = TREE_OPERAND (wsdecl, 0);
9905 deref = build_fold_indirect_ref (deref);
9906 wholestruct = grpmap->get (deref);
9908 if (wholestruct)
9910 *mapped_by_group = *wholestruct;
9911 return true;
9913 decl = wsdecl;
9916 return false;
9919 /* Helper function for omp_tsort_mapping_groups. Returns TRUE on success, or
9920 FALSE on error. */
9922 static bool
9923 omp_tsort_mapping_groups_1 (omp_mapping_group ***outlist,
9924 vec<omp_mapping_group> *groups,
9925 hash_map<tree_operand_hash_no_se,
9926 omp_mapping_group *> *grpmap,
9927 omp_mapping_group *grp)
9929 if (grp->mark == PERMANENT)
9930 return true;
9931 if (grp->mark == TEMPORARY)
9933 fprintf (stderr, "when processing group:\n");
9934 debug_mapping_group (grp);
9935 internal_error ("base pointer cycle detected");
9936 return false;
9938 grp->mark = TEMPORARY;
9940 tree attaches_to = omp_get_attachment (grp);
9942 if (attaches_to)
9944 omp_mapping_group **basep = grpmap->get (attaches_to);
9946 if (basep && *basep != grp)
9948 for (omp_mapping_group *w = *basep; w; w = w->sibling)
9949 if (!omp_tsort_mapping_groups_1 (outlist, groups, grpmap, w))
9950 return false;
9954 tree decl = OMP_CLAUSE_DECL (*grp->grp_start);
9956 while (decl)
9958 tree base = omp_get_base_pointer (decl);
9960 if (!base)
9961 break;
9963 omp_mapping_group **innerp = grpmap->get (base);
9964 omp_mapping_group *wholestruct;
9966 /* We should treat whole-structure mappings as if all (pointer, in this
9967 case) members are mapped as individual list items. Check if we have
9968 such a whole-structure mapping, if we don't have an explicit reference
9969 to the pointer member itself. */
9970 if (!innerp
9971 && TREE_CODE (base) == COMPONENT_REF
9972 && omp_mapped_by_containing_struct (grpmap, base, &wholestruct))
9973 innerp = &wholestruct;
9975 if (innerp && *innerp != grp)
9977 for (omp_mapping_group *w = *innerp; w; w = w->sibling)
9978 if (!omp_tsort_mapping_groups_1 (outlist, groups, grpmap, w))
9979 return false;
9980 break;
9983 decl = base;
9986 grp->mark = PERMANENT;
9988 /* Emit grp to output list. */
9990 **outlist = grp;
9991 *outlist = &grp->next;
9993 return true;
9996 /* Topologically sort GROUPS, so that OMP 5.0-defined base pointers come
9997 before mappings that use those pointers. This is an implementation of the
9998 depth-first search algorithm, described e.g. at:
10000 https://en.wikipedia.org/wiki/Topological_sorting
10003 static omp_mapping_group *
10004 omp_tsort_mapping_groups (vec<omp_mapping_group> *groups,
10005 hash_map<tree_operand_hash_no_se, omp_mapping_group *>
10006 *grpmap)
10008 omp_mapping_group *grp, *outlist = NULL, **cursor;
10009 unsigned int i;
10011 cursor = &outlist;
10013 FOR_EACH_VEC_ELT (*groups, i, grp)
10015 if (grp->mark != PERMANENT)
10016 if (!omp_tsort_mapping_groups_1 (&cursor, groups, grpmap, grp))
10017 return NULL;
10020 return outlist;
10023 /* Split INLIST into two parts, moving groups corresponding to
10024 ALLOC/RELEASE/DELETE mappings to one list, and other mappings to another.
10025 The former list is then appended to the latter. Each sub-list retains the
10026 order of the original list.
10027 Note that ATTACH nodes are later moved to the end of the list in
10028 gimplify_adjust_omp_clauses, for target regions. */
10030 static omp_mapping_group *
10031 omp_segregate_mapping_groups (omp_mapping_group *inlist)
10033 omp_mapping_group *ard_groups = NULL, *tf_groups = NULL;
10034 omp_mapping_group **ard_tail = &ard_groups, **tf_tail = &tf_groups;
10036 for (omp_mapping_group *w = inlist; w;)
10038 tree c = *w->grp_start;
10039 omp_mapping_group *next = w->next;
10041 gcc_assert (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP);
10043 switch (OMP_CLAUSE_MAP_KIND (c))
10045 case GOMP_MAP_ALLOC:
10046 case GOMP_MAP_RELEASE:
10047 case GOMP_MAP_DELETE:
10048 *ard_tail = w;
10049 w->next = NULL;
10050 ard_tail = &w->next;
10051 break;
10053 default:
10054 *tf_tail = w;
10055 w->next = NULL;
10056 tf_tail = &w->next;
10059 w = next;
10062 /* Now splice the lists together... */
10063 *tf_tail = ard_groups;
10065 return tf_groups;
10068 /* Given a list LIST_P containing groups of mappings given by GROUPS, reorder
10069 those groups based on the output list of omp_tsort_mapping_groups --
10070 singly-linked, threaded through each element's NEXT pointer starting at
10071 HEAD. Each list element appears exactly once in that linked list.
10073 Each element of GROUPS may correspond to one or several mapping nodes.
10074 Node groups are kept together, and in the reordered list, the positions of
10075 the original groups are reused for the positions of the reordered list.
10076 Hence if we have e.g.
10078 {to ptr ptr} firstprivate {tofrom ptr} ...
10079 ^ ^ ^
10080 first group non-"map" second group
10082 and say the second group contains a base pointer for the first so must be
10083 moved before it, the resulting list will contain:
10085 {tofrom ptr} firstprivate {to ptr ptr} ...
10086 ^ prev. second group ^ prev. first group
10089 static tree *
10090 omp_reorder_mapping_groups (vec<omp_mapping_group> *groups,
10091 omp_mapping_group *head,
10092 tree *list_p)
10094 omp_mapping_group *grp;
10095 unsigned int i;
10096 unsigned numgroups = groups->length ();
10097 auto_vec<tree> old_heads (numgroups);
10098 auto_vec<tree *> old_headps (numgroups);
10099 auto_vec<tree> new_heads (numgroups);
10100 auto_vec<tree> old_succs (numgroups);
10101 bool map_at_start = (list_p == (*groups)[0].grp_start);
10103 tree *new_grp_tail = NULL;
10105 /* Stash the start & end nodes of each mapping group before we start
10106 modifying the list. */
10107 FOR_EACH_VEC_ELT (*groups, i, grp)
10109 old_headps.quick_push (grp->grp_start);
10110 old_heads.quick_push (*grp->grp_start);
10111 old_succs.quick_push (OMP_CLAUSE_CHAIN (grp->grp_end));
10114 /* And similarly, the heads of the groups in the order we want to rearrange
10115 the list to. */
10116 for (omp_mapping_group *w = head; w; w = w->next)
10117 new_heads.quick_push (*w->grp_start);
10119 FOR_EACH_VEC_ELT (*groups, i, grp)
10121 gcc_assert (head);
10123 if (new_grp_tail && old_succs[i - 1] == old_heads[i])
10125 /* a {b c d} {e f g} h i j (original)
10127 a {k l m} {e f g} h i j (inserted new group on last iter)
10129 a {k l m} {n o p} h i j (this time, chain last group to new one)
10130 ^new_grp_tail
10132 *new_grp_tail = new_heads[i];
10134 else if (new_grp_tail)
10136 /* a {b c d} e {f g h} i j k (original)
10138 a {l m n} e {f g h} i j k (gap after last iter's group)
10140 a {l m n} e {o p q} h i j (chain last group to old successor)
10141 ^new_grp_tail
10143 *new_grp_tail = old_succs[i - 1];
10144 *old_headps[i] = new_heads[i];
10146 else
10148 /* The first inserted group -- point to new group, and leave end
10149 open.
10150 a {b c d} e f
10152 a {g h i...
10154 *grp->grp_start = new_heads[i];
10157 new_grp_tail = &OMP_CLAUSE_CHAIN (head->grp_end);
10159 head = head->next;
10162 if (new_grp_tail)
10163 *new_grp_tail = old_succs[numgroups - 1];
10165 gcc_assert (!head);
10167 return map_at_start ? (*groups)[0].grp_start : list_p;
10170 /* DECL is supposed to have lastprivate semantics in the outer contexts
10171 of combined/composite constructs, starting with OCTX.
10172 Add needed lastprivate, shared or map clause if no data sharing or
10173 mapping clause are present. IMPLICIT_P is true if it is an implicit
10174 clause (IV on simd), in which case the lastprivate will not be
10175 copied to some constructs. */
10177 static void
10178 omp_lastprivate_for_combined_outer_constructs (struct gimplify_omp_ctx *octx,
10179 tree decl, bool implicit_p)
10181 struct gimplify_omp_ctx *orig_octx = octx;
10182 for (; octx; octx = octx->outer_context)
10184 if ((octx->region_type == ORT_COMBINED_PARALLEL
10185 || (octx->region_type & ORT_COMBINED_TEAMS) == ORT_COMBINED_TEAMS)
10186 && splay_tree_lookup (octx->variables,
10187 (splay_tree_key) decl) == NULL)
10189 omp_add_variable (octx, decl, GOVD_SHARED | GOVD_SEEN);
10190 continue;
10192 if ((octx->region_type & ORT_TASK) != 0
10193 && octx->combined_loop
10194 && splay_tree_lookup (octx->variables,
10195 (splay_tree_key) decl) == NULL)
10197 omp_add_variable (octx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
10198 continue;
10200 if (implicit_p
10201 && octx->region_type == ORT_WORKSHARE
10202 && octx->combined_loop
10203 && splay_tree_lookup (octx->variables,
10204 (splay_tree_key) decl) == NULL
10205 && octx->outer_context
10206 && octx->outer_context->region_type == ORT_COMBINED_PARALLEL
10207 && splay_tree_lookup (octx->outer_context->variables,
10208 (splay_tree_key) decl) == NULL)
10210 octx = octx->outer_context;
10211 omp_add_variable (octx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
10212 continue;
10214 if ((octx->region_type == ORT_WORKSHARE || octx->region_type == ORT_ACC)
10215 && octx->combined_loop
10216 && splay_tree_lookup (octx->variables,
10217 (splay_tree_key) decl) == NULL
10218 && !omp_check_private (octx, decl, false))
10220 omp_add_variable (octx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
10221 continue;
10223 if (octx->region_type == ORT_COMBINED_TARGET)
10225 splay_tree_node n = splay_tree_lookup (octx->variables,
10226 (splay_tree_key) decl);
10227 if (n == NULL)
10229 omp_add_variable (octx, decl, GOVD_MAP | GOVD_SEEN);
10230 octx = octx->outer_context;
10232 else if (!implicit_p
10233 && (n->value & GOVD_FIRSTPRIVATE_IMPLICIT))
10235 n->value &= ~(GOVD_FIRSTPRIVATE
10236 | GOVD_FIRSTPRIVATE_IMPLICIT
10237 | GOVD_EXPLICIT);
10238 omp_add_variable (octx, decl, GOVD_MAP | GOVD_SEEN);
10239 octx = octx->outer_context;
10242 break;
10244 if (octx && (implicit_p || octx != orig_octx))
10245 omp_notice_variable (octx, decl, true);
10248 /* If we have mappings INNER and OUTER, where INNER is a component access and
10249 OUTER is a mapping of the whole containing struct, check that the mappings
10250 are compatible. We'll be deleting the inner mapping, so we need to make
10251 sure the outer mapping does (at least) the same transfers to/from the device
10252 as the inner mapping. */
10254 bool
10255 omp_check_mapping_compatibility (location_t loc,
10256 omp_mapping_group *outer,
10257 omp_mapping_group *inner)
10259 tree first_outer = *outer->grp_start, first_inner = *inner->grp_start;
10261 gcc_assert (OMP_CLAUSE_CODE (first_outer) == OMP_CLAUSE_MAP);
10262 gcc_assert (OMP_CLAUSE_CODE (first_inner) == OMP_CLAUSE_MAP);
10264 enum gomp_map_kind outer_kind = OMP_CLAUSE_MAP_KIND (first_outer);
10265 enum gomp_map_kind inner_kind = OMP_CLAUSE_MAP_KIND (first_inner);
10267 if (outer_kind == inner_kind)
10268 return true;
10270 switch (outer_kind)
10272 case GOMP_MAP_ALWAYS_TO:
10273 if (inner_kind == GOMP_MAP_FORCE_PRESENT
10274 || inner_kind == GOMP_MAP_ALLOC
10275 || inner_kind == GOMP_MAP_TO)
10276 return true;
10277 break;
10279 case GOMP_MAP_ALWAYS_FROM:
10280 if (inner_kind == GOMP_MAP_FORCE_PRESENT
10281 || inner_kind == GOMP_MAP_ALLOC
10282 || inner_kind == GOMP_MAP_FROM)
10283 return true;
10284 break;
10286 case GOMP_MAP_TO:
10287 case GOMP_MAP_FROM:
10288 if (inner_kind == GOMP_MAP_FORCE_PRESENT
10289 || inner_kind == GOMP_MAP_ALLOC)
10290 return true;
10291 break;
10293 case GOMP_MAP_ALWAYS_TOFROM:
10294 case GOMP_MAP_TOFROM:
10295 if (inner_kind == GOMP_MAP_FORCE_PRESENT
10296 || inner_kind == GOMP_MAP_ALLOC
10297 || inner_kind == GOMP_MAP_TO
10298 || inner_kind == GOMP_MAP_FROM
10299 || inner_kind == GOMP_MAP_TOFROM)
10300 return true;
10301 break;
10303 default:
10307 error_at (loc, "data movement for component %qE is not compatible with "
10308 "movement for struct %qE", OMP_CLAUSE_DECL (first_inner),
10309 OMP_CLAUSE_DECL (first_outer));
10311 return false;
10314 /* Similar to omp_resolve_clause_dependencies, but for OpenACC. The only
10315 clause dependencies we handle for now are struct element mappings and
10316 whole-struct mappings on the same directive, and duplicate clause
10317 detection. */
10319 void
10320 oacc_resolve_clause_dependencies (vec<omp_mapping_group> *groups,
10321 hash_map<tree_operand_hash_no_se,
10322 omp_mapping_group *> *grpmap)
10324 int i;
10325 omp_mapping_group *grp;
10326 hash_set<tree_operand_hash> *seen_components = NULL;
10327 hash_set<tree_operand_hash> *shown_error = NULL;
10329 FOR_EACH_VEC_ELT (*groups, i, grp)
10331 tree grp_end = grp->grp_end;
10332 tree decl = OMP_CLAUSE_DECL (grp_end);
10334 gcc_assert (OMP_CLAUSE_CODE (grp_end) == OMP_CLAUSE_MAP);
10336 if (DECL_P (grp_end))
10337 continue;
10339 tree c = OMP_CLAUSE_DECL (*grp->grp_start);
10340 while (TREE_CODE (c) == ARRAY_REF)
10341 c = TREE_OPERAND (c, 0);
10342 if (TREE_CODE (c) != COMPONENT_REF)
10343 continue;
10344 if (!seen_components)
10345 seen_components = new hash_set<tree_operand_hash> ();
10346 if (!shown_error)
10347 shown_error = new hash_set<tree_operand_hash> ();
10348 if (seen_components->contains (c)
10349 && !shown_error->contains (c))
10351 error_at (OMP_CLAUSE_LOCATION (grp_end),
10352 "%qE appears more than once in map clauses",
10353 OMP_CLAUSE_DECL (grp_end));
10354 shown_error->add (c);
10356 else
10357 seen_components->add (c);
10359 omp_mapping_group *struct_group;
10360 if (omp_mapped_by_containing_struct (grpmap, decl, &struct_group)
10361 && *grp->grp_start == grp_end)
10363 omp_check_mapping_compatibility (OMP_CLAUSE_LOCATION (grp_end),
10364 struct_group, grp);
10365 /* Remove the whole of this mapping -- redundant. */
10366 grp->deleted = true;
10370 if (seen_components)
10371 delete seen_components;
10372 if (shown_error)
10373 delete shown_error;
10376 /* Link node NEWNODE so it is pointed to by chain INSERT_AT. NEWNODE's chain
10377 is linked to the previous node pointed to by INSERT_AT. */
10379 static tree *
10380 omp_siblist_insert_node_after (tree newnode, tree *insert_at)
10382 OMP_CLAUSE_CHAIN (newnode) = *insert_at;
10383 *insert_at = newnode;
10384 return &OMP_CLAUSE_CHAIN (newnode);
10387 /* Move NODE (which is currently pointed to by the chain OLD_POS) so it is
10388 pointed to by chain MOVE_AFTER instead. */
10390 static void
10391 omp_siblist_move_node_after (tree node, tree *old_pos, tree *move_after)
10393 gcc_assert (node == *old_pos);
10394 *old_pos = OMP_CLAUSE_CHAIN (node);
10395 OMP_CLAUSE_CHAIN (node) = *move_after;
10396 *move_after = node;
10399 /* Move nodes from FIRST_PTR (pointed to by previous node's chain) to
10400 LAST_NODE to after MOVE_AFTER chain. Similar to below function, but no
10401 new nodes are prepended to the list before splicing into the new position.
10402 Return the position we should continue scanning the list at, or NULL to
10403 stay where we were. */
10405 static tree *
10406 omp_siblist_move_nodes_after (tree *first_ptr, tree last_node,
10407 tree *move_after)
10409 if (first_ptr == move_after)
10410 return NULL;
10412 tree tmp = *first_ptr;
10413 *first_ptr = OMP_CLAUSE_CHAIN (last_node);
10414 OMP_CLAUSE_CHAIN (last_node) = *move_after;
10415 *move_after = tmp;
10417 return first_ptr;
10420 /* Concatenate two lists described by [FIRST_NEW, LAST_NEW_TAIL] and
10421 [FIRST_PTR, LAST_NODE], and insert them in the OMP clause list after chain
10422 pointer MOVE_AFTER.
10424 The latter list was previously part of the OMP clause list, and the former
10425 (prepended) part is comprised of new nodes.
10427 We start with a list of nodes starting with a struct mapping node. We
10428 rearrange the list so that new nodes starting from FIRST_NEW and whose last
10429 node's chain is LAST_NEW_TAIL comes directly after MOVE_AFTER, followed by
10430 the group of mapping nodes we are currently processing (from the chain
10431 FIRST_PTR to LAST_NODE). The return value is the pointer to the next chain
10432 we should continue processing from, or NULL to stay where we were.
10434 The transformation (in the case where MOVE_AFTER and FIRST_PTR are
10435 different) is worked through below. Here we are processing LAST_NODE, and
10436 FIRST_PTR points at the preceding mapping clause:
10438 #. mapping node chain
10439 ---------------------------------------------------
10440 A. struct_node [->B]
10441 B. comp_1 [->C]
10442 C. comp_2 [->D (move_after)]
10443 D. map_to_3 [->E]
10444 E. attach_3 [->F (first_ptr)]
10445 F. map_to_4 [->G (continue_at)]
10446 G. attach_4 (last_node) [->H]
10447 H. ...
10449 *last_new_tail = *first_ptr;
10451 I. new_node (first_new) [->F (last_new_tail)]
10453 *first_ptr = OMP_CLAUSE_CHAIN (last_node)
10455 #. mapping node chain
10456 ----------------------------------------------------
10457 A. struct_node [->B]
10458 B. comp_1 [->C]
10459 C. comp_2 [->D (move_after)]
10460 D. map_to_3 [->E]
10461 E. attach_3 [->H (first_ptr)]
10462 F. map_to_4 [->G (continue_at)]
10463 G. attach_4 (last_node) [->H]
10464 H. ...
10466 I. new_node (first_new) [->F (last_new_tail)]
10468 OMP_CLAUSE_CHAIN (last_node) = *move_after;
10470 #. mapping node chain
10471 ---------------------------------------------------
10472 A. struct_node [->B]
10473 B. comp_1 [->C]
10474 C. comp_2 [->D (move_after)]
10475 D. map_to_3 [->E]
10476 E. attach_3 [->H (continue_at)]
10477 F. map_to_4 [->G]
10478 G. attach_4 (last_node) [->D]
10479 H. ...
10481 I. new_node (first_new) [->F (last_new_tail)]
10483 *move_after = first_new;
10485 #. mapping node chain
10486 ---------------------------------------------------
10487 A. struct_node [->B]
10488 B. comp_1 [->C]
10489 C. comp_2 [->I (move_after)]
10490 D. map_to_3 [->E]
10491 E. attach_3 [->H (continue_at)]
10492 F. map_to_4 [->G]
10493 G. attach_4 (last_node) [->D]
10494 H. ...
10495 I. new_node (first_new) [->F (last_new_tail)]
10497 or, in order:
10499 #. mapping node chain
10500 ---------------------------------------------------
10501 A. struct_node [->B]
10502 B. comp_1 [->C]
10503 C. comp_2 [->I (move_after)]
10504 I. new_node (first_new) [->F (last_new_tail)]
10505 F. map_to_4 [->G]
10506 G. attach_4 (last_node) [->D]
10507 D. map_to_3 [->E]
10508 E. attach_3 [->H (continue_at)]
10509 H. ...
10512 static tree *
10513 omp_siblist_move_concat_nodes_after (tree first_new, tree *last_new_tail,
10514 tree *first_ptr, tree last_node,
10515 tree *move_after)
10517 tree *continue_at = NULL;
10518 *last_new_tail = *first_ptr;
10519 if (first_ptr == move_after)
10520 *move_after = first_new;
10521 else
10523 *first_ptr = OMP_CLAUSE_CHAIN (last_node);
10524 continue_at = first_ptr;
10525 OMP_CLAUSE_CHAIN (last_node) = *move_after;
10526 *move_after = first_new;
10528 return continue_at;
10531 /* Mapping struct members causes an additional set of nodes to be created,
10532 starting with GOMP_MAP_STRUCT followed by a number of mappings equal to the
10533 number of members being mapped, in order of ascending position (address or
10534 bitwise).
10536 We scan through the list of mapping clauses, calling this function for each
10537 struct member mapping we find, and build up the list of mappings after the
10538 initial GOMP_MAP_STRUCT node. For pointer members, these will be
10539 newly-created ALLOC nodes. For non-pointer members, the existing mapping is
10540 moved into place in the sorted list.
10542 struct {
10543 int *a;
10544 int *b;
10545 int c;
10546 int *d;
10549 #pragma (acc|omp directive) copy(struct.a[0:n], struct.b[0:n], struct.c,
10550 struct.d[0:n])
10552 GOMP_MAP_STRUCT (4)
10553 [GOMP_MAP_FIRSTPRIVATE_REFERENCE -- for refs to structs]
10554 GOMP_MAP_ALLOC (struct.a)
10555 GOMP_MAP_ALLOC (struct.b)
10556 GOMP_MAP_TO (struct.c)
10557 GOMP_MAP_ALLOC (struct.d)
10560 In the case where we are mapping references to pointers, or in Fortran if
10561 we are mapping an array with a descriptor, additional nodes may be created
10562 after the struct node list also.
10564 The return code is either a pointer to the next node to process (if the
10565 list has been rearranged), else NULL to continue with the next node in the
10566 original list. */
10568 static tree *
10569 omp_accumulate_sibling_list (enum omp_region_type region_type,
10570 enum tree_code code,
10571 hash_map<tree_operand_hash, tree>
10572 *&struct_map_to_clause, tree *grp_start_p,
10573 tree grp_end, tree *inner)
10575 poly_offset_int coffset;
10576 poly_int64 cbitpos;
10577 tree ocd = OMP_CLAUSE_DECL (grp_end);
10578 bool openmp = !(region_type & ORT_ACC);
10579 tree *continue_at = NULL;
10581 while (TREE_CODE (ocd) == ARRAY_REF)
10582 ocd = TREE_OPERAND (ocd, 0);
10584 if (INDIRECT_REF_P (ocd))
10585 ocd = TREE_OPERAND (ocd, 0);
10587 tree base = extract_base_bit_offset (ocd, &cbitpos, &coffset);
10589 bool ptr = (OMP_CLAUSE_MAP_KIND (grp_end) == GOMP_MAP_ALWAYS_POINTER);
10590 bool attach_detach = ((OMP_CLAUSE_MAP_KIND (grp_end)
10591 == GOMP_MAP_ATTACH_DETACH)
10592 || (OMP_CLAUSE_MAP_KIND (grp_end)
10593 == GOMP_MAP_ATTACH_ZERO_LENGTH_ARRAY_SECTION));
10594 bool attach = (OMP_CLAUSE_MAP_KIND (grp_end) == GOMP_MAP_ATTACH
10595 || OMP_CLAUSE_MAP_KIND (grp_end) == GOMP_MAP_DETACH);
10597 /* FIXME: If we're not mapping the base pointer in some other clause on this
10598 directive, I think we want to create ALLOC/RELEASE here -- i.e. not
10599 early-exit. */
10600 if (openmp && attach_detach)
10601 return NULL;
10603 if (!struct_map_to_clause || struct_map_to_clause->get (base) == NULL)
10605 tree l = build_omp_clause (OMP_CLAUSE_LOCATION (grp_end), OMP_CLAUSE_MAP);
10606 gomp_map_kind k = attach ? GOMP_MAP_FORCE_PRESENT : GOMP_MAP_STRUCT;
10608 OMP_CLAUSE_SET_MAP_KIND (l, k);
10610 OMP_CLAUSE_DECL (l) = unshare_expr (base);
10612 OMP_CLAUSE_SIZE (l)
10613 = (!attach ? size_int (1)
10614 : (DECL_P (OMP_CLAUSE_DECL (l))
10615 ? DECL_SIZE_UNIT (OMP_CLAUSE_DECL (l))
10616 : TYPE_SIZE_UNIT (TREE_TYPE (OMP_CLAUSE_DECL (l)))));
10617 if (struct_map_to_clause == NULL)
10618 struct_map_to_clause = new hash_map<tree_operand_hash, tree>;
10619 struct_map_to_clause->put (base, l);
10621 if (ptr || attach_detach)
10623 tree extra_node;
10624 tree alloc_node
10625 = build_omp_struct_comp_nodes (code, *grp_start_p, grp_end,
10626 &extra_node);
10627 OMP_CLAUSE_CHAIN (l) = alloc_node;
10629 tree *insert_node_pos = grp_start_p;
10631 if (extra_node)
10633 OMP_CLAUSE_CHAIN (extra_node) = *insert_node_pos;
10634 OMP_CLAUSE_CHAIN (alloc_node) = extra_node;
10636 else
10637 OMP_CLAUSE_CHAIN (alloc_node) = *insert_node_pos;
10639 *insert_node_pos = l;
10641 else
10643 gcc_assert (*grp_start_p == grp_end);
10644 grp_start_p = omp_siblist_insert_node_after (l, grp_start_p);
10647 tree noind = omp_strip_indirections (base);
10649 if (!openmp
10650 && (region_type & ORT_TARGET)
10651 && TREE_CODE (noind) == COMPONENT_REF)
10653 /* The base for this component access is a struct component access
10654 itself. Insert a node to be processed on the next iteration of
10655 our caller's loop, which will subsequently be turned into a new,
10656 inner GOMP_MAP_STRUCT mapping.
10658 We need to do this else the non-DECL_P base won't be
10659 rewritten correctly in the offloaded region. */
10660 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (grp_end),
10661 OMP_CLAUSE_MAP);
10662 OMP_CLAUSE_SET_MAP_KIND (c2, GOMP_MAP_FORCE_PRESENT);
10663 OMP_CLAUSE_DECL (c2) = unshare_expr (noind);
10664 OMP_CLAUSE_SIZE (c2) = TYPE_SIZE_UNIT (TREE_TYPE (noind));
10665 *inner = c2;
10666 return NULL;
10669 tree sdecl = omp_strip_components_and_deref (base);
10671 if (POINTER_TYPE_P (TREE_TYPE (sdecl)) && (region_type & ORT_TARGET))
10673 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (grp_end),
10674 OMP_CLAUSE_MAP);
10675 bool base_ref
10676 = (INDIRECT_REF_P (base)
10677 && ((TREE_CODE (TREE_TYPE (TREE_OPERAND (base, 0)))
10678 == REFERENCE_TYPE)
10679 || (INDIRECT_REF_P (TREE_OPERAND (base, 0))
10680 && (TREE_CODE (TREE_TYPE (TREE_OPERAND
10681 (TREE_OPERAND (base, 0), 0)))
10682 == REFERENCE_TYPE))));
10683 enum gomp_map_kind mkind = base_ref ? GOMP_MAP_FIRSTPRIVATE_REFERENCE
10684 : GOMP_MAP_FIRSTPRIVATE_POINTER;
10685 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
10686 OMP_CLAUSE_DECL (c2) = sdecl;
10687 tree baddr = build_fold_addr_expr (base);
10688 baddr = fold_convert_loc (OMP_CLAUSE_LOCATION (grp_end),
10689 ptrdiff_type_node, baddr);
10690 /* This isn't going to be good enough when we add support for more
10691 complicated lvalue expressions. FIXME. */
10692 if (TREE_CODE (TREE_TYPE (sdecl)) == REFERENCE_TYPE
10693 && TREE_CODE (TREE_TYPE (TREE_TYPE (sdecl))) == POINTER_TYPE)
10694 sdecl = build_simple_mem_ref (sdecl);
10695 tree decladdr = fold_convert_loc (OMP_CLAUSE_LOCATION (grp_end),
10696 ptrdiff_type_node, sdecl);
10697 OMP_CLAUSE_SIZE (c2)
10698 = fold_build2_loc (OMP_CLAUSE_LOCATION (grp_end), MINUS_EXPR,
10699 ptrdiff_type_node, baddr, decladdr);
10700 /* Insert after struct node. */
10701 OMP_CLAUSE_CHAIN (c2) = OMP_CLAUSE_CHAIN (l);
10702 OMP_CLAUSE_CHAIN (l) = c2;
10705 return NULL;
10707 else if (struct_map_to_clause)
10709 tree *osc = struct_map_to_clause->get (base);
10710 tree *sc = NULL, *scp = NULL;
10711 sc = &OMP_CLAUSE_CHAIN (*osc);
10712 /* The struct mapping might be immediately followed by a
10713 FIRSTPRIVATE_POINTER and/or FIRSTPRIVATE_REFERENCE -- if it's an
10714 indirect access or a reference, or both. (This added node is removed
10715 in omp-low.c after it has been processed there.) */
10716 if (*sc != grp_end
10717 && (OMP_CLAUSE_MAP_KIND (*sc) == GOMP_MAP_FIRSTPRIVATE_POINTER
10718 || OMP_CLAUSE_MAP_KIND (*sc) == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
10719 sc = &OMP_CLAUSE_CHAIN (*sc);
10720 for (; *sc != grp_end; sc = &OMP_CLAUSE_CHAIN (*sc))
10721 if ((ptr || attach_detach) && sc == grp_start_p)
10722 break;
10723 else if (TREE_CODE (OMP_CLAUSE_DECL (*sc)) != COMPONENT_REF
10724 && TREE_CODE (OMP_CLAUSE_DECL (*sc)) != INDIRECT_REF
10725 && TREE_CODE (OMP_CLAUSE_DECL (*sc)) != ARRAY_REF)
10726 break;
10727 else
10729 tree sc_decl = OMP_CLAUSE_DECL (*sc);
10730 poly_offset_int offset;
10731 poly_int64 bitpos;
10733 if (TREE_CODE (sc_decl) == ARRAY_REF)
10735 while (TREE_CODE (sc_decl) == ARRAY_REF)
10736 sc_decl = TREE_OPERAND (sc_decl, 0);
10737 if (TREE_CODE (sc_decl) != COMPONENT_REF
10738 || TREE_CODE (TREE_TYPE (sc_decl)) != ARRAY_TYPE)
10739 break;
10741 else if (INDIRECT_REF_P (sc_decl)
10742 && TREE_CODE (TREE_OPERAND (sc_decl, 0)) == COMPONENT_REF
10743 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (sc_decl, 0)))
10744 == REFERENCE_TYPE))
10745 sc_decl = TREE_OPERAND (sc_decl, 0);
10747 tree base2 = extract_base_bit_offset (sc_decl, &bitpos, &offset);
10748 if (!base2 || !operand_equal_p (base2, base, 0))
10749 break;
10750 if (scp)
10751 continue;
10752 if (maybe_lt (coffset, offset)
10753 || (known_eq (coffset, offset)
10754 && maybe_lt (cbitpos, bitpos)))
10756 if (ptr || attach_detach)
10757 scp = sc;
10758 else
10759 break;
10763 if (!attach)
10764 OMP_CLAUSE_SIZE (*osc)
10765 = size_binop (PLUS_EXPR, OMP_CLAUSE_SIZE (*osc), size_one_node);
10766 if (ptr || attach_detach)
10768 tree cl = NULL_TREE, extra_node;
10769 tree alloc_node = build_omp_struct_comp_nodes (code, *grp_start_p,
10770 grp_end, &extra_node);
10771 tree *tail_chain = NULL;
10773 /* Here, we have:
10775 grp_end : the last (or only) node in this group.
10776 grp_start_p : pointer to the first node in a pointer mapping group
10777 up to and including GRP_END.
10778 sc : pointer to the chain for the end of the struct component
10779 list.
10780 scp : pointer to the chain for the sorted position at which we
10781 should insert in the middle of the struct component list
10782 (else NULL to insert at end).
10783 alloc_node : the "alloc" node for the structure (pointer-type)
10784 component. We insert at SCP (if present), else SC
10785 (the end of the struct component list).
10786 extra_node : a newly-synthesized node for an additional indirect
10787 pointer mapping or a Fortran pointer set, if needed.
10788 cl : first node to prepend before grp_start_p.
10789 tail_chain : pointer to chain of last prepended node.
10791 The general idea is we move the nodes for this struct mapping
10792 together: the alloc node goes into the sorted list directly after
10793 the struct mapping, and any extra nodes (together with the nodes
10794 mapping arrays pointed to by struct components) get moved after
10795 that list. When SCP is NULL, we insert the nodes at SC, i.e. at
10796 the end of the struct component mapping list. It's important that
10797 the alloc_node comes first in that case because it's part of the
10798 sorted component mapping list (but subsequent nodes are not!). */
10800 if (scp)
10801 omp_siblist_insert_node_after (alloc_node, scp);
10803 /* Make [cl,tail_chain] a list of the alloc node (if we haven't
10804 already inserted it) and the extra_node (if it is present). The
10805 list can be empty if we added alloc_node above and there is no
10806 extra node. */
10807 if (scp && extra_node)
10809 cl = extra_node;
10810 tail_chain = &OMP_CLAUSE_CHAIN (extra_node);
10812 else if (extra_node)
10814 OMP_CLAUSE_CHAIN (alloc_node) = extra_node;
10815 cl = alloc_node;
10816 tail_chain = &OMP_CLAUSE_CHAIN (extra_node);
10818 else if (!scp)
10820 cl = alloc_node;
10821 tail_chain = &OMP_CLAUSE_CHAIN (alloc_node);
10824 continue_at
10825 = cl ? omp_siblist_move_concat_nodes_after (cl, tail_chain,
10826 grp_start_p, grp_end,
10828 : omp_siblist_move_nodes_after (grp_start_p, grp_end, sc);
10830 else if (*sc != grp_end)
10832 gcc_assert (*grp_start_p == grp_end);
10834 /* We are moving the current node back to a previous struct node:
10835 the node that used to point to the current node will now point to
10836 the next node. */
10837 continue_at = grp_start_p;
10838 /* In the non-pointer case, the mapping clause itself is moved into
10839 the correct position in the struct component list, which in this
10840 case is just SC. */
10841 omp_siblist_move_node_after (*grp_start_p, grp_start_p, sc);
10844 return continue_at;
10847 /* Scan through GROUPS, and create sorted structure sibling lists without
10848 gimplifying. */
10850 static bool
10851 omp_build_struct_sibling_lists (enum tree_code code,
10852 enum omp_region_type region_type,
10853 vec<omp_mapping_group> *groups,
10854 hash_map<tree_operand_hash_no_se,
10855 omp_mapping_group *> **grpmap,
10856 tree *list_p)
10858 unsigned i;
10859 omp_mapping_group *grp;
10860 hash_map<tree_operand_hash, tree> *struct_map_to_clause = NULL;
10861 bool success = true;
10862 tree *new_next = NULL;
10863 tree *tail = &OMP_CLAUSE_CHAIN ((*groups)[groups->length () - 1].grp_end);
10864 auto_vec<omp_mapping_group> pre_hwm_groups;
10866 FOR_EACH_VEC_ELT (*groups, i, grp)
10868 tree c = grp->grp_end;
10869 tree decl = OMP_CLAUSE_DECL (c);
10870 tree grp_end = grp->grp_end;
10871 tree sentinel = OMP_CLAUSE_CHAIN (grp_end);
10873 if (new_next)
10874 grp->grp_start = new_next;
10876 new_next = NULL;
10878 tree *grp_start_p = grp->grp_start;
10880 if (DECL_P (decl))
10881 continue;
10883 /* Skip groups we marked for deletion in
10884 oacc_resolve_clause_dependencies. */
10885 if (grp->deleted)
10886 continue;
10888 if (OMP_CLAUSE_CHAIN (*grp_start_p)
10889 && OMP_CLAUSE_CHAIN (*grp_start_p) != grp_end)
10891 /* Don't process an array descriptor that isn't inside a derived type
10892 as a struct (the GOMP_MAP_POINTER following will have the form
10893 "var.data", but such mappings are handled specially). */
10894 tree grpmid = OMP_CLAUSE_CHAIN (*grp_start_p);
10895 if (OMP_CLAUSE_CODE (grpmid) == OMP_CLAUSE_MAP
10896 && OMP_CLAUSE_MAP_KIND (grpmid) == GOMP_MAP_TO_PSET
10897 && DECL_P (OMP_CLAUSE_DECL (grpmid)))
10898 continue;
10901 tree d = decl;
10902 if (TREE_CODE (d) == ARRAY_REF)
10904 while (TREE_CODE (d) == ARRAY_REF)
10905 d = TREE_OPERAND (d, 0);
10906 if (TREE_CODE (d) == COMPONENT_REF
10907 && TREE_CODE (TREE_TYPE (d)) == ARRAY_TYPE)
10908 decl = d;
10910 if (d == decl
10911 && INDIRECT_REF_P (decl)
10912 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
10913 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
10914 == REFERENCE_TYPE)
10915 && (OMP_CLAUSE_MAP_KIND (c)
10916 != GOMP_MAP_POINTER_TO_ZERO_LENGTH_ARRAY_SECTION))
10917 decl = TREE_OPERAND (decl, 0);
10919 STRIP_NOPS (decl);
10921 if (TREE_CODE (decl) != COMPONENT_REF)
10922 continue;
10924 /* If we're mapping the whole struct in another node, skip adding this
10925 node to a sibling list. */
10926 omp_mapping_group *wholestruct;
10927 if (omp_mapped_by_containing_struct (*grpmap, OMP_CLAUSE_DECL (c),
10928 &wholestruct))
10930 if (!(region_type & ORT_ACC)
10931 && *grp_start_p == grp_end)
10932 /* Remove the whole of this mapping -- redundant. */
10933 grp->deleted = true;
10935 continue;
10938 if (OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_TO_PSET
10939 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ATTACH
10940 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_DETACH
10941 && code != OACC_UPDATE
10942 && code != OMP_TARGET_UPDATE)
10944 if (error_operand_p (decl))
10946 success = false;
10947 goto error_out;
10950 tree stype = TREE_TYPE (decl);
10951 if (TREE_CODE (stype) == REFERENCE_TYPE)
10952 stype = TREE_TYPE (stype);
10953 if (TYPE_SIZE_UNIT (stype) == NULL
10954 || TREE_CODE (TYPE_SIZE_UNIT (stype)) != INTEGER_CST)
10956 error_at (OMP_CLAUSE_LOCATION (c),
10957 "mapping field %qE of variable length "
10958 "structure", OMP_CLAUSE_DECL (c));
10959 success = false;
10960 goto error_out;
10963 tree inner = NULL_TREE;
10965 new_next
10966 = omp_accumulate_sibling_list (region_type, code,
10967 struct_map_to_clause, grp_start_p,
10968 grp_end, &inner);
10970 if (inner)
10972 if (new_next && *new_next == NULL_TREE)
10973 *new_next = inner;
10974 else
10975 *tail = inner;
10977 OMP_CLAUSE_CHAIN (inner) = NULL_TREE;
10978 omp_mapping_group newgrp;
10979 newgrp.grp_start = new_next ? new_next : tail;
10980 newgrp.grp_end = inner;
10981 newgrp.mark = UNVISITED;
10982 newgrp.sibling = NULL;
10983 newgrp.deleted = false;
10984 newgrp.next = NULL;
10985 groups->safe_push (newgrp);
10987 /* !!! Growing GROUPS might invalidate the pointers in the group
10988 map. Rebuild it here. This is a bit inefficient, but
10989 shouldn't happen very often. */
10990 delete (*grpmap);
10991 *grpmap
10992 = omp_reindex_mapping_groups (list_p, groups, &pre_hwm_groups,
10993 sentinel);
10995 tail = &OMP_CLAUSE_CHAIN (inner);
11000 /* Delete groups marked for deletion above. At this point the order of the
11001 groups may no longer correspond to the order of the underlying list,
11002 which complicates this a little. First clear out OMP_CLAUSE_DECL for
11003 deleted nodes... */
11005 FOR_EACH_VEC_ELT (*groups, i, grp)
11006 if (grp->deleted)
11007 for (tree d = *grp->grp_start;
11008 d != OMP_CLAUSE_CHAIN (grp->grp_end);
11009 d = OMP_CLAUSE_CHAIN (d))
11010 OMP_CLAUSE_DECL (d) = NULL_TREE;
11012 /* ...then sweep through the list removing the now-empty nodes. */
11014 tail = list_p;
11015 while (*tail)
11017 if (OMP_CLAUSE_CODE (*tail) == OMP_CLAUSE_MAP
11018 && OMP_CLAUSE_DECL (*tail) == NULL_TREE)
11019 *tail = OMP_CLAUSE_CHAIN (*tail);
11020 else
11021 tail = &OMP_CLAUSE_CHAIN (*tail);
11024 error_out:
11025 if (struct_map_to_clause)
11026 delete struct_map_to_clause;
11028 return success;
11031 /* Scan the OMP clauses in *LIST_P, installing mappings into a new
11032 and previous omp contexts. */
11034 static void
11035 gimplify_scan_omp_clauses (tree *list_p, gimple_seq *pre_p,
11036 enum omp_region_type region_type,
11037 enum tree_code code)
11039 struct gimplify_omp_ctx *ctx, *outer_ctx;
11040 tree c;
11041 tree *orig_list_p = list_p;
11042 int handled_depend_iterators = -1;
11043 int nowait = -1;
11045 ctx = new_omp_context (region_type);
11046 ctx->code = code;
11047 outer_ctx = ctx->outer_context;
11048 if (code == OMP_TARGET)
11050 if (!lang_GNU_Fortran ())
11051 ctx->defaultmap[GDMK_POINTER] = GOVD_MAP | GOVD_MAP_0LEN_ARRAY;
11052 ctx->defaultmap[GDMK_SCALAR] = GOVD_FIRSTPRIVATE;
11053 ctx->defaultmap[GDMK_SCALAR_TARGET] = (lang_GNU_Fortran ()
11054 ? GOVD_MAP : GOVD_FIRSTPRIVATE);
11056 if (!lang_GNU_Fortran ())
11057 switch (code)
11059 case OMP_TARGET:
11060 case OMP_TARGET_DATA:
11061 case OMP_TARGET_ENTER_DATA:
11062 case OMP_TARGET_EXIT_DATA:
11063 case OACC_DECLARE:
11064 case OACC_HOST_DATA:
11065 case OACC_PARALLEL:
11066 case OACC_KERNELS:
11067 ctx->target_firstprivatize_array_bases = true;
11068 default:
11069 break;
11072 if (code == OMP_TARGET
11073 || code == OMP_TARGET_DATA
11074 || code == OMP_TARGET_ENTER_DATA
11075 || code == OMP_TARGET_EXIT_DATA)
11077 vec<omp_mapping_group> *groups;
11078 groups = omp_gather_mapping_groups (list_p);
11079 if (groups)
11081 hash_map<tree_operand_hash_no_se, omp_mapping_group *> *grpmap;
11082 grpmap = omp_index_mapping_groups (groups);
11084 omp_build_struct_sibling_lists (code, region_type, groups, &grpmap,
11085 list_p);
11087 omp_mapping_group *outlist = NULL;
11089 /* Topological sorting may fail if we have duplicate nodes, which
11090 we should have detected and shown an error for already. Skip
11091 sorting in that case. */
11092 if (seen_error ())
11093 goto failure;
11095 delete grpmap;
11096 delete groups;
11098 /* Rebuild now we have struct sibling lists. */
11099 groups = omp_gather_mapping_groups (list_p);
11100 grpmap = omp_index_mapping_groups (groups);
11102 outlist = omp_tsort_mapping_groups (groups, grpmap);
11103 outlist = omp_segregate_mapping_groups (outlist);
11104 list_p = omp_reorder_mapping_groups (groups, outlist, list_p);
11106 failure:
11107 delete grpmap;
11108 delete groups;
11111 /* OpenMP map clauses with 'present' need to go in front of those
11112 without. */
11113 tree present_map_head = NULL;
11114 tree *present_map_tail_p = &present_map_head;
11115 tree *first_map_clause_p = NULL;
11117 for (tree *c_p = list_p; *c_p; )
11119 tree c = *c_p;
11120 tree *next_c_p = &OMP_CLAUSE_CHAIN (c);
11122 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP)
11124 if (!first_map_clause_p)
11125 first_map_clause_p = c_p;
11126 switch (OMP_CLAUSE_MAP_KIND (c))
11128 case GOMP_MAP_PRESENT_ALLOC:
11129 case GOMP_MAP_PRESENT_FROM:
11130 case GOMP_MAP_PRESENT_TO:
11131 case GOMP_MAP_PRESENT_TOFROM:
11132 next_c_p = c_p;
11133 *c_p = OMP_CLAUSE_CHAIN (c);
11135 OMP_CLAUSE_CHAIN (c) = NULL;
11136 *present_map_tail_p = c;
11137 present_map_tail_p = &OMP_CLAUSE_CHAIN (c);
11139 break;
11141 default:
11142 break;
11146 c_p = next_c_p;
11148 if (first_map_clause_p && present_map_head)
11150 tree next = *first_map_clause_p;
11151 *first_map_clause_p = present_map_head;
11152 *present_map_tail_p = next;
11155 else if (region_type & ORT_ACC)
11157 vec<omp_mapping_group> *groups;
11158 groups = omp_gather_mapping_groups (list_p);
11159 if (groups)
11161 hash_map<tree_operand_hash_no_se, omp_mapping_group *> *grpmap;
11162 grpmap = omp_index_mapping_groups (groups);
11164 oacc_resolve_clause_dependencies (groups, grpmap);
11165 omp_build_struct_sibling_lists (code, region_type, groups, &grpmap,
11166 list_p);
11168 delete groups;
11169 delete grpmap;
11173 while ((c = *list_p) != NULL)
11175 bool remove = false;
11176 bool notice_outer = true;
11177 const char *check_non_private = NULL;
11178 unsigned int flags;
11179 tree decl;
11181 switch (OMP_CLAUSE_CODE (c))
11183 case OMP_CLAUSE_PRIVATE:
11184 flags = GOVD_PRIVATE | GOVD_EXPLICIT;
11185 if (lang_hooks.decls.omp_private_outer_ref (OMP_CLAUSE_DECL (c)))
11187 flags |= GOVD_PRIVATE_OUTER_REF;
11188 OMP_CLAUSE_PRIVATE_OUTER_REF (c) = 1;
11190 else
11191 notice_outer = false;
11192 goto do_add;
11193 case OMP_CLAUSE_SHARED:
11194 flags = GOVD_SHARED | GOVD_EXPLICIT;
11195 goto do_add;
11196 case OMP_CLAUSE_FIRSTPRIVATE:
11197 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
11198 check_non_private = "firstprivate";
11199 if (OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (c))
11201 gcc_assert (code == OMP_TARGET);
11202 flags |= GOVD_FIRSTPRIVATE_IMPLICIT;
11204 goto do_add;
11205 case OMP_CLAUSE_LASTPRIVATE:
11206 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
11207 switch (code)
11209 case OMP_DISTRIBUTE:
11210 error_at (OMP_CLAUSE_LOCATION (c),
11211 "conditional %<lastprivate%> clause on "
11212 "%qs construct", "distribute");
11213 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
11214 break;
11215 case OMP_TASKLOOP:
11216 error_at (OMP_CLAUSE_LOCATION (c),
11217 "conditional %<lastprivate%> clause on "
11218 "%qs construct", "taskloop");
11219 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
11220 break;
11221 default:
11222 break;
11224 flags = GOVD_LASTPRIVATE | GOVD_SEEN | GOVD_EXPLICIT;
11225 if (code != OMP_LOOP)
11226 check_non_private = "lastprivate";
11227 decl = OMP_CLAUSE_DECL (c);
11228 if (error_operand_p (decl))
11229 goto do_add;
11230 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c)
11231 && !lang_hooks.decls.omp_scalar_p (decl, true))
11233 error_at (OMP_CLAUSE_LOCATION (c),
11234 "non-scalar variable %qD in conditional "
11235 "%<lastprivate%> clause", decl);
11236 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
11238 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
11239 flags |= GOVD_LASTPRIVATE_CONDITIONAL;
11240 omp_lastprivate_for_combined_outer_constructs (outer_ctx, decl,
11241 false);
11242 goto do_add;
11243 case OMP_CLAUSE_REDUCTION:
11244 if (OMP_CLAUSE_REDUCTION_TASK (c))
11246 if (region_type == ORT_WORKSHARE || code == OMP_SCOPE)
11248 if (nowait == -1)
11249 nowait = omp_find_clause (*list_p,
11250 OMP_CLAUSE_NOWAIT) != NULL_TREE;
11251 if (nowait
11252 && (outer_ctx == NULL
11253 || outer_ctx->region_type != ORT_COMBINED_PARALLEL))
11255 error_at (OMP_CLAUSE_LOCATION (c),
11256 "%<task%> reduction modifier on a construct "
11257 "with a %<nowait%> clause");
11258 OMP_CLAUSE_REDUCTION_TASK (c) = 0;
11261 else if ((region_type & ORT_PARALLEL) != ORT_PARALLEL)
11263 error_at (OMP_CLAUSE_LOCATION (c),
11264 "invalid %<task%> reduction modifier on construct "
11265 "other than %<parallel%>, %qs, %<sections%> or "
11266 "%<scope%>", lang_GNU_Fortran () ? "do" : "for");
11267 OMP_CLAUSE_REDUCTION_TASK (c) = 0;
11270 if (OMP_CLAUSE_REDUCTION_INSCAN (c))
11271 switch (code)
11273 case OMP_SECTIONS:
11274 error_at (OMP_CLAUSE_LOCATION (c),
11275 "%<inscan%> %<reduction%> clause on "
11276 "%qs construct", "sections");
11277 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
11278 break;
11279 case OMP_PARALLEL:
11280 error_at (OMP_CLAUSE_LOCATION (c),
11281 "%<inscan%> %<reduction%> clause on "
11282 "%qs construct", "parallel");
11283 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
11284 break;
11285 case OMP_TEAMS:
11286 error_at (OMP_CLAUSE_LOCATION (c),
11287 "%<inscan%> %<reduction%> clause on "
11288 "%qs construct", "teams");
11289 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
11290 break;
11291 case OMP_TASKLOOP:
11292 error_at (OMP_CLAUSE_LOCATION (c),
11293 "%<inscan%> %<reduction%> clause on "
11294 "%qs construct", "taskloop");
11295 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
11296 break;
11297 case OMP_SCOPE:
11298 error_at (OMP_CLAUSE_LOCATION (c),
11299 "%<inscan%> %<reduction%> clause on "
11300 "%qs construct", "scope");
11301 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
11302 break;
11303 default:
11304 break;
11306 /* FALLTHRU */
11307 case OMP_CLAUSE_IN_REDUCTION:
11308 case OMP_CLAUSE_TASK_REDUCTION:
11309 flags = GOVD_REDUCTION | GOVD_SEEN | GOVD_EXPLICIT;
11310 /* OpenACC permits reductions on private variables. */
11311 if (!(region_type & ORT_ACC)
11312 /* taskgroup is actually not a worksharing region. */
11313 && code != OMP_TASKGROUP)
11314 check_non_private = omp_clause_code_name[OMP_CLAUSE_CODE (c)];
11315 decl = OMP_CLAUSE_DECL (c);
11316 if (TREE_CODE (decl) == MEM_REF)
11318 tree type = TREE_TYPE (decl);
11319 bool saved_into_ssa = gimplify_ctxp->into_ssa;
11320 gimplify_ctxp->into_ssa = false;
11321 if (gimplify_expr (&TYPE_MAX_VALUE (TYPE_DOMAIN (type)), pre_p,
11322 NULL, is_gimple_val, fb_rvalue, false)
11323 == GS_ERROR)
11325 gimplify_ctxp->into_ssa = saved_into_ssa;
11326 remove = true;
11327 break;
11329 gimplify_ctxp->into_ssa = saved_into_ssa;
11330 tree v = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
11331 if (DECL_P (v))
11333 omp_firstprivatize_variable (ctx, v);
11334 omp_notice_variable (ctx, v, true);
11336 decl = TREE_OPERAND (decl, 0);
11337 if (TREE_CODE (decl) == POINTER_PLUS_EXPR)
11339 gimplify_ctxp->into_ssa = false;
11340 if (gimplify_expr (&TREE_OPERAND (decl, 1), pre_p,
11341 NULL, is_gimple_val, fb_rvalue, false)
11342 == GS_ERROR)
11344 gimplify_ctxp->into_ssa = saved_into_ssa;
11345 remove = true;
11346 break;
11348 gimplify_ctxp->into_ssa = saved_into_ssa;
11349 v = TREE_OPERAND (decl, 1);
11350 if (DECL_P (v))
11352 omp_firstprivatize_variable (ctx, v);
11353 omp_notice_variable (ctx, v, true);
11355 decl = TREE_OPERAND (decl, 0);
11357 if (TREE_CODE (decl) == ADDR_EXPR
11358 || TREE_CODE (decl) == INDIRECT_REF)
11359 decl = TREE_OPERAND (decl, 0);
11361 goto do_add_decl;
11362 case OMP_CLAUSE_LINEAR:
11363 if (gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c), pre_p, NULL,
11364 is_gimple_val, fb_rvalue) == GS_ERROR)
11366 remove = true;
11367 break;
11369 else
11371 if (code == OMP_SIMD
11372 && !OMP_CLAUSE_LINEAR_NO_COPYIN (c))
11374 struct gimplify_omp_ctx *octx = outer_ctx;
11375 if (octx
11376 && octx->region_type == ORT_WORKSHARE
11377 && octx->combined_loop
11378 && !octx->distribute)
11380 if (octx->outer_context
11381 && (octx->outer_context->region_type
11382 == ORT_COMBINED_PARALLEL))
11383 octx = octx->outer_context->outer_context;
11384 else
11385 octx = octx->outer_context;
11387 if (octx
11388 && octx->region_type == ORT_WORKSHARE
11389 && octx->combined_loop
11390 && octx->distribute)
11392 error_at (OMP_CLAUSE_LOCATION (c),
11393 "%<linear%> clause for variable other than "
11394 "loop iterator specified on construct "
11395 "combined with %<distribute%>");
11396 remove = true;
11397 break;
11400 /* For combined #pragma omp parallel for simd, need to put
11401 lastprivate and perhaps firstprivate too on the
11402 parallel. Similarly for #pragma omp for simd. */
11403 struct gimplify_omp_ctx *octx = outer_ctx;
11404 bool taskloop_seen = false;
11405 decl = NULL_TREE;
11408 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
11409 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
11410 break;
11411 decl = OMP_CLAUSE_DECL (c);
11412 if (error_operand_p (decl))
11414 decl = NULL_TREE;
11415 break;
11417 flags = GOVD_SEEN;
11418 if (!OMP_CLAUSE_LINEAR_NO_COPYIN (c))
11419 flags |= GOVD_FIRSTPRIVATE;
11420 if (!OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
11421 flags |= GOVD_LASTPRIVATE;
11422 if (octx
11423 && octx->region_type == ORT_WORKSHARE
11424 && octx->combined_loop)
11426 if (octx->outer_context
11427 && (octx->outer_context->region_type
11428 == ORT_COMBINED_PARALLEL))
11429 octx = octx->outer_context;
11430 else if (omp_check_private (octx, decl, false))
11431 break;
11433 else if (octx
11434 && (octx->region_type & ORT_TASK) != 0
11435 && octx->combined_loop)
11436 taskloop_seen = true;
11437 else if (octx
11438 && octx->region_type == ORT_COMBINED_PARALLEL
11439 && ((ctx->region_type == ORT_WORKSHARE
11440 && octx == outer_ctx)
11441 || taskloop_seen))
11442 flags = GOVD_SEEN | GOVD_SHARED;
11443 else if (octx
11444 && ((octx->region_type & ORT_COMBINED_TEAMS)
11445 == ORT_COMBINED_TEAMS))
11446 flags = GOVD_SEEN | GOVD_SHARED;
11447 else if (octx
11448 && octx->region_type == ORT_COMBINED_TARGET)
11450 if (flags & GOVD_LASTPRIVATE)
11451 flags = GOVD_SEEN | GOVD_MAP;
11453 else
11454 break;
11455 splay_tree_node on
11456 = splay_tree_lookup (octx->variables,
11457 (splay_tree_key) decl);
11458 if (on && (on->value & GOVD_DATA_SHARE_CLASS) != 0)
11460 octx = NULL;
11461 break;
11463 omp_add_variable (octx, decl, flags);
11464 if (octx->outer_context == NULL)
11465 break;
11466 octx = octx->outer_context;
11468 while (1);
11469 if (octx
11470 && decl
11471 && (!OMP_CLAUSE_LINEAR_NO_COPYIN (c)
11472 || !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
11473 omp_notice_variable (octx, decl, true);
11475 flags = GOVD_LINEAR | GOVD_EXPLICIT;
11476 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
11477 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
11479 notice_outer = false;
11480 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
11482 goto do_add;
11484 case OMP_CLAUSE_MAP:
11485 decl = OMP_CLAUSE_DECL (c);
11486 if (error_operand_p (decl))
11487 remove = true;
11488 switch (code)
11490 case OMP_TARGET:
11491 break;
11492 case OACC_DATA:
11493 if (TREE_CODE (TREE_TYPE (decl)) != ARRAY_TYPE)
11494 break;
11495 /* FALLTHRU */
11496 case OMP_TARGET_DATA:
11497 case OMP_TARGET_ENTER_DATA:
11498 case OMP_TARGET_EXIT_DATA:
11499 case OACC_ENTER_DATA:
11500 case OACC_EXIT_DATA:
11501 case OACC_HOST_DATA:
11502 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
11503 || (OMP_CLAUSE_MAP_KIND (c)
11504 == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
11505 /* For target {,enter ,exit }data only the array slice is
11506 mapped, but not the pointer to it. */
11507 remove = true;
11508 break;
11509 default:
11510 break;
11512 if (remove)
11513 break;
11514 if (DECL_P (decl) && outer_ctx && (region_type & ORT_ACC))
11516 struct gimplify_omp_ctx *octx;
11517 for (octx = outer_ctx; octx; octx = octx->outer_context)
11519 if (octx->region_type != ORT_ACC_HOST_DATA)
11520 break;
11521 splay_tree_node n2
11522 = splay_tree_lookup (octx->variables,
11523 (splay_tree_key) decl);
11524 if (n2)
11525 error_at (OMP_CLAUSE_LOCATION (c), "variable %qE "
11526 "declared in enclosing %<host_data%> region",
11527 DECL_NAME (decl));
11530 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
11531 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
11532 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
11533 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
11534 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
11536 remove = true;
11537 break;
11539 else if ((OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
11540 || (OMP_CLAUSE_MAP_KIND (c)
11541 == GOMP_MAP_FIRSTPRIVATE_REFERENCE)
11542 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
11543 && TREE_CODE (OMP_CLAUSE_SIZE (c)) != INTEGER_CST)
11545 OMP_CLAUSE_SIZE (c)
11546 = get_initialized_tmp_var (OMP_CLAUSE_SIZE (c), pre_p, NULL,
11547 false);
11548 if ((region_type & ORT_TARGET) != 0)
11549 omp_add_variable (ctx, OMP_CLAUSE_SIZE (c),
11550 GOVD_FIRSTPRIVATE | GOVD_SEEN);
11553 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT)
11555 tree base = omp_strip_components_and_deref (decl);
11556 if (DECL_P (base))
11558 decl = base;
11559 splay_tree_node n
11560 = splay_tree_lookup (ctx->variables,
11561 (splay_tree_key) decl);
11562 if (seen_error ()
11563 && n
11564 && (n->value & (GOVD_MAP | GOVD_FIRSTPRIVATE)) != 0)
11566 remove = true;
11567 break;
11569 flags = GOVD_MAP | GOVD_EXPLICIT;
11571 goto do_add_decl;
11575 if (TREE_CODE (decl) == TARGET_EXPR)
11577 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
11578 is_gimple_lvalue, fb_lvalue)
11579 == GS_ERROR)
11580 remove = true;
11582 else if (!DECL_P (decl))
11584 tree d = decl, *pd;
11585 if (TREE_CODE (d) == ARRAY_REF)
11587 while (TREE_CODE (d) == ARRAY_REF)
11588 d = TREE_OPERAND (d, 0);
11589 if (TREE_CODE (d) == COMPONENT_REF
11590 && TREE_CODE (TREE_TYPE (d)) == ARRAY_TYPE)
11591 decl = d;
11593 pd = &OMP_CLAUSE_DECL (c);
11594 if (d == decl
11595 && TREE_CODE (decl) == INDIRECT_REF
11596 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
11597 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
11598 == REFERENCE_TYPE)
11599 && (OMP_CLAUSE_MAP_KIND (c)
11600 != GOMP_MAP_POINTER_TO_ZERO_LENGTH_ARRAY_SECTION))
11602 pd = &TREE_OPERAND (decl, 0);
11603 decl = TREE_OPERAND (decl, 0);
11605 /* An "attach/detach" operation on an update directive should
11606 behave as a GOMP_MAP_ALWAYS_POINTER. Beware that
11607 unlike attach or detach map kinds, GOMP_MAP_ALWAYS_POINTER
11608 depends on the previous mapping. */
11609 if (code == OACC_UPDATE
11610 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
11611 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_ALWAYS_POINTER);
11613 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
11615 if (TREE_CODE (TREE_TYPE (OMP_CLAUSE_DECL (c)))
11616 == ARRAY_TYPE)
11617 remove = true;
11618 else
11620 gomp_map_kind k = ((code == OACC_EXIT_DATA
11621 || code == OMP_TARGET_EXIT_DATA)
11622 ? GOMP_MAP_DETACH : GOMP_MAP_ATTACH);
11623 OMP_CLAUSE_SET_MAP_KIND (c, k);
11627 tree cref = decl;
11629 while (TREE_CODE (cref) == ARRAY_REF)
11630 cref = TREE_OPERAND (cref, 0);
11632 if (TREE_CODE (cref) == INDIRECT_REF)
11633 cref = TREE_OPERAND (cref, 0);
11635 if (TREE_CODE (cref) == COMPONENT_REF)
11637 tree base = cref;
11638 while (base && !DECL_P (base))
11640 tree innerbase = omp_get_base_pointer (base);
11641 if (!innerbase)
11642 break;
11643 base = innerbase;
11645 if (base
11646 && DECL_P (base)
11647 && GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c))
11648 && POINTER_TYPE_P (TREE_TYPE (base)))
11650 splay_tree_node n
11651 = splay_tree_lookup (ctx->variables,
11652 (splay_tree_key) base);
11653 n->value |= GOVD_SEEN;
11657 if (code == OMP_TARGET && OMP_CLAUSE_MAP_IN_REDUCTION (c))
11659 /* Don't gimplify *pd fully at this point, as the base
11660 will need to be adjusted during omp lowering. */
11661 auto_vec<tree, 10> expr_stack;
11662 tree *p = pd;
11663 while (handled_component_p (*p)
11664 || TREE_CODE (*p) == INDIRECT_REF
11665 || TREE_CODE (*p) == ADDR_EXPR
11666 || TREE_CODE (*p) == MEM_REF
11667 || TREE_CODE (*p) == NON_LVALUE_EXPR)
11669 expr_stack.safe_push (*p);
11670 p = &TREE_OPERAND (*p, 0);
11672 for (int i = expr_stack.length () - 1; i >= 0; i--)
11674 tree t = expr_stack[i];
11675 if (TREE_CODE (t) == ARRAY_REF
11676 || TREE_CODE (t) == ARRAY_RANGE_REF)
11678 if (TREE_OPERAND (t, 2) == NULL_TREE)
11680 tree low = unshare_expr (array_ref_low_bound (t));
11681 if (!is_gimple_min_invariant (low))
11683 TREE_OPERAND (t, 2) = low;
11684 if (gimplify_expr (&TREE_OPERAND (t, 2),
11685 pre_p, NULL,
11686 is_gimple_reg,
11687 fb_rvalue) == GS_ERROR)
11688 remove = true;
11691 else if (gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
11692 NULL, is_gimple_reg,
11693 fb_rvalue) == GS_ERROR)
11694 remove = true;
11695 if (TREE_OPERAND (t, 3) == NULL_TREE)
11697 tree elmt_size = array_ref_element_size (t);
11698 if (!is_gimple_min_invariant (elmt_size))
11700 elmt_size = unshare_expr (elmt_size);
11701 tree elmt_type
11702 = TREE_TYPE (TREE_TYPE (TREE_OPERAND (t,
11703 0)));
11704 tree factor
11705 = size_int (TYPE_ALIGN_UNIT (elmt_type));
11706 elmt_size
11707 = size_binop (EXACT_DIV_EXPR, elmt_size,
11708 factor);
11709 TREE_OPERAND (t, 3) = elmt_size;
11710 if (gimplify_expr (&TREE_OPERAND (t, 3),
11711 pre_p, NULL,
11712 is_gimple_reg,
11713 fb_rvalue) == GS_ERROR)
11714 remove = true;
11717 else if (gimplify_expr (&TREE_OPERAND (t, 3), pre_p,
11718 NULL, is_gimple_reg,
11719 fb_rvalue) == GS_ERROR)
11720 remove = true;
11722 else if (TREE_CODE (t) == COMPONENT_REF)
11724 if (TREE_OPERAND (t, 2) == NULL_TREE)
11726 tree offset = component_ref_field_offset (t);
11727 if (!is_gimple_min_invariant (offset))
11729 offset = unshare_expr (offset);
11730 tree field = TREE_OPERAND (t, 1);
11731 tree factor
11732 = size_int (DECL_OFFSET_ALIGN (field)
11733 / BITS_PER_UNIT);
11734 offset = size_binop (EXACT_DIV_EXPR, offset,
11735 factor);
11736 TREE_OPERAND (t, 2) = offset;
11737 if (gimplify_expr (&TREE_OPERAND (t, 2),
11738 pre_p, NULL,
11739 is_gimple_reg,
11740 fb_rvalue) == GS_ERROR)
11741 remove = true;
11744 else if (gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
11745 NULL, is_gimple_reg,
11746 fb_rvalue) == GS_ERROR)
11747 remove = true;
11750 for (; expr_stack.length () > 0; )
11752 tree t = expr_stack.pop ();
11754 if (TREE_CODE (t) == ARRAY_REF
11755 || TREE_CODE (t) == ARRAY_RANGE_REF)
11757 if (!is_gimple_min_invariant (TREE_OPERAND (t, 1))
11758 && gimplify_expr (&TREE_OPERAND (t, 1), pre_p,
11759 NULL, is_gimple_val,
11760 fb_rvalue) == GS_ERROR)
11761 remove = true;
11765 else if (gimplify_expr (pd, pre_p, NULL, is_gimple_lvalue,
11766 fb_lvalue) == GS_ERROR)
11768 remove = true;
11769 break;
11771 break;
11773 flags = GOVD_MAP | GOVD_EXPLICIT;
11774 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_TO
11775 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_TOFROM)
11776 flags |= GOVD_MAP_ALWAYS_TO;
11778 if ((code == OMP_TARGET
11779 || code == OMP_TARGET_DATA
11780 || code == OMP_TARGET_ENTER_DATA
11781 || code == OMP_TARGET_EXIT_DATA)
11782 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
11784 for (struct gimplify_omp_ctx *octx = outer_ctx; octx;
11785 octx = octx->outer_context)
11787 splay_tree_node n
11788 = splay_tree_lookup (octx->variables,
11789 (splay_tree_key) OMP_CLAUSE_DECL (c));
11790 /* If this is contained in an outer OpenMP region as a
11791 firstprivate value, remove the attach/detach. */
11792 if (n && (n->value & GOVD_FIRSTPRIVATE))
11794 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FIRSTPRIVATE_POINTER);
11795 goto do_add;
11799 enum gomp_map_kind map_kind = (code == OMP_TARGET_EXIT_DATA
11800 ? GOMP_MAP_DETACH
11801 : GOMP_MAP_ATTACH);
11802 OMP_CLAUSE_SET_MAP_KIND (c, map_kind);
11805 goto do_add;
11807 case OMP_CLAUSE_AFFINITY:
11808 gimplify_omp_affinity (list_p, pre_p);
11809 remove = true;
11810 break;
11811 case OMP_CLAUSE_DOACROSS:
11812 if (OMP_CLAUSE_DOACROSS_KIND (c) == OMP_CLAUSE_DOACROSS_SINK)
11814 tree deps = OMP_CLAUSE_DECL (c);
11815 while (deps && TREE_CODE (deps) == TREE_LIST)
11817 if (TREE_CODE (TREE_PURPOSE (deps)) == TRUNC_DIV_EXPR
11818 && DECL_P (TREE_OPERAND (TREE_PURPOSE (deps), 1)))
11819 gimplify_expr (&TREE_OPERAND (TREE_PURPOSE (deps), 1),
11820 pre_p, NULL, is_gimple_val, fb_rvalue);
11821 deps = TREE_CHAIN (deps);
11824 else
11825 gcc_assert (OMP_CLAUSE_DOACROSS_KIND (c)
11826 == OMP_CLAUSE_DOACROSS_SOURCE);
11827 break;
11828 case OMP_CLAUSE_DEPEND:
11829 if (handled_depend_iterators == -1)
11830 handled_depend_iterators = gimplify_omp_depend (list_p, pre_p);
11831 if (handled_depend_iterators)
11833 if (handled_depend_iterators == 2)
11834 remove = true;
11835 break;
11837 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
11839 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
11840 NULL, is_gimple_val, fb_rvalue);
11841 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
11843 if (error_operand_p (OMP_CLAUSE_DECL (c)))
11845 remove = true;
11846 break;
11848 if (OMP_CLAUSE_DECL (c) != null_pointer_node)
11850 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (OMP_CLAUSE_DECL (c));
11851 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
11852 is_gimple_val, fb_rvalue) == GS_ERROR)
11854 remove = true;
11855 break;
11858 if (code == OMP_TASK)
11859 ctx->has_depend = true;
11860 break;
11862 case OMP_CLAUSE_TO:
11863 case OMP_CLAUSE_FROM:
11864 case OMP_CLAUSE__CACHE_:
11865 decl = OMP_CLAUSE_DECL (c);
11866 if (error_operand_p (decl))
11868 remove = true;
11869 break;
11871 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
11872 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
11873 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
11874 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
11875 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
11877 remove = true;
11878 break;
11880 if (!DECL_P (decl))
11882 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p,
11883 NULL, is_gimple_lvalue, fb_lvalue)
11884 == GS_ERROR)
11886 remove = true;
11887 break;
11889 break;
11891 goto do_notice;
11893 case OMP_CLAUSE_USE_DEVICE_PTR:
11894 case OMP_CLAUSE_USE_DEVICE_ADDR:
11895 flags = GOVD_EXPLICIT;
11896 goto do_add;
11898 case OMP_CLAUSE_HAS_DEVICE_ADDR:
11899 decl = OMP_CLAUSE_DECL (c);
11900 while (TREE_CODE (decl) == INDIRECT_REF
11901 || TREE_CODE (decl) == ARRAY_REF)
11902 decl = TREE_OPERAND (decl, 0);
11903 flags = GOVD_EXPLICIT;
11904 goto do_add_decl;
11906 case OMP_CLAUSE_IS_DEVICE_PTR:
11907 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
11908 goto do_add;
11910 do_add:
11911 decl = OMP_CLAUSE_DECL (c);
11912 do_add_decl:
11913 if (error_operand_p (decl))
11915 remove = true;
11916 break;
11918 if (DECL_NAME (decl) == NULL_TREE && (flags & GOVD_SHARED) == 0)
11920 tree t = omp_member_access_dummy_var (decl);
11921 if (t)
11923 tree v = DECL_VALUE_EXPR (decl);
11924 DECL_NAME (decl) = DECL_NAME (TREE_OPERAND (v, 1));
11925 if (outer_ctx)
11926 omp_notice_variable (outer_ctx, t, true);
11929 if (code == OACC_DATA
11930 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP
11931 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
11932 flags |= GOVD_MAP_0LEN_ARRAY;
11933 omp_add_variable (ctx, decl, flags);
11934 if ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
11935 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_IN_REDUCTION
11936 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_TASK_REDUCTION)
11937 && OMP_CLAUSE_REDUCTION_PLACEHOLDER (c))
11939 struct gimplify_omp_ctx *pctx
11940 = code == OMP_TARGET ? outer_ctx : ctx;
11941 if (pctx)
11942 omp_add_variable (pctx, OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
11943 GOVD_LOCAL | GOVD_SEEN);
11944 if (pctx
11945 && OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c)
11946 && walk_tree (&OMP_CLAUSE_REDUCTION_INIT (c),
11947 find_decl_expr,
11948 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
11949 NULL) == NULL_TREE)
11950 omp_add_variable (pctx,
11951 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
11952 GOVD_LOCAL | GOVD_SEEN);
11953 gimplify_omp_ctxp = pctx;
11954 push_gimplify_context ();
11956 OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c) = NULL;
11957 OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c) = NULL;
11959 gimplify_and_add (OMP_CLAUSE_REDUCTION_INIT (c),
11960 &OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c));
11961 pop_gimplify_context
11962 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c)));
11963 push_gimplify_context ();
11964 gimplify_and_add (OMP_CLAUSE_REDUCTION_MERGE (c),
11965 &OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c));
11966 pop_gimplify_context
11967 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c)));
11968 OMP_CLAUSE_REDUCTION_INIT (c) = NULL_TREE;
11969 OMP_CLAUSE_REDUCTION_MERGE (c) = NULL_TREE;
11971 gimplify_omp_ctxp = outer_ctx;
11973 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
11974 && OMP_CLAUSE_LASTPRIVATE_STMT (c))
11976 gimplify_omp_ctxp = ctx;
11977 push_gimplify_context ();
11978 if (TREE_CODE (OMP_CLAUSE_LASTPRIVATE_STMT (c)) != BIND_EXPR)
11980 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
11981 NULL, NULL);
11982 TREE_SIDE_EFFECTS (bind) = 1;
11983 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LASTPRIVATE_STMT (c);
11984 OMP_CLAUSE_LASTPRIVATE_STMT (c) = bind;
11986 gimplify_and_add (OMP_CLAUSE_LASTPRIVATE_STMT (c),
11987 &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c));
11988 pop_gimplify_context
11989 (gimple_seq_first_stmt (OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c)));
11990 OMP_CLAUSE_LASTPRIVATE_STMT (c) = NULL_TREE;
11992 gimplify_omp_ctxp = outer_ctx;
11994 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
11995 && OMP_CLAUSE_LINEAR_STMT (c))
11997 gimplify_omp_ctxp = ctx;
11998 push_gimplify_context ();
11999 if (TREE_CODE (OMP_CLAUSE_LINEAR_STMT (c)) != BIND_EXPR)
12001 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
12002 NULL, NULL);
12003 TREE_SIDE_EFFECTS (bind) = 1;
12004 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LINEAR_STMT (c);
12005 OMP_CLAUSE_LINEAR_STMT (c) = bind;
12007 gimplify_and_add (OMP_CLAUSE_LINEAR_STMT (c),
12008 &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c));
12009 pop_gimplify_context
12010 (gimple_seq_first_stmt (OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c)));
12011 OMP_CLAUSE_LINEAR_STMT (c) = NULL_TREE;
12013 gimplify_omp_ctxp = outer_ctx;
12015 if (notice_outer)
12016 goto do_notice;
12017 break;
12019 case OMP_CLAUSE_COPYIN:
12020 case OMP_CLAUSE_COPYPRIVATE:
12021 decl = OMP_CLAUSE_DECL (c);
12022 if (error_operand_p (decl))
12024 remove = true;
12025 break;
12027 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_COPYPRIVATE
12028 && !remove
12029 && !omp_check_private (ctx, decl, true))
12031 remove = true;
12032 if (is_global_var (decl))
12034 if (DECL_THREAD_LOCAL_P (decl))
12035 remove = false;
12036 else if (DECL_HAS_VALUE_EXPR_P (decl))
12038 tree value = get_base_address (DECL_VALUE_EXPR (decl));
12040 if (value
12041 && DECL_P (value)
12042 && DECL_THREAD_LOCAL_P (value))
12043 remove = false;
12046 if (remove)
12047 error_at (OMP_CLAUSE_LOCATION (c),
12048 "copyprivate variable %qE is not threadprivate"
12049 " or private in outer context", DECL_NAME (decl));
12051 do_notice:
12052 if ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
12053 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_FIRSTPRIVATE
12054 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE)
12055 && outer_ctx
12056 && ((region_type & ORT_TASKLOOP) == ORT_TASKLOOP
12057 || (region_type == ORT_WORKSHARE
12058 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
12059 && (OMP_CLAUSE_REDUCTION_INSCAN (c)
12060 || code == OMP_LOOP)))
12061 && (outer_ctx->region_type == ORT_COMBINED_PARALLEL
12062 || (code == OMP_LOOP
12063 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
12064 && ((outer_ctx->region_type & ORT_COMBINED_TEAMS)
12065 == ORT_COMBINED_TEAMS))))
12067 splay_tree_node on
12068 = splay_tree_lookup (outer_ctx->variables,
12069 (splay_tree_key)decl);
12070 if (on == NULL || (on->value & GOVD_DATA_SHARE_CLASS) == 0)
12072 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
12073 && TREE_CODE (OMP_CLAUSE_DECL (c)) == MEM_REF
12074 && (TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE
12075 || (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
12076 && (TREE_CODE (TREE_TYPE (TREE_TYPE (decl)))
12077 == POINTER_TYPE))))
12078 omp_firstprivatize_variable (outer_ctx, decl);
12079 else
12081 omp_add_variable (outer_ctx, decl,
12082 GOVD_SEEN | GOVD_SHARED);
12083 if (outer_ctx->outer_context)
12084 omp_notice_variable (outer_ctx->outer_context, decl,
12085 true);
12089 if (outer_ctx)
12090 omp_notice_variable (outer_ctx, decl, true);
12091 if (check_non_private
12092 && (region_type == ORT_WORKSHARE || code == OMP_SCOPE)
12093 && (OMP_CLAUSE_CODE (c) != OMP_CLAUSE_REDUCTION
12094 || decl == OMP_CLAUSE_DECL (c)
12095 || (TREE_CODE (OMP_CLAUSE_DECL (c)) == MEM_REF
12096 && (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c), 0))
12097 == ADDR_EXPR
12098 || (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c), 0))
12099 == POINTER_PLUS_EXPR
12100 && (TREE_CODE (TREE_OPERAND (TREE_OPERAND
12101 (OMP_CLAUSE_DECL (c), 0), 0))
12102 == ADDR_EXPR)))))
12103 && omp_check_private (ctx, decl, false))
12105 error ("%s variable %qE is private in outer context",
12106 check_non_private, DECL_NAME (decl));
12107 remove = true;
12109 break;
12111 case OMP_CLAUSE_DETACH:
12112 flags = GOVD_FIRSTPRIVATE | GOVD_SEEN;
12113 goto do_add;
12115 case OMP_CLAUSE_IF:
12116 if (OMP_CLAUSE_IF_MODIFIER (c) != ERROR_MARK
12117 && OMP_CLAUSE_IF_MODIFIER (c) != code)
12119 const char *p[2];
12120 for (int i = 0; i < 2; i++)
12121 switch (i ? OMP_CLAUSE_IF_MODIFIER (c) : code)
12123 case VOID_CST: p[i] = "cancel"; break;
12124 case OMP_PARALLEL: p[i] = "parallel"; break;
12125 case OMP_SIMD: p[i] = "simd"; break;
12126 case OMP_TASK: p[i] = "task"; break;
12127 case OMP_TASKLOOP: p[i] = "taskloop"; break;
12128 case OMP_TARGET_DATA: p[i] = "target data"; break;
12129 case OMP_TARGET: p[i] = "target"; break;
12130 case OMP_TARGET_UPDATE: p[i] = "target update"; break;
12131 case OMP_TARGET_ENTER_DATA:
12132 p[i] = "target enter data"; break;
12133 case OMP_TARGET_EXIT_DATA: p[i] = "target exit data"; break;
12134 default: gcc_unreachable ();
12136 error_at (OMP_CLAUSE_LOCATION (c),
12137 "expected %qs %<if%> clause modifier rather than %qs",
12138 p[0], p[1]);
12139 remove = true;
12141 /* Fall through. */
12143 case OMP_CLAUSE_SELF:
12144 case OMP_CLAUSE_FINAL:
12145 OMP_CLAUSE_OPERAND (c, 0)
12146 = gimple_boolify (OMP_CLAUSE_OPERAND (c, 0));
12147 /* Fall through. */
12149 case OMP_CLAUSE_NUM_TEAMS:
12150 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_NUM_TEAMS
12151 && OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c)
12152 && !is_gimple_min_invariant (OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c)))
12154 if (error_operand_p (OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c)))
12156 remove = true;
12157 break;
12159 OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c)
12160 = get_initialized_tmp_var (OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c),
12161 pre_p, NULL, true);
12163 /* Fall through. */
12165 case OMP_CLAUSE_SCHEDULE:
12166 case OMP_CLAUSE_NUM_THREADS:
12167 case OMP_CLAUSE_THREAD_LIMIT:
12168 case OMP_CLAUSE_DIST_SCHEDULE:
12169 case OMP_CLAUSE_DEVICE:
12170 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEVICE
12171 && OMP_CLAUSE_DEVICE_ANCESTOR (c))
12173 if (code != OMP_TARGET)
12175 error_at (OMP_CLAUSE_LOCATION (c),
12176 "%<device%> clause with %<ancestor%> is only "
12177 "allowed on %<target%> construct");
12178 remove = true;
12179 break;
12182 tree clauses = *orig_list_p;
12183 for (; clauses ; clauses = OMP_CLAUSE_CHAIN (clauses))
12184 if (OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_DEVICE
12185 && OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_FIRSTPRIVATE
12186 && OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_PRIVATE
12187 && OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_DEFAULTMAP
12188 && OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_MAP
12191 error_at (OMP_CLAUSE_LOCATION (c),
12192 "with %<ancestor%>, only the %<device%>, "
12193 "%<firstprivate%>, %<private%>, %<defaultmap%>, "
12194 "and %<map%> clauses may appear on the "
12195 "construct");
12196 remove = true;
12197 break;
12200 /* Fall through. */
12202 case OMP_CLAUSE_PRIORITY:
12203 case OMP_CLAUSE_GRAINSIZE:
12204 case OMP_CLAUSE_NUM_TASKS:
12205 case OMP_CLAUSE_FILTER:
12206 case OMP_CLAUSE_HINT:
12207 case OMP_CLAUSE_ASYNC:
12208 case OMP_CLAUSE_WAIT:
12209 case OMP_CLAUSE_NUM_GANGS:
12210 case OMP_CLAUSE_NUM_WORKERS:
12211 case OMP_CLAUSE_VECTOR_LENGTH:
12212 case OMP_CLAUSE_WORKER:
12213 case OMP_CLAUSE_VECTOR:
12214 if (OMP_CLAUSE_OPERAND (c, 0)
12215 && !is_gimple_min_invariant (OMP_CLAUSE_OPERAND (c, 0)))
12217 if (error_operand_p (OMP_CLAUSE_OPERAND (c, 0)))
12219 remove = true;
12220 break;
12222 /* All these clauses care about value, not a particular decl,
12223 so try to force it into a SSA_NAME or fresh temporary. */
12224 OMP_CLAUSE_OPERAND (c, 0)
12225 = get_initialized_tmp_var (OMP_CLAUSE_OPERAND (c, 0),
12226 pre_p, NULL, true);
12228 break;
12230 case OMP_CLAUSE_GANG:
12231 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 0), pre_p, NULL,
12232 is_gimple_val, fb_rvalue) == GS_ERROR)
12233 remove = true;
12234 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 1), pre_p, NULL,
12235 is_gimple_val, fb_rvalue) == GS_ERROR)
12236 remove = true;
12237 break;
12239 case OMP_CLAUSE_NOWAIT:
12240 nowait = 1;
12241 break;
12243 case OMP_CLAUSE_ORDERED:
12244 case OMP_CLAUSE_UNTIED:
12245 case OMP_CLAUSE_COLLAPSE:
12246 case OMP_CLAUSE_TILE:
12247 case OMP_CLAUSE_AUTO:
12248 case OMP_CLAUSE_SEQ:
12249 case OMP_CLAUSE_INDEPENDENT:
12250 case OMP_CLAUSE_MERGEABLE:
12251 case OMP_CLAUSE_PROC_BIND:
12252 case OMP_CLAUSE_SAFELEN:
12253 case OMP_CLAUSE_SIMDLEN:
12254 case OMP_CLAUSE_NOGROUP:
12255 case OMP_CLAUSE_THREADS:
12256 case OMP_CLAUSE_SIMD:
12257 case OMP_CLAUSE_BIND:
12258 case OMP_CLAUSE_IF_PRESENT:
12259 case OMP_CLAUSE_FINALIZE:
12260 break;
12262 case OMP_CLAUSE_ORDER:
12263 ctx->order_concurrent = true;
12264 break;
12266 case OMP_CLAUSE_DEFAULTMAP:
12267 enum gimplify_defaultmap_kind gdmkmin, gdmkmax;
12268 switch (OMP_CLAUSE_DEFAULTMAP_CATEGORY (c))
12270 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_UNSPECIFIED:
12271 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_ALL:
12272 gdmkmin = GDMK_SCALAR;
12273 gdmkmax = GDMK_POINTER;
12274 break;
12275 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_SCALAR:
12276 gdmkmin = GDMK_SCALAR;
12277 gdmkmax = GDMK_SCALAR_TARGET;
12278 break;
12279 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_AGGREGATE:
12280 gdmkmin = gdmkmax = GDMK_AGGREGATE;
12281 break;
12282 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_ALLOCATABLE:
12283 gdmkmin = gdmkmax = GDMK_ALLOCATABLE;
12284 break;
12285 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_POINTER:
12286 gdmkmin = gdmkmax = GDMK_POINTER;
12287 break;
12288 default:
12289 gcc_unreachable ();
12291 for (int gdmk = gdmkmin; gdmk <= gdmkmax; gdmk++)
12292 switch (OMP_CLAUSE_DEFAULTMAP_BEHAVIOR (c))
12294 case OMP_CLAUSE_DEFAULTMAP_ALLOC:
12295 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_ALLOC_ONLY;
12296 break;
12297 case OMP_CLAUSE_DEFAULTMAP_TO:
12298 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_TO_ONLY;
12299 break;
12300 case OMP_CLAUSE_DEFAULTMAP_FROM:
12301 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_FROM_ONLY;
12302 break;
12303 case OMP_CLAUSE_DEFAULTMAP_TOFROM:
12304 ctx->defaultmap[gdmk] = GOVD_MAP;
12305 break;
12306 case OMP_CLAUSE_DEFAULTMAP_FIRSTPRIVATE:
12307 ctx->defaultmap[gdmk] = GOVD_FIRSTPRIVATE;
12308 break;
12309 case OMP_CLAUSE_DEFAULTMAP_NONE:
12310 ctx->defaultmap[gdmk] = 0;
12311 break;
12312 case OMP_CLAUSE_DEFAULTMAP_PRESENT:
12313 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_FORCE_PRESENT;
12314 break;
12315 case OMP_CLAUSE_DEFAULTMAP_DEFAULT:
12316 switch (gdmk)
12318 case GDMK_SCALAR:
12319 ctx->defaultmap[gdmk] = GOVD_FIRSTPRIVATE;
12320 break;
12321 case GDMK_SCALAR_TARGET:
12322 ctx->defaultmap[gdmk] = (lang_GNU_Fortran ()
12323 ? GOVD_MAP : GOVD_FIRSTPRIVATE);
12324 break;
12325 case GDMK_AGGREGATE:
12326 case GDMK_ALLOCATABLE:
12327 ctx->defaultmap[gdmk] = GOVD_MAP;
12328 break;
12329 case GDMK_POINTER:
12330 ctx->defaultmap[gdmk] = GOVD_MAP;
12331 if (!lang_GNU_Fortran ())
12332 ctx->defaultmap[gdmk] |= GOVD_MAP_0LEN_ARRAY;
12333 break;
12334 default:
12335 gcc_unreachable ();
12337 break;
12338 default:
12339 gcc_unreachable ();
12341 break;
12343 case OMP_CLAUSE_ALIGNED:
12344 decl = OMP_CLAUSE_DECL (c);
12345 if (error_operand_p (decl))
12347 remove = true;
12348 break;
12350 if (gimplify_expr (&OMP_CLAUSE_ALIGNED_ALIGNMENT (c), pre_p, NULL,
12351 is_gimple_val, fb_rvalue) == GS_ERROR)
12353 remove = true;
12354 break;
12356 if (!is_global_var (decl)
12357 && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
12358 omp_add_variable (ctx, decl, GOVD_ALIGNED);
12359 break;
12361 case OMP_CLAUSE_NONTEMPORAL:
12362 decl = OMP_CLAUSE_DECL (c);
12363 if (error_operand_p (decl))
12365 remove = true;
12366 break;
12368 omp_add_variable (ctx, decl, GOVD_NONTEMPORAL);
12369 break;
12371 case OMP_CLAUSE_ALLOCATE:
12372 decl = OMP_CLAUSE_DECL (c);
12373 if (error_operand_p (decl))
12375 remove = true;
12376 break;
12378 if (gimplify_expr (&OMP_CLAUSE_ALLOCATE_ALLOCATOR (c), pre_p, NULL,
12379 is_gimple_val, fb_rvalue) == GS_ERROR)
12381 remove = true;
12382 break;
12384 else if (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c) == NULL_TREE
12385 || (TREE_CODE (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c))
12386 == INTEGER_CST))
12388 else if (code == OMP_TASKLOOP
12389 || !DECL_P (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)))
12390 OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
12391 = get_initialized_tmp_var (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
12392 pre_p, NULL, false);
12393 break;
12395 case OMP_CLAUSE_DEFAULT:
12396 ctx->default_kind = OMP_CLAUSE_DEFAULT_KIND (c);
12397 break;
12399 case OMP_CLAUSE_INCLUSIVE:
12400 case OMP_CLAUSE_EXCLUSIVE:
12401 decl = OMP_CLAUSE_DECL (c);
12403 splay_tree_node n = splay_tree_lookup (outer_ctx->variables,
12404 (splay_tree_key) decl);
12405 if (n == NULL || (n->value & GOVD_REDUCTION) == 0)
12407 error_at (OMP_CLAUSE_LOCATION (c),
12408 "%qD specified in %qs clause but not in %<inscan%> "
12409 "%<reduction%> clause on the containing construct",
12410 decl, omp_clause_code_name[OMP_CLAUSE_CODE (c)]);
12411 remove = true;
12413 else
12415 n->value |= GOVD_REDUCTION_INSCAN;
12416 if (outer_ctx->region_type == ORT_SIMD
12417 && outer_ctx->outer_context
12418 && outer_ctx->outer_context->region_type == ORT_WORKSHARE)
12420 n = splay_tree_lookup (outer_ctx->outer_context->variables,
12421 (splay_tree_key) decl);
12422 if (n && (n->value & GOVD_REDUCTION) != 0)
12423 n->value |= GOVD_REDUCTION_INSCAN;
12427 break;
12429 case OMP_CLAUSE_NOHOST:
12430 default:
12431 gcc_unreachable ();
12434 if (code == OACC_DATA
12435 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP
12436 && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
12437 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
12438 remove = true;
12439 if (remove)
12440 *list_p = OMP_CLAUSE_CHAIN (c);
12441 else
12442 list_p = &OMP_CLAUSE_CHAIN (c);
12445 ctx->clauses = *orig_list_p;
12446 gimplify_omp_ctxp = ctx;
12449 /* Return true if DECL is a candidate for shared to firstprivate
12450 optimization. We only consider non-addressable scalars, not
12451 too big, and not references. */
12453 static bool
12454 omp_shared_to_firstprivate_optimizable_decl_p (tree decl)
12456 if (TREE_ADDRESSABLE (decl))
12457 return false;
12458 tree type = TREE_TYPE (decl);
12459 if (!is_gimple_reg_type (type)
12460 || TREE_CODE (type) == REFERENCE_TYPE
12461 || TREE_ADDRESSABLE (type))
12462 return false;
12463 /* Don't optimize too large decls, as each thread/task will have
12464 its own. */
12465 HOST_WIDE_INT len = int_size_in_bytes (type);
12466 if (len == -1 || len > 4 * POINTER_SIZE / BITS_PER_UNIT)
12467 return false;
12468 if (omp_privatize_by_reference (decl))
12469 return false;
12470 return true;
12473 /* Helper function of omp_find_stores_op and gimplify_adjust_omp_clauses*.
12474 For omp_shared_to_firstprivate_optimizable_decl_p decl mark it as
12475 GOVD_WRITTEN in outer contexts. */
12477 static void
12478 omp_mark_stores (struct gimplify_omp_ctx *ctx, tree decl)
12480 for (; ctx; ctx = ctx->outer_context)
12482 splay_tree_node n = splay_tree_lookup (ctx->variables,
12483 (splay_tree_key) decl);
12484 if (n == NULL)
12485 continue;
12486 else if (n->value & GOVD_SHARED)
12488 n->value |= GOVD_WRITTEN;
12489 return;
12491 else if (n->value & GOVD_DATA_SHARE_CLASS)
12492 return;
12496 /* Helper callback for walk_gimple_seq to discover possible stores
12497 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
12498 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
12499 for those. */
12501 static tree
12502 omp_find_stores_op (tree *tp, int *walk_subtrees, void *data)
12504 struct walk_stmt_info *wi = (struct walk_stmt_info *) data;
12506 *walk_subtrees = 0;
12507 if (!wi->is_lhs)
12508 return NULL_TREE;
12510 tree op = *tp;
12513 if (handled_component_p (op))
12514 op = TREE_OPERAND (op, 0);
12515 else if ((TREE_CODE (op) == MEM_REF || TREE_CODE (op) == TARGET_MEM_REF)
12516 && TREE_CODE (TREE_OPERAND (op, 0)) == ADDR_EXPR)
12517 op = TREE_OPERAND (TREE_OPERAND (op, 0), 0);
12518 else
12519 break;
12521 while (1);
12522 if (!DECL_P (op) || !omp_shared_to_firstprivate_optimizable_decl_p (op))
12523 return NULL_TREE;
12525 omp_mark_stores (gimplify_omp_ctxp, op);
12526 return NULL_TREE;
12529 /* Helper callback for walk_gimple_seq to discover possible stores
12530 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
12531 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
12532 for those. */
12534 static tree
12535 omp_find_stores_stmt (gimple_stmt_iterator *gsi_p,
12536 bool *handled_ops_p,
12537 struct walk_stmt_info *wi)
12539 gimple *stmt = gsi_stmt (*gsi_p);
12540 switch (gimple_code (stmt))
12542 /* Don't recurse on OpenMP constructs for which
12543 gimplify_adjust_omp_clauses already handled the bodies,
12544 except handle gimple_omp_for_pre_body. */
12545 case GIMPLE_OMP_FOR:
12546 *handled_ops_p = true;
12547 if (gimple_omp_for_pre_body (stmt))
12548 walk_gimple_seq (gimple_omp_for_pre_body (stmt),
12549 omp_find_stores_stmt, omp_find_stores_op, wi);
12550 break;
12551 case GIMPLE_OMP_PARALLEL:
12552 case GIMPLE_OMP_TASK:
12553 case GIMPLE_OMP_SECTIONS:
12554 case GIMPLE_OMP_SINGLE:
12555 case GIMPLE_OMP_SCOPE:
12556 case GIMPLE_OMP_TARGET:
12557 case GIMPLE_OMP_TEAMS:
12558 case GIMPLE_OMP_CRITICAL:
12559 *handled_ops_p = true;
12560 break;
12561 default:
12562 break;
12564 return NULL_TREE;
12567 struct gimplify_adjust_omp_clauses_data
12569 tree *list_p;
12570 gimple_seq *pre_p;
12573 /* For all variables that were not actually used within the context,
12574 remove PRIVATE, SHARED, and FIRSTPRIVATE clauses. */
12576 static int
12577 gimplify_adjust_omp_clauses_1 (splay_tree_node n, void *data)
12579 tree *list_p = ((struct gimplify_adjust_omp_clauses_data *) data)->list_p;
12580 gimple_seq *pre_p
12581 = ((struct gimplify_adjust_omp_clauses_data *) data)->pre_p;
12582 tree decl = (tree) n->key;
12583 unsigned flags = n->value;
12584 enum omp_clause_code code;
12585 tree clause;
12586 bool private_debug;
12588 if (gimplify_omp_ctxp->region_type == ORT_COMBINED_PARALLEL
12589 && (flags & GOVD_LASTPRIVATE_CONDITIONAL) != 0)
12590 flags = GOVD_SHARED | GOVD_SEEN | GOVD_WRITTEN;
12591 if (flags & (GOVD_EXPLICIT | GOVD_LOCAL))
12592 return 0;
12593 if ((flags & GOVD_SEEN) == 0)
12594 return 0;
12595 if (flags & GOVD_DEBUG_PRIVATE)
12597 gcc_assert ((flags & GOVD_DATA_SHARE_CLASS) == GOVD_SHARED);
12598 private_debug = true;
12600 else if (flags & GOVD_MAP)
12601 private_debug = false;
12602 else
12603 private_debug
12604 = lang_hooks.decls.omp_private_debug_clause (decl,
12605 !!(flags & GOVD_SHARED));
12606 if (private_debug)
12607 code = OMP_CLAUSE_PRIVATE;
12608 else if (flags & GOVD_MAP)
12610 code = OMP_CLAUSE_MAP;
12611 if ((gimplify_omp_ctxp->region_type & ORT_ACC) == 0
12612 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl))))
12614 error ("%<_Atomic%> %qD in implicit %<map%> clause", decl);
12615 return 0;
12617 if (VAR_P (decl)
12618 && DECL_IN_CONSTANT_POOL (decl)
12619 && !lookup_attribute ("omp declare target",
12620 DECL_ATTRIBUTES (decl)))
12622 tree id = get_identifier ("omp declare target");
12623 DECL_ATTRIBUTES (decl)
12624 = tree_cons (id, NULL_TREE, DECL_ATTRIBUTES (decl));
12625 varpool_node *node = varpool_node::get (decl);
12626 if (node)
12628 node->offloadable = 1;
12629 if (ENABLE_OFFLOADING)
12630 g->have_offload = true;
12634 else if (flags & GOVD_SHARED)
12636 if (is_global_var (decl))
12638 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
12639 while (ctx != NULL)
12641 splay_tree_node on
12642 = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
12643 if (on && (on->value & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
12644 | GOVD_PRIVATE | GOVD_REDUCTION
12645 | GOVD_LINEAR | GOVD_MAP)) != 0)
12646 break;
12647 ctx = ctx->outer_context;
12649 if (ctx == NULL)
12650 return 0;
12652 code = OMP_CLAUSE_SHARED;
12653 /* Don't optimize shared into firstprivate for read-only vars
12654 on tasks with depend clause, we shouldn't try to copy them
12655 until the dependencies are satisfied. */
12656 if (gimplify_omp_ctxp->has_depend)
12657 flags |= GOVD_WRITTEN;
12659 else if (flags & GOVD_PRIVATE)
12660 code = OMP_CLAUSE_PRIVATE;
12661 else if (flags & GOVD_FIRSTPRIVATE)
12663 code = OMP_CLAUSE_FIRSTPRIVATE;
12664 if ((gimplify_omp_ctxp->region_type & ORT_TARGET)
12665 && (gimplify_omp_ctxp->region_type & ORT_ACC) == 0
12666 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl))))
12668 error ("%<_Atomic%> %qD in implicit %<firstprivate%> clause on "
12669 "%<target%> construct", decl);
12670 return 0;
12673 else if (flags & GOVD_LASTPRIVATE)
12674 code = OMP_CLAUSE_LASTPRIVATE;
12675 else if (flags & (GOVD_ALIGNED | GOVD_NONTEMPORAL))
12676 return 0;
12677 else if (flags & GOVD_CONDTEMP)
12679 code = OMP_CLAUSE__CONDTEMP_;
12680 gimple_add_tmp_var (decl);
12682 else
12683 gcc_unreachable ();
12685 if (((flags & GOVD_LASTPRIVATE)
12686 || (code == OMP_CLAUSE_SHARED && (flags & GOVD_WRITTEN)))
12687 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
12688 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
12690 tree chain = *list_p;
12691 clause = build_omp_clause (input_location, code);
12692 OMP_CLAUSE_DECL (clause) = decl;
12693 OMP_CLAUSE_CHAIN (clause) = chain;
12694 if (private_debug)
12695 OMP_CLAUSE_PRIVATE_DEBUG (clause) = 1;
12696 else if (code == OMP_CLAUSE_PRIVATE && (flags & GOVD_PRIVATE_OUTER_REF))
12697 OMP_CLAUSE_PRIVATE_OUTER_REF (clause) = 1;
12698 else if (code == OMP_CLAUSE_SHARED
12699 && (flags & GOVD_WRITTEN) == 0
12700 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
12701 OMP_CLAUSE_SHARED_READONLY (clause) = 1;
12702 else if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_EXPLICIT) == 0)
12703 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (clause) = 1;
12704 else if (code == OMP_CLAUSE_MAP && (flags & GOVD_MAP_0LEN_ARRAY) != 0)
12706 tree nc = build_omp_clause (input_location, OMP_CLAUSE_MAP);
12707 OMP_CLAUSE_DECL (nc) = decl;
12708 if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
12709 && TREE_CODE (TREE_TYPE (TREE_TYPE (decl))) == POINTER_TYPE)
12710 OMP_CLAUSE_DECL (clause)
12711 = build_simple_mem_ref_loc (input_location, decl);
12712 OMP_CLAUSE_DECL (clause)
12713 = build2 (MEM_REF, char_type_node, OMP_CLAUSE_DECL (clause),
12714 build_int_cst (build_pointer_type (char_type_node), 0));
12715 OMP_CLAUSE_SIZE (clause) = size_zero_node;
12716 OMP_CLAUSE_SIZE (nc) = size_zero_node;
12717 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_ALLOC);
12718 OMP_CLAUSE_MAP_MAYBE_ZERO_LENGTH_ARRAY_SECTION (clause) = 1;
12719 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_POINTER);
12720 OMP_CLAUSE_CHAIN (nc) = chain;
12721 OMP_CLAUSE_CHAIN (clause) = nc;
12722 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
12723 gimplify_omp_ctxp = ctx->outer_context;
12724 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (clause), 0),
12725 pre_p, NULL, is_gimple_val, fb_rvalue);
12726 gimplify_omp_ctxp = ctx;
12728 else if (code == OMP_CLAUSE_MAP)
12730 int kind;
12731 /* Not all combinations of these GOVD_MAP flags are actually valid. */
12732 switch (flags & (GOVD_MAP_TO_ONLY
12733 | GOVD_MAP_FORCE
12734 | GOVD_MAP_FORCE_PRESENT
12735 | GOVD_MAP_ALLOC_ONLY
12736 | GOVD_MAP_FROM_ONLY))
12738 case 0:
12739 kind = GOMP_MAP_TOFROM;
12740 break;
12741 case GOVD_MAP_FORCE:
12742 kind = GOMP_MAP_TOFROM | GOMP_MAP_FLAG_FORCE;
12743 break;
12744 case GOVD_MAP_TO_ONLY:
12745 kind = GOMP_MAP_TO;
12746 break;
12747 case GOVD_MAP_FROM_ONLY:
12748 kind = GOMP_MAP_FROM;
12749 break;
12750 case GOVD_MAP_ALLOC_ONLY:
12751 kind = GOMP_MAP_ALLOC;
12752 break;
12753 case GOVD_MAP_TO_ONLY | GOVD_MAP_FORCE:
12754 kind = GOMP_MAP_TO | GOMP_MAP_FLAG_FORCE;
12755 break;
12756 case GOVD_MAP_FORCE_PRESENT:
12757 kind = GOMP_MAP_FORCE_PRESENT;
12758 break;
12759 case GOVD_MAP_FORCE_PRESENT | GOVD_MAP_ALLOC_ONLY:
12760 kind = GOMP_MAP_FORCE_PRESENT;
12761 break;
12762 default:
12763 gcc_unreachable ();
12765 OMP_CLAUSE_SET_MAP_KIND (clause, kind);
12766 /* Setting of the implicit flag for the runtime is currently disabled for
12767 OpenACC. */
12768 if ((gimplify_omp_ctxp->region_type & ORT_ACC) == 0)
12769 OMP_CLAUSE_MAP_RUNTIME_IMPLICIT_P (clause) = 1;
12770 if (DECL_SIZE (decl)
12771 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
12773 tree decl2 = DECL_VALUE_EXPR (decl);
12774 gcc_assert (INDIRECT_REF_P (decl2));
12775 decl2 = TREE_OPERAND (decl2, 0);
12776 gcc_assert (DECL_P (decl2));
12777 tree mem = build_simple_mem_ref (decl2);
12778 OMP_CLAUSE_DECL (clause) = mem;
12779 OMP_CLAUSE_SIZE (clause) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
12780 if (gimplify_omp_ctxp->outer_context)
12782 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
12783 omp_notice_variable (ctx, decl2, true);
12784 omp_notice_variable (ctx, OMP_CLAUSE_SIZE (clause), true);
12786 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
12787 OMP_CLAUSE_MAP);
12788 OMP_CLAUSE_DECL (nc) = decl;
12789 OMP_CLAUSE_SIZE (nc) = size_zero_node;
12790 if (gimplify_omp_ctxp->target_firstprivatize_array_bases)
12791 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_POINTER);
12792 else
12793 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
12794 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
12795 OMP_CLAUSE_CHAIN (clause) = nc;
12797 else if (gimplify_omp_ctxp->target_firstprivatize_array_bases
12798 && omp_privatize_by_reference (decl))
12800 OMP_CLAUSE_DECL (clause) = build_simple_mem_ref (decl);
12801 OMP_CLAUSE_SIZE (clause)
12802 = unshare_expr (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl))));
12803 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
12804 gimplify_omp_ctxp = ctx->outer_context;
12805 gimplify_expr (&OMP_CLAUSE_SIZE (clause),
12806 pre_p, NULL, is_gimple_val, fb_rvalue);
12807 gimplify_omp_ctxp = ctx;
12808 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
12809 OMP_CLAUSE_MAP);
12810 OMP_CLAUSE_DECL (nc) = decl;
12811 OMP_CLAUSE_SIZE (nc) = size_zero_node;
12812 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_REFERENCE);
12813 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
12814 OMP_CLAUSE_CHAIN (clause) = nc;
12816 else
12817 OMP_CLAUSE_SIZE (clause) = DECL_SIZE_UNIT (decl);
12819 if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_LASTPRIVATE) != 0)
12821 tree nc = build_omp_clause (input_location, OMP_CLAUSE_LASTPRIVATE);
12822 OMP_CLAUSE_DECL (nc) = decl;
12823 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (nc) = 1;
12824 OMP_CLAUSE_CHAIN (nc) = chain;
12825 OMP_CLAUSE_CHAIN (clause) = nc;
12826 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
12827 gimplify_omp_ctxp = ctx->outer_context;
12828 lang_hooks.decls.omp_finish_clause (nc, pre_p,
12829 (ctx->region_type & ORT_ACC) != 0);
12830 gimplify_omp_ctxp = ctx;
12832 *list_p = clause;
12833 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
12834 gimplify_omp_ctxp = ctx->outer_context;
12835 /* Don't call omp_finish_clause on implicitly added OMP_CLAUSE_PRIVATE
12836 in simd. Those are only added for the local vars inside of simd body
12837 and they don't need to be e.g. default constructible. */
12838 if (code != OMP_CLAUSE_PRIVATE || ctx->region_type != ORT_SIMD)
12839 lang_hooks.decls.omp_finish_clause (clause, pre_p,
12840 (ctx->region_type & ORT_ACC) != 0);
12841 if (gimplify_omp_ctxp)
12842 for (; clause != chain; clause = OMP_CLAUSE_CHAIN (clause))
12843 if (OMP_CLAUSE_CODE (clause) == OMP_CLAUSE_MAP
12844 && DECL_P (OMP_CLAUSE_SIZE (clause)))
12845 omp_notice_variable (gimplify_omp_ctxp, OMP_CLAUSE_SIZE (clause),
12846 true);
12847 gimplify_omp_ctxp = ctx;
12848 return 0;
12851 static void
12852 gimplify_adjust_omp_clauses (gimple_seq *pre_p, gimple_seq body, tree *list_p,
12853 enum tree_code code)
12855 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
12856 tree *orig_list_p = list_p;
12857 tree c, decl;
12858 bool has_inscan_reductions = false;
12860 if (body)
12862 struct gimplify_omp_ctx *octx;
12863 for (octx = ctx; octx; octx = octx->outer_context)
12864 if ((octx->region_type & (ORT_PARALLEL | ORT_TASK | ORT_TEAMS)) != 0)
12865 break;
12866 if (octx)
12868 struct walk_stmt_info wi;
12869 memset (&wi, 0, sizeof (wi));
12870 walk_gimple_seq (body, omp_find_stores_stmt,
12871 omp_find_stores_op, &wi);
12875 if (ctx->add_safelen1)
12877 /* If there are VLAs in the body of simd loop, prevent
12878 vectorization. */
12879 gcc_assert (ctx->region_type == ORT_SIMD);
12880 c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_SAFELEN);
12881 OMP_CLAUSE_SAFELEN_EXPR (c) = integer_one_node;
12882 OMP_CLAUSE_CHAIN (c) = *list_p;
12883 *list_p = c;
12884 list_p = &OMP_CLAUSE_CHAIN (c);
12887 if (ctx->region_type == ORT_WORKSHARE
12888 && ctx->outer_context
12889 && ctx->outer_context->region_type == ORT_COMBINED_PARALLEL)
12891 for (c = ctx->outer_context->clauses; c; c = OMP_CLAUSE_CHAIN (c))
12892 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
12893 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
12895 decl = OMP_CLAUSE_DECL (c);
12896 splay_tree_node n
12897 = splay_tree_lookup (ctx->outer_context->variables,
12898 (splay_tree_key) decl);
12899 gcc_checking_assert (!splay_tree_lookup (ctx->variables,
12900 (splay_tree_key) decl));
12901 omp_add_variable (ctx, decl, n->value);
12902 tree c2 = copy_node (c);
12903 OMP_CLAUSE_CHAIN (c2) = *list_p;
12904 *list_p = c2;
12905 if ((n->value & GOVD_FIRSTPRIVATE) == 0)
12906 continue;
12907 c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
12908 OMP_CLAUSE_FIRSTPRIVATE);
12909 OMP_CLAUSE_DECL (c2) = decl;
12910 OMP_CLAUSE_CHAIN (c2) = *list_p;
12911 *list_p = c2;
12915 tree attach_list = NULL_TREE;
12916 tree *attach_tail = &attach_list;
12918 while ((c = *list_p) != NULL)
12920 splay_tree_node n;
12921 bool remove = false;
12922 bool move_attach = false;
12924 switch (OMP_CLAUSE_CODE (c))
12926 case OMP_CLAUSE_FIRSTPRIVATE:
12927 if ((ctx->region_type & ORT_TARGET)
12928 && (ctx->region_type & ORT_ACC) == 0
12929 && TYPE_ATOMIC (strip_array_types
12930 (TREE_TYPE (OMP_CLAUSE_DECL (c)))))
12932 error_at (OMP_CLAUSE_LOCATION (c),
12933 "%<_Atomic%> %qD in %<firstprivate%> clause on "
12934 "%<target%> construct", OMP_CLAUSE_DECL (c));
12935 remove = true;
12936 break;
12938 if (OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (c))
12940 decl = OMP_CLAUSE_DECL (c);
12941 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
12942 if ((n->value & GOVD_MAP) != 0)
12944 remove = true;
12945 break;
12947 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT_TARGET (c) = 0;
12948 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (c) = 0;
12950 /* FALLTHRU */
12951 case OMP_CLAUSE_PRIVATE:
12952 case OMP_CLAUSE_SHARED:
12953 case OMP_CLAUSE_LINEAR:
12954 decl = OMP_CLAUSE_DECL (c);
12955 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
12956 remove = !(n->value & GOVD_SEEN);
12957 if ((n->value & GOVD_LASTPRIVATE_CONDITIONAL) != 0
12958 && code == OMP_PARALLEL
12959 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_FIRSTPRIVATE)
12960 remove = true;
12961 if (! remove)
12963 bool shared = OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED;
12964 if ((n->value & GOVD_DEBUG_PRIVATE)
12965 || lang_hooks.decls.omp_private_debug_clause (decl, shared))
12967 gcc_assert ((n->value & GOVD_DEBUG_PRIVATE) == 0
12968 || ((n->value & GOVD_DATA_SHARE_CLASS)
12969 == GOVD_SHARED));
12970 OMP_CLAUSE_SET_CODE (c, OMP_CLAUSE_PRIVATE);
12971 OMP_CLAUSE_PRIVATE_DEBUG (c) = 1;
12973 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
12974 && ctx->has_depend
12975 && DECL_P (decl))
12976 n->value |= GOVD_WRITTEN;
12977 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
12978 && (n->value & GOVD_WRITTEN) == 0
12979 && DECL_P (decl)
12980 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
12981 OMP_CLAUSE_SHARED_READONLY (c) = 1;
12982 else if (DECL_P (decl)
12983 && ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
12984 && (n->value & GOVD_WRITTEN) != 0)
12985 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
12986 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
12987 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
12988 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
12990 else
12991 n->value &= ~GOVD_EXPLICIT;
12992 break;
12994 case OMP_CLAUSE_LASTPRIVATE:
12995 /* Make sure OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE is set to
12996 accurately reflect the presence of a FIRSTPRIVATE clause. */
12997 decl = OMP_CLAUSE_DECL (c);
12998 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
12999 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c)
13000 = (n->value & GOVD_FIRSTPRIVATE) != 0;
13001 if (code == OMP_DISTRIBUTE
13002 && OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
13004 remove = true;
13005 error_at (OMP_CLAUSE_LOCATION (c),
13006 "same variable used in %<firstprivate%> and "
13007 "%<lastprivate%> clauses on %<distribute%> "
13008 "construct");
13010 if (!remove
13011 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
13012 && DECL_P (decl)
13013 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
13014 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
13015 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) && code == OMP_PARALLEL)
13016 remove = true;
13017 break;
13019 case OMP_CLAUSE_ALIGNED:
13020 decl = OMP_CLAUSE_DECL (c);
13021 if (!is_global_var (decl))
13023 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
13024 remove = n == NULL || !(n->value & GOVD_SEEN);
13025 if (!remove && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
13027 struct gimplify_omp_ctx *octx;
13028 if (n != NULL
13029 && (n->value & (GOVD_DATA_SHARE_CLASS
13030 & ~GOVD_FIRSTPRIVATE)))
13031 remove = true;
13032 else
13033 for (octx = ctx->outer_context; octx;
13034 octx = octx->outer_context)
13036 n = splay_tree_lookup (octx->variables,
13037 (splay_tree_key) decl);
13038 if (n == NULL)
13039 continue;
13040 if (n->value & GOVD_LOCAL)
13041 break;
13042 /* We have to avoid assigning a shared variable
13043 to itself when trying to add
13044 __builtin_assume_aligned. */
13045 if (n->value & GOVD_SHARED)
13047 remove = true;
13048 break;
13053 else if (TREE_CODE (TREE_TYPE (decl)) == ARRAY_TYPE)
13055 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
13056 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
13057 remove = true;
13059 break;
13061 case OMP_CLAUSE_HAS_DEVICE_ADDR:
13062 decl = OMP_CLAUSE_DECL (c);
13063 while (INDIRECT_REF_P (decl)
13064 || TREE_CODE (decl) == ARRAY_REF)
13065 decl = TREE_OPERAND (decl, 0);
13066 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
13067 remove = n == NULL || !(n->value & GOVD_SEEN);
13068 break;
13070 case OMP_CLAUSE_IS_DEVICE_PTR:
13071 case OMP_CLAUSE_NONTEMPORAL:
13072 decl = OMP_CLAUSE_DECL (c);
13073 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
13074 remove = n == NULL || !(n->value & GOVD_SEEN);
13075 break;
13077 case OMP_CLAUSE_MAP:
13078 switch (OMP_CLAUSE_MAP_KIND (c))
13080 case GOMP_MAP_PRESENT_ALLOC:
13081 case GOMP_MAP_PRESENT_TO:
13082 case GOMP_MAP_PRESENT_FROM:
13083 case GOMP_MAP_PRESENT_TOFROM:
13084 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FORCE_PRESENT);
13085 break;
13086 default:
13087 break;
13089 if (code == OMP_TARGET_EXIT_DATA
13090 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_POINTER)
13092 remove = true;
13093 break;
13095 /* If we have a target region, we can push all the attaches to the
13096 end of the list (we may have standalone "attach" operations
13097 synthesized for GOMP_MAP_STRUCT nodes that must be processed after
13098 the attachment point AND the pointed-to block have been mapped).
13099 If we have something else, e.g. "enter data", we need to keep
13100 "attach" nodes together with the previous node they attach to so
13101 that separate "exit data" operations work properly (see
13102 libgomp/target.c). */
13103 if ((ctx->region_type & ORT_TARGET) != 0
13104 && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH
13105 || (OMP_CLAUSE_MAP_KIND (c)
13106 == GOMP_MAP_ATTACH_ZERO_LENGTH_ARRAY_SECTION)))
13107 move_attach = true;
13108 decl = OMP_CLAUSE_DECL (c);
13109 /* Data clauses associated with reductions must be
13110 compatible with present_or_copy. Warn and adjust the clause
13111 if that is not the case. */
13112 if (ctx->region_type == ORT_ACC_PARALLEL
13113 || ctx->region_type == ORT_ACC_SERIAL)
13115 tree t = DECL_P (decl) ? decl : TREE_OPERAND (decl, 0);
13116 n = NULL;
13118 if (DECL_P (t))
13119 n = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
13121 if (n && (n->value & GOVD_REDUCTION))
13123 enum gomp_map_kind kind = OMP_CLAUSE_MAP_KIND (c);
13125 OMP_CLAUSE_MAP_IN_REDUCTION (c) = 1;
13126 if ((kind & GOMP_MAP_TOFROM) != GOMP_MAP_TOFROM
13127 && kind != GOMP_MAP_FORCE_PRESENT
13128 && kind != GOMP_MAP_POINTER)
13130 warning_at (OMP_CLAUSE_LOCATION (c), 0,
13131 "incompatible data clause with reduction "
13132 "on %qE; promoting to %<present_or_copy%>",
13133 DECL_NAME (t));
13134 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_TOFROM);
13138 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT
13139 && (code == OMP_TARGET_EXIT_DATA || code == OACC_EXIT_DATA))
13141 remove = true;
13142 break;
13144 if (!DECL_P (decl))
13146 if ((ctx->region_type & ORT_TARGET) != 0
13147 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
13149 if (INDIRECT_REF_P (decl)
13150 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
13151 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
13152 == REFERENCE_TYPE))
13153 decl = TREE_OPERAND (decl, 0);
13154 if (TREE_CODE (decl) == COMPONENT_REF)
13156 while (TREE_CODE (decl) == COMPONENT_REF)
13157 decl = TREE_OPERAND (decl, 0);
13158 if (DECL_P (decl))
13160 n = splay_tree_lookup (ctx->variables,
13161 (splay_tree_key) decl);
13162 if (!(n->value & GOVD_SEEN))
13163 remove = true;
13167 break;
13169 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
13170 if ((ctx->region_type & ORT_TARGET) != 0
13171 && !(n->value & GOVD_SEEN)
13172 && GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c)) == 0
13173 && (!is_global_var (decl)
13174 || !lookup_attribute ("omp declare target link",
13175 DECL_ATTRIBUTES (decl))))
13177 remove = true;
13178 /* For struct element mapping, if struct is never referenced
13179 in target block and none of the mapping has always modifier,
13180 remove all the struct element mappings, which immediately
13181 follow the GOMP_MAP_STRUCT map clause. */
13182 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT)
13184 HOST_WIDE_INT cnt = tree_to_shwi (OMP_CLAUSE_SIZE (c));
13185 while (cnt--)
13186 OMP_CLAUSE_CHAIN (c)
13187 = OMP_CLAUSE_CHAIN (OMP_CLAUSE_CHAIN (c));
13190 else if (DECL_SIZE (decl)
13191 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST
13192 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_POINTER
13193 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FIRSTPRIVATE_POINTER
13194 && (OMP_CLAUSE_MAP_KIND (c)
13195 != GOMP_MAP_FIRSTPRIVATE_REFERENCE))
13197 /* For GOMP_MAP_FORCE_DEVICEPTR, we'll never enter here, because
13198 for these, TREE_CODE (DECL_SIZE (decl)) will always be
13199 INTEGER_CST. */
13200 gcc_assert (OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FORCE_DEVICEPTR);
13202 tree decl2 = DECL_VALUE_EXPR (decl);
13203 gcc_assert (INDIRECT_REF_P (decl2));
13204 decl2 = TREE_OPERAND (decl2, 0);
13205 gcc_assert (DECL_P (decl2));
13206 tree mem = build_simple_mem_ref (decl2);
13207 OMP_CLAUSE_DECL (c) = mem;
13208 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
13209 if (ctx->outer_context)
13211 omp_notice_variable (ctx->outer_context, decl2, true);
13212 omp_notice_variable (ctx->outer_context,
13213 OMP_CLAUSE_SIZE (c), true);
13215 if (((ctx->region_type & ORT_TARGET) != 0
13216 || !ctx->target_firstprivatize_array_bases)
13217 && ((n->value & GOVD_SEEN) == 0
13218 || (n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE)) == 0))
13220 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (c),
13221 OMP_CLAUSE_MAP);
13222 OMP_CLAUSE_DECL (nc) = decl;
13223 OMP_CLAUSE_SIZE (nc) = size_zero_node;
13224 if (ctx->target_firstprivatize_array_bases)
13225 OMP_CLAUSE_SET_MAP_KIND (nc,
13226 GOMP_MAP_FIRSTPRIVATE_POINTER);
13227 else
13228 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
13229 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (c);
13230 OMP_CLAUSE_CHAIN (c) = nc;
13231 c = nc;
13234 else
13236 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
13237 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
13238 gcc_assert ((n->value & GOVD_SEEN) == 0
13239 || ((n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE))
13240 == 0));
13242 break;
13244 case OMP_CLAUSE_TO:
13245 case OMP_CLAUSE_FROM:
13246 case OMP_CLAUSE__CACHE_:
13247 decl = OMP_CLAUSE_DECL (c);
13248 if (!DECL_P (decl))
13249 break;
13250 if (DECL_SIZE (decl)
13251 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
13253 tree decl2 = DECL_VALUE_EXPR (decl);
13254 gcc_assert (INDIRECT_REF_P (decl2));
13255 decl2 = TREE_OPERAND (decl2, 0);
13256 gcc_assert (DECL_P (decl2));
13257 tree mem = build_simple_mem_ref (decl2);
13258 OMP_CLAUSE_DECL (c) = mem;
13259 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
13260 if (ctx->outer_context)
13262 omp_notice_variable (ctx->outer_context, decl2, true);
13263 omp_notice_variable (ctx->outer_context,
13264 OMP_CLAUSE_SIZE (c), true);
13267 else if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
13268 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
13269 break;
13271 case OMP_CLAUSE_REDUCTION:
13272 if (OMP_CLAUSE_REDUCTION_INSCAN (c))
13274 decl = OMP_CLAUSE_DECL (c);
13275 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
13276 if ((n->value & GOVD_REDUCTION_INSCAN) == 0)
13278 remove = true;
13279 error_at (OMP_CLAUSE_LOCATION (c),
13280 "%qD specified in %<inscan%> %<reduction%> clause "
13281 "but not in %<scan%> directive clause", decl);
13282 break;
13284 has_inscan_reductions = true;
13286 /* FALLTHRU */
13287 case OMP_CLAUSE_IN_REDUCTION:
13288 case OMP_CLAUSE_TASK_REDUCTION:
13289 decl = OMP_CLAUSE_DECL (c);
13290 /* OpenACC reductions need a present_or_copy data clause.
13291 Add one if necessary. Emit error when the reduction is private. */
13292 if (ctx->region_type == ORT_ACC_PARALLEL
13293 || ctx->region_type == ORT_ACC_SERIAL)
13295 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
13296 if (n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE))
13298 remove = true;
13299 error_at (OMP_CLAUSE_LOCATION (c), "invalid private "
13300 "reduction on %qE", DECL_NAME (decl));
13302 else if ((n->value & GOVD_MAP) == 0)
13304 tree next = OMP_CLAUSE_CHAIN (c);
13305 tree nc = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_MAP);
13306 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_TOFROM);
13307 OMP_CLAUSE_DECL (nc) = decl;
13308 OMP_CLAUSE_CHAIN (c) = nc;
13309 lang_hooks.decls.omp_finish_clause (nc, pre_p,
13310 (ctx->region_type
13311 & ORT_ACC) != 0);
13312 while (1)
13314 OMP_CLAUSE_MAP_IN_REDUCTION (nc) = 1;
13315 if (OMP_CLAUSE_CHAIN (nc) == NULL)
13316 break;
13317 nc = OMP_CLAUSE_CHAIN (nc);
13319 OMP_CLAUSE_CHAIN (nc) = next;
13320 n->value |= GOVD_MAP;
13323 if (DECL_P (decl)
13324 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
13325 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
13326 break;
13328 case OMP_CLAUSE_ALLOCATE:
13329 decl = OMP_CLAUSE_DECL (c);
13330 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
13331 if (n != NULL && !(n->value & GOVD_SEEN))
13333 if ((n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE | GOVD_LINEAR))
13334 != 0
13335 && (n->value & (GOVD_REDUCTION | GOVD_LASTPRIVATE)) == 0)
13336 remove = true;
13338 if (!remove
13339 && OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
13340 && TREE_CODE (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)) != INTEGER_CST
13341 && ((ctx->region_type & (ORT_PARALLEL | ORT_TARGET)) != 0
13342 || (ctx->region_type & ORT_TASKLOOP) == ORT_TASK
13343 || (ctx->region_type & ORT_HOST_TEAMS) == ORT_HOST_TEAMS))
13345 tree allocator = OMP_CLAUSE_ALLOCATE_ALLOCATOR (c);
13346 n = splay_tree_lookup (ctx->variables, (splay_tree_key) allocator);
13347 if (n == NULL)
13349 enum omp_clause_default_kind default_kind
13350 = ctx->default_kind;
13351 ctx->default_kind = OMP_CLAUSE_DEFAULT_FIRSTPRIVATE;
13352 omp_notice_variable (ctx, OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
13353 true);
13354 ctx->default_kind = default_kind;
13356 else
13357 omp_notice_variable (ctx, OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
13358 true);
13360 break;
13362 case OMP_CLAUSE_COPYIN:
13363 case OMP_CLAUSE_COPYPRIVATE:
13364 case OMP_CLAUSE_IF:
13365 case OMP_CLAUSE_SELF:
13366 case OMP_CLAUSE_NUM_THREADS:
13367 case OMP_CLAUSE_NUM_TEAMS:
13368 case OMP_CLAUSE_THREAD_LIMIT:
13369 case OMP_CLAUSE_DIST_SCHEDULE:
13370 case OMP_CLAUSE_DEVICE:
13371 case OMP_CLAUSE_SCHEDULE:
13372 case OMP_CLAUSE_NOWAIT:
13373 case OMP_CLAUSE_ORDERED:
13374 case OMP_CLAUSE_DEFAULT:
13375 case OMP_CLAUSE_UNTIED:
13376 case OMP_CLAUSE_COLLAPSE:
13377 case OMP_CLAUSE_FINAL:
13378 case OMP_CLAUSE_MERGEABLE:
13379 case OMP_CLAUSE_PROC_BIND:
13380 case OMP_CLAUSE_SAFELEN:
13381 case OMP_CLAUSE_SIMDLEN:
13382 case OMP_CLAUSE_DEPEND:
13383 case OMP_CLAUSE_DOACROSS:
13384 case OMP_CLAUSE_PRIORITY:
13385 case OMP_CLAUSE_GRAINSIZE:
13386 case OMP_CLAUSE_NUM_TASKS:
13387 case OMP_CLAUSE_NOGROUP:
13388 case OMP_CLAUSE_THREADS:
13389 case OMP_CLAUSE_SIMD:
13390 case OMP_CLAUSE_FILTER:
13391 case OMP_CLAUSE_HINT:
13392 case OMP_CLAUSE_DEFAULTMAP:
13393 case OMP_CLAUSE_ORDER:
13394 case OMP_CLAUSE_BIND:
13395 case OMP_CLAUSE_DETACH:
13396 case OMP_CLAUSE_USE_DEVICE_PTR:
13397 case OMP_CLAUSE_USE_DEVICE_ADDR:
13398 case OMP_CLAUSE_ASYNC:
13399 case OMP_CLAUSE_WAIT:
13400 case OMP_CLAUSE_INDEPENDENT:
13401 case OMP_CLAUSE_NUM_GANGS:
13402 case OMP_CLAUSE_NUM_WORKERS:
13403 case OMP_CLAUSE_VECTOR_LENGTH:
13404 case OMP_CLAUSE_GANG:
13405 case OMP_CLAUSE_WORKER:
13406 case OMP_CLAUSE_VECTOR:
13407 case OMP_CLAUSE_AUTO:
13408 case OMP_CLAUSE_SEQ:
13409 case OMP_CLAUSE_TILE:
13410 case OMP_CLAUSE_IF_PRESENT:
13411 case OMP_CLAUSE_FINALIZE:
13412 case OMP_CLAUSE_INCLUSIVE:
13413 case OMP_CLAUSE_EXCLUSIVE:
13414 break;
13416 case OMP_CLAUSE_NOHOST:
13417 default:
13418 gcc_unreachable ();
13421 if (remove)
13422 *list_p = OMP_CLAUSE_CHAIN (c);
13423 else if (move_attach)
13425 /* Remove attach node from here, separate out into its own list. */
13426 *attach_tail = c;
13427 *list_p = OMP_CLAUSE_CHAIN (c);
13428 OMP_CLAUSE_CHAIN (c) = NULL_TREE;
13429 attach_tail = &OMP_CLAUSE_CHAIN (c);
13431 else
13432 list_p = &OMP_CLAUSE_CHAIN (c);
13435 /* Splice attach nodes at the end of the list. */
13436 if (attach_list)
13438 *list_p = attach_list;
13439 list_p = attach_tail;
13442 /* Add in any implicit data sharing. */
13443 struct gimplify_adjust_omp_clauses_data data;
13444 if ((gimplify_omp_ctxp->region_type & ORT_ACC) == 0)
13446 /* OpenMP. Implicit clauses are added at the start of the clause list,
13447 but after any non-map clauses. */
13448 tree *implicit_add_list_p = orig_list_p;
13449 while (*implicit_add_list_p
13450 && OMP_CLAUSE_CODE (*implicit_add_list_p) != OMP_CLAUSE_MAP)
13451 implicit_add_list_p = &OMP_CLAUSE_CHAIN (*implicit_add_list_p);
13452 data.list_p = implicit_add_list_p;
13454 else
13455 /* OpenACC. */
13456 data.list_p = list_p;
13457 data.pre_p = pre_p;
13458 splay_tree_foreach (ctx->variables, gimplify_adjust_omp_clauses_1, &data);
13460 if (has_inscan_reductions)
13461 for (c = *orig_list_p; c; c = OMP_CLAUSE_CHAIN (c))
13462 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
13463 && !OMP_CLAUSE_LINEAR_NO_COPYIN (c))
13465 error_at (OMP_CLAUSE_LOCATION (c),
13466 "%<inscan%> %<reduction%> clause used together with "
13467 "%<linear%> clause for a variable other than loop "
13468 "iterator");
13469 break;
13472 gimplify_omp_ctxp = ctx->outer_context;
13473 delete_omp_context (ctx);
13476 /* Return 0 if CONSTRUCTS selectors don't match the OpenMP context,
13477 -1 if unknown yet (simd is involved, won't be known until vectorization)
13478 and 1 if they do. If SCORES is non-NULL, it should point to an array
13479 of at least 2*NCONSTRUCTS+2 ints, and will be filled with the positions
13480 of the CONSTRUCTS (position -1 if it will never match) followed by
13481 number of constructs in the OpenMP context construct trait. If the
13482 score depends on whether it will be in a declare simd clone or not,
13483 the function returns 2 and there will be two sets of the scores, the first
13484 one for the case that it is not in a declare simd clone, the other
13485 that it is in a declare simd clone. */
13488 omp_construct_selector_matches (enum tree_code *constructs, int nconstructs,
13489 int *scores)
13491 int matched = 0, cnt = 0;
13492 bool simd_seen = false;
13493 bool target_seen = false;
13494 int declare_simd_cnt = -1;
13495 auto_vec<enum tree_code, 16> codes;
13496 for (struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp; ctx;)
13498 if (((ctx->region_type & ORT_PARALLEL) && ctx->code == OMP_PARALLEL)
13499 || ((ctx->region_type & (ORT_TARGET | ORT_IMPLICIT_TARGET | ORT_ACC))
13500 == ORT_TARGET && ctx->code == OMP_TARGET)
13501 || ((ctx->region_type & ORT_TEAMS) && ctx->code == OMP_TEAMS)
13502 || (ctx->region_type == ORT_WORKSHARE && ctx->code == OMP_FOR)
13503 || (ctx->region_type == ORT_SIMD
13504 && ctx->code == OMP_SIMD
13505 && !omp_find_clause (ctx->clauses, OMP_CLAUSE_BIND)))
13507 ++cnt;
13508 if (scores)
13509 codes.safe_push (ctx->code);
13510 else if (matched < nconstructs && ctx->code == constructs[matched])
13512 if (ctx->code == OMP_SIMD)
13514 if (matched)
13515 return 0;
13516 simd_seen = true;
13518 ++matched;
13520 if (ctx->code == OMP_TARGET)
13522 if (scores == NULL)
13523 return matched < nconstructs ? 0 : simd_seen ? -1 : 1;
13524 target_seen = true;
13525 break;
13528 else if (ctx->region_type == ORT_WORKSHARE
13529 && ctx->code == OMP_LOOP
13530 && ctx->outer_context
13531 && ctx->outer_context->region_type == ORT_COMBINED_PARALLEL
13532 && ctx->outer_context->outer_context
13533 && ctx->outer_context->outer_context->code == OMP_LOOP
13534 && ctx->outer_context->outer_context->distribute)
13535 ctx = ctx->outer_context->outer_context;
13536 ctx = ctx->outer_context;
13538 if (!target_seen
13539 && lookup_attribute ("omp declare simd",
13540 DECL_ATTRIBUTES (current_function_decl)))
13542 /* Declare simd is a maybe case, it is supposed to be added only to the
13543 omp-simd-clone.cc added clones and not to the base function. */
13544 declare_simd_cnt = cnt++;
13545 if (scores)
13546 codes.safe_push (OMP_SIMD);
13547 else if (cnt == 0
13548 && constructs[0] == OMP_SIMD)
13550 gcc_assert (matched == 0);
13551 simd_seen = true;
13552 if (++matched == nconstructs)
13553 return -1;
13556 if (tree attr = lookup_attribute ("omp declare variant variant",
13557 DECL_ATTRIBUTES (current_function_decl)))
13559 enum tree_code variant_constructs[5];
13560 int variant_nconstructs = 0;
13561 if (!target_seen)
13562 variant_nconstructs
13563 = omp_constructor_traits_to_codes (TREE_VALUE (attr),
13564 variant_constructs);
13565 for (int i = 0; i < variant_nconstructs; i++)
13567 ++cnt;
13568 if (scores)
13569 codes.safe_push (variant_constructs[i]);
13570 else if (matched < nconstructs
13571 && variant_constructs[i] == constructs[matched])
13573 if (variant_constructs[i] == OMP_SIMD)
13575 if (matched)
13576 return 0;
13577 simd_seen = true;
13579 ++matched;
13583 if (!target_seen
13584 && lookup_attribute ("omp declare target block",
13585 DECL_ATTRIBUTES (current_function_decl)))
13587 if (scores)
13588 codes.safe_push (OMP_TARGET);
13589 else if (matched < nconstructs && constructs[matched] == OMP_TARGET)
13590 ++matched;
13592 if (scores)
13594 for (int pass = 0; pass < (declare_simd_cnt == -1 ? 1 : 2); pass++)
13596 int j = codes.length () - 1;
13597 for (int i = nconstructs - 1; i >= 0; i--)
13599 while (j >= 0
13600 && (pass != 0 || declare_simd_cnt != j)
13601 && constructs[i] != codes[j])
13602 --j;
13603 if (pass == 0 && declare_simd_cnt != -1 && j > declare_simd_cnt)
13604 *scores++ = j - 1;
13605 else
13606 *scores++ = j;
13608 *scores++ = ((pass == 0 && declare_simd_cnt != -1)
13609 ? codes.length () - 1 : codes.length ());
13611 return declare_simd_cnt == -1 ? 1 : 2;
13613 if (matched == nconstructs)
13614 return simd_seen ? -1 : 1;
13615 return 0;
13618 /* Gimplify OACC_CACHE. */
13620 static void
13621 gimplify_oacc_cache (tree *expr_p, gimple_seq *pre_p)
13623 tree expr = *expr_p;
13625 gimplify_scan_omp_clauses (&OACC_CACHE_CLAUSES (expr), pre_p, ORT_ACC,
13626 OACC_CACHE);
13627 gimplify_adjust_omp_clauses (pre_p, NULL, &OACC_CACHE_CLAUSES (expr),
13628 OACC_CACHE);
13630 /* TODO: Do something sensible with this information. */
13632 *expr_p = NULL_TREE;
13635 /* Helper function of gimplify_oacc_declare. The helper's purpose is to,
13636 if required, translate 'kind' in CLAUSE into an 'entry' kind and 'exit'
13637 kind. The entry kind will replace the one in CLAUSE, while the exit
13638 kind will be used in a new omp_clause and returned to the caller. */
13640 static tree
13641 gimplify_oacc_declare_1 (tree clause)
13643 HOST_WIDE_INT kind, new_op;
13644 bool ret = false;
13645 tree c = NULL;
13647 kind = OMP_CLAUSE_MAP_KIND (clause);
13649 switch (kind)
13651 case GOMP_MAP_ALLOC:
13652 new_op = GOMP_MAP_RELEASE;
13653 ret = true;
13654 break;
13656 case GOMP_MAP_FROM:
13657 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_FORCE_ALLOC);
13658 new_op = GOMP_MAP_FROM;
13659 ret = true;
13660 break;
13662 case GOMP_MAP_TOFROM:
13663 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_TO);
13664 new_op = GOMP_MAP_FROM;
13665 ret = true;
13666 break;
13668 case GOMP_MAP_DEVICE_RESIDENT:
13669 case GOMP_MAP_FORCE_DEVICEPTR:
13670 case GOMP_MAP_FORCE_PRESENT:
13671 case GOMP_MAP_LINK:
13672 case GOMP_MAP_POINTER:
13673 case GOMP_MAP_TO:
13674 break;
13676 default:
13677 gcc_unreachable ();
13678 break;
13681 if (ret)
13683 c = build_omp_clause (OMP_CLAUSE_LOCATION (clause), OMP_CLAUSE_MAP);
13684 OMP_CLAUSE_SET_MAP_KIND (c, new_op);
13685 OMP_CLAUSE_DECL (c) = OMP_CLAUSE_DECL (clause);
13688 return c;
13691 /* Gimplify OACC_DECLARE. */
13693 static void
13694 gimplify_oacc_declare (tree *expr_p, gimple_seq *pre_p)
13696 tree expr = *expr_p;
13697 gomp_target *stmt;
13698 tree clauses, t, decl;
13700 clauses = OACC_DECLARE_CLAUSES (expr);
13702 gimplify_scan_omp_clauses (&clauses, pre_p, ORT_TARGET_DATA, OACC_DECLARE);
13703 gimplify_adjust_omp_clauses (pre_p, NULL, &clauses, OACC_DECLARE);
13705 for (t = clauses; t; t = OMP_CLAUSE_CHAIN (t))
13707 decl = OMP_CLAUSE_DECL (t);
13709 if (TREE_CODE (decl) == MEM_REF)
13710 decl = TREE_OPERAND (decl, 0);
13712 if (VAR_P (decl) && !is_oacc_declared (decl))
13714 tree attr = get_identifier ("oacc declare target");
13715 DECL_ATTRIBUTES (decl) = tree_cons (attr, NULL_TREE,
13716 DECL_ATTRIBUTES (decl));
13719 if (VAR_P (decl)
13720 && !is_global_var (decl)
13721 && DECL_CONTEXT (decl) == current_function_decl)
13723 tree c = gimplify_oacc_declare_1 (t);
13724 if (c)
13726 if (oacc_declare_returns == NULL)
13727 oacc_declare_returns = new hash_map<tree, tree>;
13729 oacc_declare_returns->put (decl, c);
13733 if (gimplify_omp_ctxp)
13734 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_SEEN);
13737 stmt = gimple_build_omp_target (NULL, GF_OMP_TARGET_KIND_OACC_DECLARE,
13738 clauses);
13740 gimplify_seq_add_stmt (pre_p, stmt);
13742 *expr_p = NULL_TREE;
13745 /* Gimplify the contents of an OMP_PARALLEL statement. This involves
13746 gimplification of the body, as well as scanning the body for used
13747 variables. We need to do this scan now, because variable-sized
13748 decls will be decomposed during gimplification. */
13750 static void
13751 gimplify_omp_parallel (tree *expr_p, gimple_seq *pre_p)
13753 tree expr = *expr_p;
13754 gimple *g;
13755 gimple_seq body = NULL;
13757 gimplify_scan_omp_clauses (&OMP_PARALLEL_CLAUSES (expr), pre_p,
13758 OMP_PARALLEL_COMBINED (expr)
13759 ? ORT_COMBINED_PARALLEL
13760 : ORT_PARALLEL, OMP_PARALLEL);
13762 push_gimplify_context ();
13764 g = gimplify_and_return_first (OMP_PARALLEL_BODY (expr), &body);
13765 if (gimple_code (g) == GIMPLE_BIND)
13766 pop_gimplify_context (g);
13767 else
13768 pop_gimplify_context (NULL);
13770 gimplify_adjust_omp_clauses (pre_p, body, &OMP_PARALLEL_CLAUSES (expr),
13771 OMP_PARALLEL);
13773 g = gimple_build_omp_parallel (body,
13774 OMP_PARALLEL_CLAUSES (expr),
13775 NULL_TREE, NULL_TREE);
13776 if (OMP_PARALLEL_COMBINED (expr))
13777 gimple_omp_set_subcode (g, GF_OMP_PARALLEL_COMBINED);
13778 gimplify_seq_add_stmt (pre_p, g);
13779 *expr_p = NULL_TREE;
13782 /* Gimplify the contents of an OMP_TASK statement. This involves
13783 gimplification of the body, as well as scanning the body for used
13784 variables. We need to do this scan now, because variable-sized
13785 decls will be decomposed during gimplification. */
13787 static void
13788 gimplify_omp_task (tree *expr_p, gimple_seq *pre_p)
13790 tree expr = *expr_p;
13791 gimple *g;
13792 gimple_seq body = NULL;
13793 bool nowait = false;
13794 bool has_depend = false;
13796 if (OMP_TASK_BODY (expr) == NULL_TREE)
13798 for (tree c = OMP_TASK_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
13799 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND)
13801 has_depend = true;
13802 if (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_MUTEXINOUTSET)
13804 error_at (OMP_CLAUSE_LOCATION (c),
13805 "%<mutexinoutset%> kind in %<depend%> clause on a "
13806 "%<taskwait%> construct");
13807 break;
13810 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_NOWAIT)
13811 nowait = true;
13812 if (nowait && !has_depend)
13814 error_at (EXPR_LOCATION (expr),
13815 "%<taskwait%> construct with %<nowait%> clause but no "
13816 "%<depend%> clauses");
13817 *expr_p = NULL_TREE;
13818 return;
13822 gimplify_scan_omp_clauses (&OMP_TASK_CLAUSES (expr), pre_p,
13823 omp_find_clause (OMP_TASK_CLAUSES (expr),
13824 OMP_CLAUSE_UNTIED)
13825 ? ORT_UNTIED_TASK : ORT_TASK, OMP_TASK);
13827 if (OMP_TASK_BODY (expr))
13829 push_gimplify_context ();
13831 g = gimplify_and_return_first (OMP_TASK_BODY (expr), &body);
13832 if (gimple_code (g) == GIMPLE_BIND)
13833 pop_gimplify_context (g);
13834 else
13835 pop_gimplify_context (NULL);
13838 gimplify_adjust_omp_clauses (pre_p, body, &OMP_TASK_CLAUSES (expr),
13839 OMP_TASK);
13841 g = gimple_build_omp_task (body,
13842 OMP_TASK_CLAUSES (expr),
13843 NULL_TREE, NULL_TREE,
13844 NULL_TREE, NULL_TREE, NULL_TREE);
13845 if (OMP_TASK_BODY (expr) == NULL_TREE)
13846 gimple_omp_task_set_taskwait_p (g, true);
13847 gimplify_seq_add_stmt (pre_p, g);
13848 *expr_p = NULL_TREE;
13851 /* Helper function for gimplify_omp_for. If *TP is not a gimple constant,
13852 force it into a temporary initialized in PRE_P and add firstprivate clause
13853 to ORIG_FOR_STMT. */
13855 static void
13856 gimplify_omp_taskloop_expr (tree type, tree *tp, gimple_seq *pre_p,
13857 tree orig_for_stmt)
13859 if (*tp == NULL || is_gimple_constant (*tp))
13860 return;
13862 *tp = get_initialized_tmp_var (*tp, pre_p, NULL, false);
13863 /* Reference to pointer conversion is considered useless,
13864 but is significant for firstprivate clause. Force it
13865 here. */
13866 if (type
13867 && TREE_CODE (type) == POINTER_TYPE
13868 && TREE_CODE (TREE_TYPE (*tp)) == REFERENCE_TYPE)
13870 tree v = create_tmp_var (TYPE_MAIN_VARIANT (type));
13871 tree m = build2 (INIT_EXPR, TREE_TYPE (v), v, *tp);
13872 gimplify_and_add (m, pre_p);
13873 *tp = v;
13876 tree c = build_omp_clause (input_location, OMP_CLAUSE_FIRSTPRIVATE);
13877 OMP_CLAUSE_DECL (c) = *tp;
13878 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (orig_for_stmt);
13879 OMP_FOR_CLAUSES (orig_for_stmt) = c;
13882 /* Helper function of gimplify_omp_for, find OMP_ORDERED with
13883 null OMP_ORDERED_BODY inside of OMP_FOR's body. */
13885 static tree
13886 find_standalone_omp_ordered (tree *tp, int *walk_subtrees, void *)
13888 switch (TREE_CODE (*tp))
13890 case OMP_ORDERED:
13891 if (OMP_ORDERED_BODY (*tp) == NULL_TREE)
13892 return *tp;
13893 break;
13894 case OMP_SIMD:
13895 case OMP_PARALLEL:
13896 case OMP_TARGET:
13897 *walk_subtrees = 0;
13898 break;
13899 default:
13900 break;
13902 return NULL_TREE;
13905 /* Gimplify the gross structure of an OMP_FOR statement. */
13907 static enum gimplify_status
13908 gimplify_omp_for (tree *expr_p, gimple_seq *pre_p)
13910 tree for_stmt, orig_for_stmt, inner_for_stmt = NULL_TREE, decl, var, t;
13911 enum gimplify_status ret = GS_ALL_DONE;
13912 enum gimplify_status tret;
13913 gomp_for *gfor;
13914 gimple_seq for_body, for_pre_body;
13915 int i;
13916 bitmap has_decl_expr = NULL;
13917 enum omp_region_type ort = ORT_WORKSHARE;
13918 bool openacc = TREE_CODE (*expr_p) == OACC_LOOP;
13920 orig_for_stmt = for_stmt = *expr_p;
13922 bool loop_p = (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_BIND)
13923 != NULL_TREE);
13924 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
13926 tree *data[4] = { NULL, NULL, NULL, NULL };
13927 gcc_assert (TREE_CODE (for_stmt) != OACC_LOOP);
13928 inner_for_stmt = walk_tree (&OMP_FOR_BODY (for_stmt),
13929 find_combined_omp_for, data, NULL);
13930 if (inner_for_stmt == NULL_TREE)
13932 gcc_assert (seen_error ());
13933 *expr_p = NULL_TREE;
13934 return GS_ERROR;
13936 if (data[2] && OMP_FOR_PRE_BODY (*data[2]))
13938 append_to_statement_list_force (OMP_FOR_PRE_BODY (*data[2]),
13939 &OMP_FOR_PRE_BODY (for_stmt));
13940 OMP_FOR_PRE_BODY (*data[2]) = NULL_TREE;
13942 if (OMP_FOR_PRE_BODY (inner_for_stmt))
13944 append_to_statement_list_force (OMP_FOR_PRE_BODY (inner_for_stmt),
13945 &OMP_FOR_PRE_BODY (for_stmt));
13946 OMP_FOR_PRE_BODY (inner_for_stmt) = NULL_TREE;
13949 if (data[0])
13951 /* We have some statements or variable declarations in between
13952 the composite construct directives. Move them around the
13953 inner_for_stmt. */
13954 data[0] = expr_p;
13955 for (i = 0; i < 3; i++)
13956 if (data[i])
13958 tree t = *data[i];
13959 if (i < 2 && data[i + 1] == &OMP_BODY (t))
13960 data[i + 1] = data[i];
13961 *data[i] = OMP_BODY (t);
13962 tree body = build3 (BIND_EXPR, void_type_node, NULL_TREE,
13963 NULL_TREE, make_node (BLOCK));
13964 OMP_BODY (t) = body;
13965 append_to_statement_list_force (inner_for_stmt,
13966 &BIND_EXPR_BODY (body));
13967 *data[3] = t;
13968 data[3] = tsi_stmt_ptr (tsi_start (BIND_EXPR_BODY (body)));
13969 gcc_assert (*data[3] == inner_for_stmt);
13971 return GS_OK;
13974 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (inner_for_stmt)); i++)
13975 if (!loop_p
13976 && OMP_FOR_ORIG_DECLS (inner_for_stmt)
13977 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
13978 i)) == TREE_LIST
13979 && TREE_PURPOSE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
13980 i)))
13982 tree orig = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt), i);
13983 /* Class iterators aren't allowed on OMP_SIMD, so the only
13984 case we need to solve is distribute parallel for. They are
13985 allowed on the loop construct, but that is already handled
13986 in gimplify_omp_loop. */
13987 gcc_assert (TREE_CODE (inner_for_stmt) == OMP_FOR
13988 && TREE_CODE (for_stmt) == OMP_DISTRIBUTE
13989 && data[1]);
13990 tree orig_decl = TREE_PURPOSE (orig);
13991 tree last = TREE_VALUE (orig);
13992 tree *pc;
13993 for (pc = &OMP_FOR_CLAUSES (inner_for_stmt);
13994 *pc; pc = &OMP_CLAUSE_CHAIN (*pc))
13995 if ((OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_PRIVATE
13996 || OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_LASTPRIVATE)
13997 && OMP_CLAUSE_DECL (*pc) == orig_decl)
13998 break;
13999 if (*pc == NULL_TREE)
14001 tree *spc;
14002 for (spc = &OMP_PARALLEL_CLAUSES (*data[1]);
14003 *spc; spc = &OMP_CLAUSE_CHAIN (*spc))
14004 if (OMP_CLAUSE_CODE (*spc) == OMP_CLAUSE_PRIVATE
14005 && OMP_CLAUSE_DECL (*spc) == orig_decl)
14006 break;
14007 if (*spc)
14009 tree c = *spc;
14010 *spc = OMP_CLAUSE_CHAIN (c);
14011 OMP_CLAUSE_CHAIN (c) = NULL_TREE;
14012 *pc = c;
14015 if (*pc == NULL_TREE)
14017 else if (OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_PRIVATE)
14019 /* private clause will appear only on inner_for_stmt.
14020 Change it into firstprivate, and add private clause
14021 on for_stmt. */
14022 tree c = copy_node (*pc);
14023 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
14024 OMP_FOR_CLAUSES (for_stmt) = c;
14025 OMP_CLAUSE_CODE (*pc) = OMP_CLAUSE_FIRSTPRIVATE;
14026 lang_hooks.decls.omp_finish_clause (*pc, pre_p, openacc);
14028 else
14030 /* lastprivate clause will appear on both inner_for_stmt
14031 and for_stmt. Add firstprivate clause to
14032 inner_for_stmt. */
14033 tree c = build_omp_clause (OMP_CLAUSE_LOCATION (*pc),
14034 OMP_CLAUSE_FIRSTPRIVATE);
14035 OMP_CLAUSE_DECL (c) = OMP_CLAUSE_DECL (*pc);
14036 OMP_CLAUSE_CHAIN (c) = *pc;
14037 *pc = c;
14038 lang_hooks.decls.omp_finish_clause (*pc, pre_p, openacc);
14040 tree c = build_omp_clause (UNKNOWN_LOCATION,
14041 OMP_CLAUSE_FIRSTPRIVATE);
14042 OMP_CLAUSE_DECL (c) = last;
14043 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
14044 OMP_PARALLEL_CLAUSES (*data[1]) = c;
14045 c = build_omp_clause (UNKNOWN_LOCATION,
14046 *pc ? OMP_CLAUSE_SHARED
14047 : OMP_CLAUSE_FIRSTPRIVATE);
14048 OMP_CLAUSE_DECL (c) = orig_decl;
14049 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
14050 OMP_PARALLEL_CLAUSES (*data[1]) = c;
14052 /* Similarly, take care of C++ range for temporaries, those should
14053 be firstprivate on OMP_PARALLEL if any. */
14054 if (data[1])
14055 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (inner_for_stmt)); i++)
14056 if (OMP_FOR_ORIG_DECLS (inner_for_stmt)
14057 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
14058 i)) == TREE_LIST
14059 && TREE_CHAIN (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
14060 i)))
14062 tree orig
14063 = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt), i);
14064 tree v = TREE_CHAIN (orig);
14065 tree c = build_omp_clause (UNKNOWN_LOCATION,
14066 OMP_CLAUSE_FIRSTPRIVATE);
14067 /* First add firstprivate clause for the __for_end artificial
14068 decl. */
14069 OMP_CLAUSE_DECL (c) = TREE_VEC_ELT (v, 1);
14070 if (TREE_CODE (TREE_TYPE (OMP_CLAUSE_DECL (c)))
14071 == REFERENCE_TYPE)
14072 OMP_CLAUSE_FIRSTPRIVATE_NO_REFERENCE (c) = 1;
14073 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
14074 OMP_PARALLEL_CLAUSES (*data[1]) = c;
14075 if (TREE_VEC_ELT (v, 0))
14077 /* And now the same for __for_range artificial decl if it
14078 exists. */
14079 c = build_omp_clause (UNKNOWN_LOCATION,
14080 OMP_CLAUSE_FIRSTPRIVATE);
14081 OMP_CLAUSE_DECL (c) = TREE_VEC_ELT (v, 0);
14082 if (TREE_CODE (TREE_TYPE (OMP_CLAUSE_DECL (c)))
14083 == REFERENCE_TYPE)
14084 OMP_CLAUSE_FIRSTPRIVATE_NO_REFERENCE (c) = 1;
14085 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
14086 OMP_PARALLEL_CLAUSES (*data[1]) = c;
14091 switch (TREE_CODE (for_stmt))
14093 case OMP_FOR:
14094 if (OMP_FOR_NON_RECTANGULAR (inner_for_stmt ? inner_for_stmt : for_stmt))
14096 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
14097 OMP_CLAUSE_SCHEDULE))
14098 error_at (EXPR_LOCATION (for_stmt),
14099 "%qs clause may not appear on non-rectangular %qs",
14100 "schedule", lang_GNU_Fortran () ? "do" : "for");
14101 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ORDERED))
14102 error_at (EXPR_LOCATION (for_stmt),
14103 "%qs clause may not appear on non-rectangular %qs",
14104 "ordered", lang_GNU_Fortran () ? "do" : "for");
14106 break;
14107 case OMP_DISTRIBUTE:
14108 if (OMP_FOR_NON_RECTANGULAR (inner_for_stmt ? inner_for_stmt : for_stmt)
14109 && omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
14110 OMP_CLAUSE_DIST_SCHEDULE))
14111 error_at (EXPR_LOCATION (for_stmt),
14112 "%qs clause may not appear on non-rectangular %qs",
14113 "dist_schedule", "distribute");
14114 break;
14115 case OACC_LOOP:
14116 ort = ORT_ACC;
14117 break;
14118 case OMP_TASKLOOP:
14119 if (OMP_FOR_NON_RECTANGULAR (inner_for_stmt ? inner_for_stmt : for_stmt))
14121 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
14122 OMP_CLAUSE_GRAINSIZE))
14123 error_at (EXPR_LOCATION (for_stmt),
14124 "%qs clause may not appear on non-rectangular %qs",
14125 "grainsize", "taskloop");
14126 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
14127 OMP_CLAUSE_NUM_TASKS))
14128 error_at (EXPR_LOCATION (for_stmt),
14129 "%qs clause may not appear on non-rectangular %qs",
14130 "num_tasks", "taskloop");
14132 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_UNTIED))
14133 ort = ORT_UNTIED_TASKLOOP;
14134 else
14135 ort = ORT_TASKLOOP;
14136 break;
14137 case OMP_SIMD:
14138 ort = ORT_SIMD;
14139 break;
14140 default:
14141 gcc_unreachable ();
14144 /* Set OMP_CLAUSE_LINEAR_NO_COPYIN flag on explicit linear
14145 clause for the IV. */
14146 if (ort == ORT_SIMD && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
14148 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), 0);
14149 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
14150 decl = TREE_OPERAND (t, 0);
14151 for (tree c = OMP_FOR_CLAUSES (for_stmt); c; c = OMP_CLAUSE_CHAIN (c))
14152 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
14153 && OMP_CLAUSE_DECL (c) == decl)
14155 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
14156 break;
14160 if (TREE_CODE (for_stmt) != OMP_TASKLOOP)
14161 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (for_stmt), pre_p, ort,
14162 loop_p && TREE_CODE (for_stmt) != OMP_SIMD
14163 ? OMP_LOOP : TREE_CODE (for_stmt));
14165 if (TREE_CODE (for_stmt) == OMP_DISTRIBUTE)
14166 gimplify_omp_ctxp->distribute = true;
14168 /* Handle OMP_FOR_INIT. */
14169 for_pre_body = NULL;
14170 if ((ort == ORT_SIMD
14171 || (inner_for_stmt && TREE_CODE (inner_for_stmt) == OMP_SIMD))
14172 && OMP_FOR_PRE_BODY (for_stmt))
14174 has_decl_expr = BITMAP_ALLOC (NULL);
14175 if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == DECL_EXPR
14176 && VAR_P (DECL_EXPR_DECL (OMP_FOR_PRE_BODY (for_stmt))))
14178 t = OMP_FOR_PRE_BODY (for_stmt);
14179 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
14181 else if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == STATEMENT_LIST)
14183 tree_stmt_iterator si;
14184 for (si = tsi_start (OMP_FOR_PRE_BODY (for_stmt)); !tsi_end_p (si);
14185 tsi_next (&si))
14187 t = tsi_stmt (si);
14188 if (TREE_CODE (t) == DECL_EXPR
14189 && VAR_P (DECL_EXPR_DECL (t)))
14190 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
14194 if (OMP_FOR_PRE_BODY (for_stmt))
14196 if (TREE_CODE (for_stmt) != OMP_TASKLOOP || gimplify_omp_ctxp)
14197 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
14198 else
14200 struct gimplify_omp_ctx ctx;
14201 memset (&ctx, 0, sizeof (ctx));
14202 ctx.region_type = ORT_NONE;
14203 gimplify_omp_ctxp = &ctx;
14204 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
14205 gimplify_omp_ctxp = NULL;
14208 OMP_FOR_PRE_BODY (for_stmt) = NULL_TREE;
14210 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
14211 for_stmt = inner_for_stmt;
14213 /* For taskloop, need to gimplify the start, end and step before the
14214 taskloop, outside of the taskloop omp context. */
14215 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
14217 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
14219 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
14220 gimple_seq *for_pre_p = (gimple_seq_empty_p (for_pre_body)
14221 ? pre_p : &for_pre_body);
14222 tree type = TREE_TYPE (TREE_OPERAND (t, 0));
14223 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
14225 tree v = TREE_OPERAND (t, 1);
14226 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 1),
14227 for_pre_p, orig_for_stmt);
14228 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 2),
14229 for_pre_p, orig_for_stmt);
14231 else
14232 gimplify_omp_taskloop_expr (type, &TREE_OPERAND (t, 1), for_pre_p,
14233 orig_for_stmt);
14235 /* Handle OMP_FOR_COND. */
14236 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
14237 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
14239 tree v = TREE_OPERAND (t, 1);
14240 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 1),
14241 for_pre_p, orig_for_stmt);
14242 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 2),
14243 for_pre_p, orig_for_stmt);
14245 else
14246 gimplify_omp_taskloop_expr (type, &TREE_OPERAND (t, 1), for_pre_p,
14247 orig_for_stmt);
14249 /* Handle OMP_FOR_INCR. */
14250 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
14251 if (TREE_CODE (t) == MODIFY_EXPR)
14253 decl = TREE_OPERAND (t, 0);
14254 t = TREE_OPERAND (t, 1);
14255 tree *tp = &TREE_OPERAND (t, 1);
14256 if (TREE_CODE (t) == PLUS_EXPR && *tp == decl)
14257 tp = &TREE_OPERAND (t, 0);
14259 gimplify_omp_taskloop_expr (NULL_TREE, tp, for_pre_p,
14260 orig_for_stmt);
14264 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (orig_for_stmt), pre_p, ort,
14265 OMP_TASKLOOP);
14268 if (orig_for_stmt != for_stmt)
14269 gimplify_omp_ctxp->combined_loop = true;
14271 for_body = NULL;
14272 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
14273 == TREE_VEC_LENGTH (OMP_FOR_COND (for_stmt)));
14274 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
14275 == TREE_VEC_LENGTH (OMP_FOR_INCR (for_stmt)));
14277 tree c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ORDERED);
14278 bool is_doacross = false;
14279 if (c && walk_tree_without_duplicates (&OMP_FOR_BODY (for_stmt),
14280 find_standalone_omp_ordered, NULL))
14282 OMP_CLAUSE_ORDERED_DOACROSS (c) = 1;
14283 is_doacross = true;
14284 int len = TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt));
14285 gimplify_omp_ctxp->loop_iter_var.create (len * 2);
14286 for (tree *pc = &OMP_FOR_CLAUSES (for_stmt); *pc; )
14287 if (OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_LINEAR)
14289 error_at (OMP_CLAUSE_LOCATION (*pc),
14290 "%<linear%> clause may not be specified together "
14291 "with %<ordered%> clause if stand-alone %<ordered%> "
14292 "construct is nested in it");
14293 *pc = OMP_CLAUSE_CHAIN (*pc);
14295 else
14296 pc = &OMP_CLAUSE_CHAIN (*pc);
14298 int collapse = 1, tile = 0;
14299 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_COLLAPSE);
14300 if (c)
14301 collapse = tree_to_shwi (OMP_CLAUSE_COLLAPSE_EXPR (c));
14302 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_TILE);
14303 if (c)
14304 tile = list_length (OMP_CLAUSE_TILE_LIST (c));
14305 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ALLOCATE);
14306 hash_set<tree> *allocate_uids = NULL;
14307 if (c)
14309 allocate_uids = new hash_set<tree>;
14310 for (; c; c = OMP_CLAUSE_CHAIN (c))
14311 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_ALLOCATE)
14312 allocate_uids->add (OMP_CLAUSE_DECL (c));
14314 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
14316 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
14317 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
14318 decl = TREE_OPERAND (t, 0);
14319 gcc_assert (DECL_P (decl));
14320 gcc_assert (INTEGRAL_TYPE_P (TREE_TYPE (decl))
14321 || POINTER_TYPE_P (TREE_TYPE (decl)));
14322 if (is_doacross)
14324 if (TREE_CODE (for_stmt) == OMP_FOR && OMP_FOR_ORIG_DECLS (for_stmt))
14326 tree orig_decl = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
14327 if (TREE_CODE (orig_decl) == TREE_LIST)
14329 orig_decl = TREE_PURPOSE (orig_decl);
14330 if (!orig_decl)
14331 orig_decl = decl;
14333 gimplify_omp_ctxp->loop_iter_var.quick_push (orig_decl);
14335 else
14336 gimplify_omp_ctxp->loop_iter_var.quick_push (decl);
14337 gimplify_omp_ctxp->loop_iter_var.quick_push (decl);
14340 if (for_stmt == orig_for_stmt)
14342 tree orig_decl = decl;
14343 if (OMP_FOR_ORIG_DECLS (for_stmt))
14345 tree orig_decl = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
14346 if (TREE_CODE (orig_decl) == TREE_LIST)
14348 orig_decl = TREE_PURPOSE (orig_decl);
14349 if (!orig_decl)
14350 orig_decl = decl;
14353 if (is_global_var (orig_decl) && DECL_THREAD_LOCAL_P (orig_decl))
14354 error_at (EXPR_LOCATION (for_stmt),
14355 "threadprivate iteration variable %qD", orig_decl);
14358 /* Make sure the iteration variable is private. */
14359 tree c = NULL_TREE;
14360 tree c2 = NULL_TREE;
14361 if (orig_for_stmt != for_stmt)
14363 /* Preserve this information until we gimplify the inner simd. */
14364 if (has_decl_expr
14365 && bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
14366 TREE_PRIVATE (t) = 1;
14368 else if (ort == ORT_SIMD)
14370 splay_tree_node n = splay_tree_lookup (gimplify_omp_ctxp->variables,
14371 (splay_tree_key) decl);
14372 omp_is_private (gimplify_omp_ctxp, decl,
14373 1 + (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
14374 != 1));
14375 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
14377 omp_notice_variable (gimplify_omp_ctxp, decl, true);
14378 if (n->value & GOVD_LASTPRIVATE_CONDITIONAL)
14379 for (tree c3 = omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
14380 OMP_CLAUSE_LASTPRIVATE);
14381 c3; c3 = omp_find_clause (OMP_CLAUSE_CHAIN (c3),
14382 OMP_CLAUSE_LASTPRIVATE))
14383 if (OMP_CLAUSE_DECL (c3) == decl)
14385 warning_at (OMP_CLAUSE_LOCATION (c3), OPT_Wopenmp,
14386 "conditional %<lastprivate%> on loop "
14387 "iterator %qD ignored", decl);
14388 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c3) = 0;
14389 n->value &= ~GOVD_LASTPRIVATE_CONDITIONAL;
14392 else if (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1 && !loop_p)
14394 c = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
14395 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
14396 unsigned int flags = GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN;
14397 if ((has_decl_expr
14398 && bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
14399 || TREE_PRIVATE (t))
14401 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
14402 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
14404 struct gimplify_omp_ctx *outer
14405 = gimplify_omp_ctxp->outer_context;
14406 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
14408 if (outer->region_type == ORT_WORKSHARE
14409 && outer->combined_loop)
14411 n = splay_tree_lookup (outer->variables,
14412 (splay_tree_key)decl);
14413 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
14415 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
14416 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
14418 else
14420 struct gimplify_omp_ctx *octx = outer->outer_context;
14421 if (octx
14422 && octx->region_type == ORT_COMBINED_PARALLEL
14423 && octx->outer_context
14424 && (octx->outer_context->region_type
14425 == ORT_WORKSHARE)
14426 && octx->outer_context->combined_loop)
14428 octx = octx->outer_context;
14429 n = splay_tree_lookup (octx->variables,
14430 (splay_tree_key)decl);
14431 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
14433 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
14434 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
14441 OMP_CLAUSE_DECL (c) = decl;
14442 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
14443 OMP_FOR_CLAUSES (for_stmt) = c;
14444 omp_add_variable (gimplify_omp_ctxp, decl, flags);
14445 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
14446 omp_lastprivate_for_combined_outer_constructs (outer, decl,
14447 true);
14449 else
14451 bool lastprivate
14452 = (!has_decl_expr
14453 || !bitmap_bit_p (has_decl_expr, DECL_UID (decl)));
14454 if (TREE_PRIVATE (t))
14455 lastprivate = false;
14456 if (loop_p && OMP_FOR_ORIG_DECLS (for_stmt))
14458 tree elt = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
14459 if (TREE_CODE (elt) == TREE_LIST && TREE_PURPOSE (elt))
14460 lastprivate = false;
14463 struct gimplify_omp_ctx *outer
14464 = gimplify_omp_ctxp->outer_context;
14465 if (outer && lastprivate)
14466 omp_lastprivate_for_combined_outer_constructs (outer, decl,
14467 true);
14469 c = build_omp_clause (input_location,
14470 lastprivate ? OMP_CLAUSE_LASTPRIVATE
14471 : OMP_CLAUSE_PRIVATE);
14472 OMP_CLAUSE_DECL (c) = decl;
14473 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
14474 OMP_FOR_CLAUSES (for_stmt) = c;
14475 omp_add_variable (gimplify_omp_ctxp, decl,
14476 (lastprivate ? GOVD_LASTPRIVATE : GOVD_PRIVATE)
14477 | GOVD_EXPLICIT | GOVD_SEEN);
14478 c = NULL_TREE;
14481 else if (omp_is_private (gimplify_omp_ctxp, decl, 0))
14483 omp_notice_variable (gimplify_omp_ctxp, decl, true);
14484 splay_tree_node n = splay_tree_lookup (gimplify_omp_ctxp->variables,
14485 (splay_tree_key) decl);
14486 if (n && (n->value & GOVD_LASTPRIVATE_CONDITIONAL))
14487 for (tree c3 = omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
14488 OMP_CLAUSE_LASTPRIVATE);
14489 c3; c3 = omp_find_clause (OMP_CLAUSE_CHAIN (c3),
14490 OMP_CLAUSE_LASTPRIVATE))
14491 if (OMP_CLAUSE_DECL (c3) == decl)
14493 warning_at (OMP_CLAUSE_LOCATION (c3), OPT_Wopenmp,
14494 "conditional %<lastprivate%> on loop "
14495 "iterator %qD ignored", decl);
14496 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c3) = 0;
14497 n->value &= ~GOVD_LASTPRIVATE_CONDITIONAL;
14500 else
14501 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_PRIVATE | GOVD_SEEN);
14503 /* If DECL is not a gimple register, create a temporary variable to act
14504 as an iteration counter. This is valid, since DECL cannot be
14505 modified in the body of the loop. Similarly for any iteration vars
14506 in simd with collapse > 1 where the iterator vars must be
14507 lastprivate. And similarly for vars mentioned in allocate clauses. */
14508 if (orig_for_stmt != for_stmt)
14509 var = decl;
14510 else if (!is_gimple_reg (decl)
14511 || (ort == ORT_SIMD
14512 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) > 1)
14513 || (allocate_uids && allocate_uids->contains (decl)))
14515 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
14516 /* Make sure omp_add_variable is not called on it prematurely.
14517 We call it ourselves a few lines later. */
14518 gimplify_omp_ctxp = NULL;
14519 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
14520 gimplify_omp_ctxp = ctx;
14521 TREE_OPERAND (t, 0) = var;
14523 gimplify_seq_add_stmt (&for_body, gimple_build_assign (decl, var));
14525 if (ort == ORT_SIMD
14526 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
14528 c2 = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
14529 OMP_CLAUSE_LINEAR_NO_COPYIN (c2) = 1;
14530 OMP_CLAUSE_LINEAR_NO_COPYOUT (c2) = 1;
14531 OMP_CLAUSE_DECL (c2) = var;
14532 OMP_CLAUSE_CHAIN (c2) = OMP_FOR_CLAUSES (for_stmt);
14533 OMP_FOR_CLAUSES (for_stmt) = c2;
14534 omp_add_variable (gimplify_omp_ctxp, var,
14535 GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN);
14536 if (c == NULL_TREE)
14538 c = c2;
14539 c2 = NULL_TREE;
14542 else
14543 omp_add_variable (gimplify_omp_ctxp, var,
14544 GOVD_PRIVATE | GOVD_SEEN);
14546 else
14547 var = decl;
14549 gimplify_omp_ctxp->in_for_exprs = true;
14550 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
14552 tree lb = TREE_OPERAND (t, 1);
14553 tret = gimplify_expr (&TREE_VEC_ELT (lb, 1), &for_pre_body, NULL,
14554 is_gimple_val, fb_rvalue, false);
14555 ret = MIN (ret, tret);
14556 tret = gimplify_expr (&TREE_VEC_ELT (lb, 2), &for_pre_body, NULL,
14557 is_gimple_val, fb_rvalue, false);
14559 else
14560 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
14561 is_gimple_val, fb_rvalue, false);
14562 gimplify_omp_ctxp->in_for_exprs = false;
14563 ret = MIN (ret, tret);
14564 if (ret == GS_ERROR)
14565 return ret;
14567 /* Handle OMP_FOR_COND. */
14568 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
14569 gcc_assert (COMPARISON_CLASS_P (t));
14570 gcc_assert (TREE_OPERAND (t, 0) == decl);
14572 gimplify_omp_ctxp->in_for_exprs = true;
14573 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
14575 tree ub = TREE_OPERAND (t, 1);
14576 tret = gimplify_expr (&TREE_VEC_ELT (ub, 1), &for_pre_body, NULL,
14577 is_gimple_val, fb_rvalue, false);
14578 ret = MIN (ret, tret);
14579 tret = gimplify_expr (&TREE_VEC_ELT (ub, 2), &for_pre_body, NULL,
14580 is_gimple_val, fb_rvalue, false);
14582 else
14583 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
14584 is_gimple_val, fb_rvalue, false);
14585 gimplify_omp_ctxp->in_for_exprs = false;
14586 ret = MIN (ret, tret);
14588 /* Handle OMP_FOR_INCR. */
14589 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
14590 switch (TREE_CODE (t))
14592 case PREINCREMENT_EXPR:
14593 case POSTINCREMENT_EXPR:
14595 tree decl = TREE_OPERAND (t, 0);
14596 /* c_omp_for_incr_canonicalize_ptr() should have been
14597 called to massage things appropriately. */
14598 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
14600 if (orig_for_stmt != for_stmt)
14601 break;
14602 t = build_int_cst (TREE_TYPE (decl), 1);
14603 if (c)
14604 OMP_CLAUSE_LINEAR_STEP (c) = t;
14605 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
14606 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
14607 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
14608 break;
14611 case PREDECREMENT_EXPR:
14612 case POSTDECREMENT_EXPR:
14613 /* c_omp_for_incr_canonicalize_ptr() should have been
14614 called to massage things appropriately. */
14615 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
14616 if (orig_for_stmt != for_stmt)
14617 break;
14618 t = build_int_cst (TREE_TYPE (decl), -1);
14619 if (c)
14620 OMP_CLAUSE_LINEAR_STEP (c) = t;
14621 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
14622 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
14623 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
14624 break;
14626 case MODIFY_EXPR:
14627 gcc_assert (TREE_OPERAND (t, 0) == decl);
14628 TREE_OPERAND (t, 0) = var;
14630 t = TREE_OPERAND (t, 1);
14631 switch (TREE_CODE (t))
14633 case PLUS_EXPR:
14634 if (TREE_OPERAND (t, 1) == decl)
14636 TREE_OPERAND (t, 1) = TREE_OPERAND (t, 0);
14637 TREE_OPERAND (t, 0) = var;
14638 break;
14641 /* Fallthru. */
14642 case MINUS_EXPR:
14643 case POINTER_PLUS_EXPR:
14644 gcc_assert (TREE_OPERAND (t, 0) == decl);
14645 TREE_OPERAND (t, 0) = var;
14646 break;
14647 default:
14648 gcc_unreachable ();
14651 gimplify_omp_ctxp->in_for_exprs = true;
14652 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
14653 is_gimple_val, fb_rvalue, false);
14654 ret = MIN (ret, tret);
14655 if (c)
14657 tree step = TREE_OPERAND (t, 1);
14658 tree stept = TREE_TYPE (decl);
14659 if (POINTER_TYPE_P (stept))
14660 stept = sizetype;
14661 step = fold_convert (stept, step);
14662 if (TREE_CODE (t) == MINUS_EXPR)
14663 step = fold_build1 (NEGATE_EXPR, stept, step);
14664 OMP_CLAUSE_LINEAR_STEP (c) = step;
14665 if (step != TREE_OPERAND (t, 1))
14667 tret = gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c),
14668 &for_pre_body, NULL,
14669 is_gimple_val, fb_rvalue, false);
14670 ret = MIN (ret, tret);
14673 gimplify_omp_ctxp->in_for_exprs = false;
14674 break;
14676 default:
14677 gcc_unreachable ();
14680 if (c2)
14682 gcc_assert (c);
14683 OMP_CLAUSE_LINEAR_STEP (c2) = OMP_CLAUSE_LINEAR_STEP (c);
14686 if ((var != decl || collapse > 1 || tile) && orig_for_stmt == for_stmt)
14688 for (c = OMP_FOR_CLAUSES (for_stmt); c ; c = OMP_CLAUSE_CHAIN (c))
14689 if (((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
14690 && OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c) == NULL)
14691 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
14692 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)
14693 && OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c) == NULL))
14694 && OMP_CLAUSE_DECL (c) == decl)
14696 if (is_doacross && (collapse == 1 || i >= collapse))
14697 t = var;
14698 else
14700 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
14701 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
14702 gcc_assert (TREE_OPERAND (t, 0) == var);
14703 t = TREE_OPERAND (t, 1);
14704 gcc_assert (TREE_CODE (t) == PLUS_EXPR
14705 || TREE_CODE (t) == MINUS_EXPR
14706 || TREE_CODE (t) == POINTER_PLUS_EXPR);
14707 gcc_assert (TREE_OPERAND (t, 0) == var);
14708 t = build2 (TREE_CODE (t), TREE_TYPE (decl),
14709 is_doacross ? var : decl,
14710 TREE_OPERAND (t, 1));
14712 gimple_seq *seq;
14713 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE)
14714 seq = &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c);
14715 else
14716 seq = &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c);
14717 push_gimplify_context ();
14718 gimplify_assign (decl, t, seq);
14719 gimple *bind = NULL;
14720 if (gimplify_ctxp->temps)
14722 bind = gimple_build_bind (NULL_TREE, *seq, NULL_TREE);
14723 *seq = NULL;
14724 gimplify_seq_add_stmt (seq, bind);
14726 pop_gimplify_context (bind);
14729 if (OMP_FOR_NON_RECTANGULAR (for_stmt) && var != decl)
14730 for (int j = i + 1; j < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); j++)
14732 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), j);
14733 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
14734 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
14735 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
14736 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
14737 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), j);
14738 gcc_assert (COMPARISON_CLASS_P (t));
14739 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
14740 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
14741 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
14745 BITMAP_FREE (has_decl_expr);
14746 delete allocate_uids;
14748 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP
14749 || (loop_p && orig_for_stmt == for_stmt))
14751 push_gimplify_context ();
14752 if (TREE_CODE (OMP_FOR_BODY (orig_for_stmt)) != BIND_EXPR)
14754 OMP_FOR_BODY (orig_for_stmt)
14755 = build3 (BIND_EXPR, void_type_node, NULL,
14756 OMP_FOR_BODY (orig_for_stmt), NULL);
14757 TREE_SIDE_EFFECTS (OMP_FOR_BODY (orig_for_stmt)) = 1;
14761 gimple *g = gimplify_and_return_first (OMP_FOR_BODY (orig_for_stmt),
14762 &for_body);
14764 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP
14765 || (loop_p && orig_for_stmt == for_stmt))
14767 if (gimple_code (g) == GIMPLE_BIND)
14768 pop_gimplify_context (g);
14769 else
14770 pop_gimplify_context (NULL);
14773 if (orig_for_stmt != for_stmt)
14774 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
14776 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
14777 decl = TREE_OPERAND (t, 0);
14778 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
14779 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
14780 gimplify_omp_ctxp = ctx->outer_context;
14781 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
14782 gimplify_omp_ctxp = ctx;
14783 omp_add_variable (gimplify_omp_ctxp, var, GOVD_PRIVATE | GOVD_SEEN);
14784 TREE_OPERAND (t, 0) = var;
14785 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
14786 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
14787 TREE_OPERAND (TREE_OPERAND (t, 1), 0) = var;
14788 if (OMP_FOR_NON_RECTANGULAR (for_stmt))
14789 for (int j = i + 1;
14790 j < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); j++)
14792 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), j);
14793 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
14794 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
14795 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
14797 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
14798 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
14800 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), j);
14801 gcc_assert (COMPARISON_CLASS_P (t));
14802 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
14803 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
14805 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
14806 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
14811 gimplify_adjust_omp_clauses (pre_p, for_body,
14812 &OMP_FOR_CLAUSES (orig_for_stmt),
14813 TREE_CODE (orig_for_stmt));
14815 int kind;
14816 switch (TREE_CODE (orig_for_stmt))
14818 case OMP_FOR: kind = GF_OMP_FOR_KIND_FOR; break;
14819 case OMP_SIMD: kind = GF_OMP_FOR_KIND_SIMD; break;
14820 case OMP_DISTRIBUTE: kind = GF_OMP_FOR_KIND_DISTRIBUTE; break;
14821 case OMP_TASKLOOP: kind = GF_OMP_FOR_KIND_TASKLOOP; break;
14822 case OACC_LOOP: kind = GF_OMP_FOR_KIND_OACC_LOOP; break;
14823 default:
14824 gcc_unreachable ();
14826 if (loop_p && kind == GF_OMP_FOR_KIND_SIMD)
14828 gimplify_seq_add_seq (pre_p, for_pre_body);
14829 for_pre_body = NULL;
14831 gfor = gimple_build_omp_for (for_body, kind, OMP_FOR_CLAUSES (orig_for_stmt),
14832 TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)),
14833 for_pre_body);
14834 if (orig_for_stmt != for_stmt)
14835 gimple_omp_for_set_combined_p (gfor, true);
14836 if (gimplify_omp_ctxp
14837 && (gimplify_omp_ctxp->combined_loop
14838 || (gimplify_omp_ctxp->region_type == ORT_COMBINED_PARALLEL
14839 && gimplify_omp_ctxp->outer_context
14840 && gimplify_omp_ctxp->outer_context->combined_loop)))
14842 gimple_omp_for_set_combined_into_p (gfor, true);
14843 if (gimplify_omp_ctxp->combined_loop)
14844 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_SIMD);
14845 else
14846 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_FOR);
14849 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
14851 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
14852 gimple_omp_for_set_index (gfor, i, TREE_OPERAND (t, 0));
14853 gimple_omp_for_set_initial (gfor, i, TREE_OPERAND (t, 1));
14854 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
14855 gimple_omp_for_set_cond (gfor, i, TREE_CODE (t));
14856 gimple_omp_for_set_final (gfor, i, TREE_OPERAND (t, 1));
14857 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
14858 gimple_omp_for_set_incr (gfor, i, TREE_OPERAND (t, 1));
14861 /* OMP_TASKLOOP is gimplified as two GIMPLE_OMP_FOR taskloop
14862 constructs with GIMPLE_OMP_TASK sandwiched in between them.
14863 The outer taskloop stands for computing the number of iterations,
14864 counts for collapsed loops and holding taskloop specific clauses.
14865 The task construct stands for the effect of data sharing on the
14866 explicit task it creates and the inner taskloop stands for expansion
14867 of the static loop inside of the explicit task construct. */
14868 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
14870 tree *gfor_clauses_ptr = gimple_omp_for_clauses_ptr (gfor);
14871 tree task_clauses = NULL_TREE;
14872 tree c = *gfor_clauses_ptr;
14873 tree *gtask_clauses_ptr = &task_clauses;
14874 tree outer_for_clauses = NULL_TREE;
14875 tree *gforo_clauses_ptr = &outer_for_clauses;
14876 bitmap lastprivate_uids = NULL;
14877 if (omp_find_clause (c, OMP_CLAUSE_ALLOCATE))
14879 c = omp_find_clause (c, OMP_CLAUSE_LASTPRIVATE);
14880 if (c)
14882 lastprivate_uids = BITMAP_ALLOC (NULL);
14883 for (; c; c = omp_find_clause (OMP_CLAUSE_CHAIN (c),
14884 OMP_CLAUSE_LASTPRIVATE))
14885 bitmap_set_bit (lastprivate_uids,
14886 DECL_UID (OMP_CLAUSE_DECL (c)));
14888 c = *gfor_clauses_ptr;
14890 for (; c; c = OMP_CLAUSE_CHAIN (c))
14891 switch (OMP_CLAUSE_CODE (c))
14893 /* These clauses are allowed on task, move them there. */
14894 case OMP_CLAUSE_SHARED:
14895 case OMP_CLAUSE_FIRSTPRIVATE:
14896 case OMP_CLAUSE_DEFAULT:
14897 case OMP_CLAUSE_IF:
14898 case OMP_CLAUSE_UNTIED:
14899 case OMP_CLAUSE_FINAL:
14900 case OMP_CLAUSE_MERGEABLE:
14901 case OMP_CLAUSE_PRIORITY:
14902 case OMP_CLAUSE_REDUCTION:
14903 case OMP_CLAUSE_IN_REDUCTION:
14904 *gtask_clauses_ptr = c;
14905 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
14906 break;
14907 case OMP_CLAUSE_PRIVATE:
14908 if (OMP_CLAUSE_PRIVATE_TASKLOOP_IV (c))
14910 /* We want private on outer for and firstprivate
14911 on task. */
14912 *gtask_clauses_ptr
14913 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
14914 OMP_CLAUSE_FIRSTPRIVATE);
14915 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
14916 lang_hooks.decls.omp_finish_clause (*gtask_clauses_ptr, NULL,
14917 openacc);
14918 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
14919 *gforo_clauses_ptr = c;
14920 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
14922 else
14924 *gtask_clauses_ptr = c;
14925 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
14927 break;
14928 /* These clauses go into outer taskloop clauses. */
14929 case OMP_CLAUSE_GRAINSIZE:
14930 case OMP_CLAUSE_NUM_TASKS:
14931 case OMP_CLAUSE_NOGROUP:
14932 *gforo_clauses_ptr = c;
14933 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
14934 break;
14935 /* Collapse clause we duplicate on both taskloops. */
14936 case OMP_CLAUSE_COLLAPSE:
14937 *gfor_clauses_ptr = c;
14938 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
14939 *gforo_clauses_ptr = copy_node (c);
14940 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr);
14941 break;
14942 /* For lastprivate, keep the clause on inner taskloop, and add
14943 a shared clause on task. If the same decl is also firstprivate,
14944 add also firstprivate clause on the inner taskloop. */
14945 case OMP_CLAUSE_LASTPRIVATE:
14946 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c))
14948 /* For taskloop C++ lastprivate IVs, we want:
14949 1) private on outer taskloop
14950 2) firstprivate and shared on task
14951 3) lastprivate on inner taskloop */
14952 *gtask_clauses_ptr
14953 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
14954 OMP_CLAUSE_FIRSTPRIVATE);
14955 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
14956 lang_hooks.decls.omp_finish_clause (*gtask_clauses_ptr, NULL,
14957 openacc);
14958 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
14959 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c) = 1;
14960 *gforo_clauses_ptr = build_omp_clause (OMP_CLAUSE_LOCATION (c),
14961 OMP_CLAUSE_PRIVATE);
14962 OMP_CLAUSE_DECL (*gforo_clauses_ptr) = OMP_CLAUSE_DECL (c);
14963 OMP_CLAUSE_PRIVATE_TASKLOOP_IV (*gforo_clauses_ptr) = 1;
14964 TREE_TYPE (*gforo_clauses_ptr) = TREE_TYPE (c);
14965 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr);
14967 *gfor_clauses_ptr = c;
14968 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
14969 *gtask_clauses_ptr
14970 = build_omp_clause (OMP_CLAUSE_LOCATION (c), OMP_CLAUSE_SHARED);
14971 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
14972 if (OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
14973 OMP_CLAUSE_SHARED_FIRSTPRIVATE (*gtask_clauses_ptr) = 1;
14974 gtask_clauses_ptr
14975 = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
14976 break;
14977 /* Allocate clause we duplicate on task and inner taskloop
14978 if the decl is lastprivate, otherwise just put on task. */
14979 case OMP_CLAUSE_ALLOCATE:
14980 if (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
14981 && DECL_P (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)))
14983 /* Additionally, put firstprivate clause on task
14984 for the allocator if it is not constant. */
14985 *gtask_clauses_ptr
14986 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
14987 OMP_CLAUSE_FIRSTPRIVATE);
14988 OMP_CLAUSE_DECL (*gtask_clauses_ptr)
14989 = OMP_CLAUSE_ALLOCATE_ALLOCATOR (c);
14990 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
14992 if (lastprivate_uids
14993 && bitmap_bit_p (lastprivate_uids,
14994 DECL_UID (OMP_CLAUSE_DECL (c))))
14996 *gfor_clauses_ptr = c;
14997 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
14998 *gtask_clauses_ptr = copy_node (c);
14999 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
15001 else
15003 *gtask_clauses_ptr = c;
15004 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
15006 break;
15007 default:
15008 gcc_unreachable ();
15010 *gfor_clauses_ptr = NULL_TREE;
15011 *gtask_clauses_ptr = NULL_TREE;
15012 *gforo_clauses_ptr = NULL_TREE;
15013 BITMAP_FREE (lastprivate_uids);
15014 gimple_set_location (gfor, input_location);
15015 g = gimple_build_bind (NULL_TREE, gfor, NULL_TREE);
15016 g = gimple_build_omp_task (g, task_clauses, NULL_TREE, NULL_TREE,
15017 NULL_TREE, NULL_TREE, NULL_TREE);
15018 gimple_set_location (g, input_location);
15019 gimple_omp_task_set_taskloop_p (g, true);
15020 g = gimple_build_bind (NULL_TREE, g, NULL_TREE);
15021 gomp_for *gforo
15022 = gimple_build_omp_for (g, GF_OMP_FOR_KIND_TASKLOOP, outer_for_clauses,
15023 gimple_omp_for_collapse (gfor),
15024 gimple_omp_for_pre_body (gfor));
15025 gimple_omp_for_set_pre_body (gfor, NULL);
15026 gimple_omp_for_set_combined_p (gforo, true);
15027 gimple_omp_for_set_combined_into_p (gfor, true);
15028 for (i = 0; i < (int) gimple_omp_for_collapse (gfor); i++)
15030 tree type = TREE_TYPE (gimple_omp_for_index (gfor, i));
15031 tree v = create_tmp_var (type);
15032 gimple_omp_for_set_index (gforo, i, v);
15033 t = unshare_expr (gimple_omp_for_initial (gfor, i));
15034 gimple_omp_for_set_initial (gforo, i, t);
15035 gimple_omp_for_set_cond (gforo, i,
15036 gimple_omp_for_cond (gfor, i));
15037 t = unshare_expr (gimple_omp_for_final (gfor, i));
15038 gimple_omp_for_set_final (gforo, i, t);
15039 t = unshare_expr (gimple_omp_for_incr (gfor, i));
15040 gcc_assert (TREE_OPERAND (t, 0) == gimple_omp_for_index (gfor, i));
15041 TREE_OPERAND (t, 0) = v;
15042 gimple_omp_for_set_incr (gforo, i, t);
15043 t = build_omp_clause (input_location, OMP_CLAUSE_PRIVATE);
15044 OMP_CLAUSE_DECL (t) = v;
15045 OMP_CLAUSE_CHAIN (t) = gimple_omp_for_clauses (gforo);
15046 gimple_omp_for_set_clauses (gforo, t);
15047 if (OMP_FOR_NON_RECTANGULAR (for_stmt))
15049 tree *p1 = NULL, *p2 = NULL;
15050 t = gimple_omp_for_initial (gforo, i);
15051 if (TREE_CODE (t) == TREE_VEC)
15052 p1 = &TREE_VEC_ELT (t, 0);
15053 t = gimple_omp_for_final (gforo, i);
15054 if (TREE_CODE (t) == TREE_VEC)
15056 if (p1)
15057 p2 = &TREE_VEC_ELT (t, 0);
15058 else
15059 p1 = &TREE_VEC_ELT (t, 0);
15061 if (p1)
15063 int j;
15064 for (j = 0; j < i; j++)
15065 if (*p1 == gimple_omp_for_index (gfor, j))
15067 *p1 = gimple_omp_for_index (gforo, j);
15068 if (p2)
15069 *p2 = *p1;
15070 break;
15072 gcc_assert (j < i);
15076 gimplify_seq_add_stmt (pre_p, gforo);
15078 else
15079 gimplify_seq_add_stmt (pre_p, gfor);
15081 if (TREE_CODE (orig_for_stmt) == OMP_FOR)
15083 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
15084 unsigned lastprivate_conditional = 0;
15085 while (ctx
15086 && (ctx->region_type == ORT_TARGET_DATA
15087 || ctx->region_type == ORT_TASKGROUP))
15088 ctx = ctx->outer_context;
15089 if (ctx && (ctx->region_type & ORT_PARALLEL) != 0)
15090 for (tree c = gimple_omp_for_clauses (gfor);
15091 c; c = OMP_CLAUSE_CHAIN (c))
15092 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
15093 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
15094 ++lastprivate_conditional;
15095 if (lastprivate_conditional)
15097 struct omp_for_data fd;
15098 omp_extract_for_data (gfor, &fd, NULL);
15099 tree type = build_array_type_nelts (unsigned_type_for (fd.iter_type),
15100 lastprivate_conditional);
15101 tree var = create_tmp_var_raw (type);
15102 tree c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE__CONDTEMP_);
15103 OMP_CLAUSE_DECL (c) = var;
15104 OMP_CLAUSE_CHAIN (c) = gimple_omp_for_clauses (gfor);
15105 gimple_omp_for_set_clauses (gfor, c);
15106 omp_add_variable (ctx, var, GOVD_CONDTEMP | GOVD_SEEN);
15109 else if (TREE_CODE (orig_for_stmt) == OMP_SIMD)
15111 unsigned lastprivate_conditional = 0;
15112 for (tree c = gimple_omp_for_clauses (gfor); c; c = OMP_CLAUSE_CHAIN (c))
15113 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
15114 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
15115 ++lastprivate_conditional;
15116 if (lastprivate_conditional)
15118 struct omp_for_data fd;
15119 omp_extract_for_data (gfor, &fd, NULL);
15120 tree type = unsigned_type_for (fd.iter_type);
15121 while (lastprivate_conditional--)
15123 tree c = build_omp_clause (UNKNOWN_LOCATION,
15124 OMP_CLAUSE__CONDTEMP_);
15125 OMP_CLAUSE_DECL (c) = create_tmp_var (type);
15126 OMP_CLAUSE_CHAIN (c) = gimple_omp_for_clauses (gfor);
15127 gimple_omp_for_set_clauses (gfor, c);
15132 if (ret != GS_ALL_DONE)
15133 return GS_ERROR;
15134 *expr_p = NULL_TREE;
15135 return GS_ALL_DONE;
15138 /* Helper for gimplify_omp_loop, called through walk_tree. */
15140 static tree
15141 note_no_context_vars (tree *tp, int *, void *data)
15143 if (VAR_P (*tp)
15144 && DECL_CONTEXT (*tp) == NULL_TREE
15145 && !is_global_var (*tp))
15147 vec<tree> *d = (vec<tree> *) data;
15148 d->safe_push (*tp);
15149 DECL_CONTEXT (*tp) = current_function_decl;
15151 return NULL_TREE;
15154 /* Gimplify the gross structure of an OMP_LOOP statement. */
15156 static enum gimplify_status
15157 gimplify_omp_loop (tree *expr_p, gimple_seq *pre_p)
15159 tree for_stmt = *expr_p;
15160 tree clauses = OMP_FOR_CLAUSES (for_stmt);
15161 struct gimplify_omp_ctx *octx = gimplify_omp_ctxp;
15162 enum omp_clause_bind_kind kind = OMP_CLAUSE_BIND_THREAD;
15163 int i;
15165 /* If order is not present, the behavior is as if order(concurrent)
15166 appeared. */
15167 tree order = omp_find_clause (clauses, OMP_CLAUSE_ORDER);
15168 if (order == NULL_TREE)
15170 order = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_ORDER);
15171 OMP_CLAUSE_CHAIN (order) = clauses;
15172 OMP_FOR_CLAUSES (for_stmt) = clauses = order;
15175 tree bind = omp_find_clause (clauses, OMP_CLAUSE_BIND);
15176 if (bind == NULL_TREE)
15178 if (!flag_openmp) /* flag_openmp_simd */
15180 else if (octx && (octx->region_type & ORT_TEAMS) != 0)
15181 kind = OMP_CLAUSE_BIND_TEAMS;
15182 else if (octx && (octx->region_type & ORT_PARALLEL) != 0)
15183 kind = OMP_CLAUSE_BIND_PARALLEL;
15184 else
15186 for (; octx; octx = octx->outer_context)
15188 if ((octx->region_type & ORT_ACC) != 0
15189 || octx->region_type == ORT_NONE
15190 || octx->region_type == ORT_IMPLICIT_TARGET)
15191 continue;
15192 break;
15194 if (octx == NULL && !in_omp_construct)
15195 error_at (EXPR_LOCATION (for_stmt),
15196 "%<bind%> clause not specified on a %<loop%> "
15197 "construct not nested inside another OpenMP construct");
15199 bind = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_BIND);
15200 OMP_CLAUSE_CHAIN (bind) = clauses;
15201 OMP_CLAUSE_BIND_KIND (bind) = kind;
15202 OMP_FOR_CLAUSES (for_stmt) = bind;
15204 else
15205 switch (OMP_CLAUSE_BIND_KIND (bind))
15207 case OMP_CLAUSE_BIND_THREAD:
15208 break;
15209 case OMP_CLAUSE_BIND_PARALLEL:
15210 if (!flag_openmp) /* flag_openmp_simd */
15212 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
15213 break;
15215 for (; octx; octx = octx->outer_context)
15216 if (octx->region_type == ORT_SIMD
15217 && omp_find_clause (octx->clauses, OMP_CLAUSE_BIND) == NULL_TREE)
15219 error_at (EXPR_LOCATION (for_stmt),
15220 "%<bind(parallel)%> on a %<loop%> construct nested "
15221 "inside %<simd%> construct");
15222 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
15223 break;
15225 kind = OMP_CLAUSE_BIND_PARALLEL;
15226 break;
15227 case OMP_CLAUSE_BIND_TEAMS:
15228 if (!flag_openmp) /* flag_openmp_simd */
15230 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
15231 break;
15233 if ((octx
15234 && octx->region_type != ORT_IMPLICIT_TARGET
15235 && octx->region_type != ORT_NONE
15236 && (octx->region_type & ORT_TEAMS) == 0)
15237 || in_omp_construct)
15239 error_at (EXPR_LOCATION (for_stmt),
15240 "%<bind(teams)%> on a %<loop%> region not strictly "
15241 "nested inside of a %<teams%> region");
15242 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
15243 break;
15245 kind = OMP_CLAUSE_BIND_TEAMS;
15246 break;
15247 default:
15248 gcc_unreachable ();
15251 for (tree *pc = &OMP_FOR_CLAUSES (for_stmt); *pc; )
15252 switch (OMP_CLAUSE_CODE (*pc))
15254 case OMP_CLAUSE_REDUCTION:
15255 if (OMP_CLAUSE_REDUCTION_INSCAN (*pc))
15257 error_at (OMP_CLAUSE_LOCATION (*pc),
15258 "%<inscan%> %<reduction%> clause on "
15259 "%qs construct", "loop");
15260 OMP_CLAUSE_REDUCTION_INSCAN (*pc) = 0;
15262 if (OMP_CLAUSE_REDUCTION_TASK (*pc))
15264 error_at (OMP_CLAUSE_LOCATION (*pc),
15265 "invalid %<task%> reduction modifier on construct "
15266 "other than %<parallel%>, %qs or %<sections%>",
15267 lang_GNU_Fortran () ? "do" : "for");
15268 OMP_CLAUSE_REDUCTION_TASK (*pc) = 0;
15270 pc = &OMP_CLAUSE_CHAIN (*pc);
15271 break;
15272 case OMP_CLAUSE_LASTPRIVATE:
15273 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
15275 tree t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
15276 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
15277 if (OMP_CLAUSE_DECL (*pc) == TREE_OPERAND (t, 0))
15278 break;
15279 if (OMP_FOR_ORIG_DECLS (for_stmt)
15280 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt),
15281 i)) == TREE_LIST
15282 && TREE_PURPOSE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt),
15283 i)))
15285 tree orig = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
15286 if (OMP_CLAUSE_DECL (*pc) == TREE_PURPOSE (orig))
15287 break;
15290 if (i == TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)))
15292 error_at (OMP_CLAUSE_LOCATION (*pc),
15293 "%<lastprivate%> clause on a %<loop%> construct refers "
15294 "to a variable %qD which is not the loop iterator",
15295 OMP_CLAUSE_DECL (*pc));
15296 *pc = OMP_CLAUSE_CHAIN (*pc);
15297 break;
15299 pc = &OMP_CLAUSE_CHAIN (*pc);
15300 break;
15301 default:
15302 pc = &OMP_CLAUSE_CHAIN (*pc);
15303 break;
15306 TREE_SET_CODE (for_stmt, OMP_SIMD);
15308 int last;
15309 switch (kind)
15311 case OMP_CLAUSE_BIND_THREAD: last = 0; break;
15312 case OMP_CLAUSE_BIND_PARALLEL: last = 1; break;
15313 case OMP_CLAUSE_BIND_TEAMS: last = 2; break;
15315 for (int pass = 1; pass <= last; pass++)
15317 if (pass == 2)
15319 tree bind = build3 (BIND_EXPR, void_type_node, NULL, NULL,
15320 make_node (BLOCK));
15321 append_to_statement_list (*expr_p, &BIND_EXPR_BODY (bind));
15322 *expr_p = make_node (OMP_PARALLEL);
15323 TREE_TYPE (*expr_p) = void_type_node;
15324 OMP_PARALLEL_BODY (*expr_p) = bind;
15325 OMP_PARALLEL_COMBINED (*expr_p) = 1;
15326 SET_EXPR_LOCATION (*expr_p, EXPR_LOCATION (for_stmt));
15327 tree *pc = &OMP_PARALLEL_CLAUSES (*expr_p);
15328 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
15329 if (OMP_FOR_ORIG_DECLS (for_stmt)
15330 && (TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i))
15331 == TREE_LIST))
15333 tree elt = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
15334 if (TREE_PURPOSE (elt) && TREE_VALUE (elt))
15336 *pc = build_omp_clause (UNKNOWN_LOCATION,
15337 OMP_CLAUSE_FIRSTPRIVATE);
15338 OMP_CLAUSE_DECL (*pc) = TREE_VALUE (elt);
15339 pc = &OMP_CLAUSE_CHAIN (*pc);
15343 tree t = make_node (pass == 2 ? OMP_DISTRIBUTE : OMP_FOR);
15344 tree *pc = &OMP_FOR_CLAUSES (t);
15345 TREE_TYPE (t) = void_type_node;
15346 OMP_FOR_BODY (t) = *expr_p;
15347 SET_EXPR_LOCATION (t, EXPR_LOCATION (for_stmt));
15348 for (tree c = OMP_FOR_CLAUSES (for_stmt); c; c = OMP_CLAUSE_CHAIN (c))
15349 switch (OMP_CLAUSE_CODE (c))
15351 case OMP_CLAUSE_BIND:
15352 case OMP_CLAUSE_ORDER:
15353 case OMP_CLAUSE_COLLAPSE:
15354 *pc = copy_node (c);
15355 pc = &OMP_CLAUSE_CHAIN (*pc);
15356 break;
15357 case OMP_CLAUSE_PRIVATE:
15358 case OMP_CLAUSE_FIRSTPRIVATE:
15359 /* Only needed on innermost. */
15360 break;
15361 case OMP_CLAUSE_LASTPRIVATE:
15362 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c) && pass != last)
15364 *pc = build_omp_clause (OMP_CLAUSE_LOCATION (c),
15365 OMP_CLAUSE_FIRSTPRIVATE);
15366 OMP_CLAUSE_DECL (*pc) = OMP_CLAUSE_DECL (c);
15367 lang_hooks.decls.omp_finish_clause (*pc, NULL, false);
15368 pc = &OMP_CLAUSE_CHAIN (*pc);
15370 *pc = copy_node (c);
15371 OMP_CLAUSE_LASTPRIVATE_STMT (*pc) = NULL_TREE;
15372 TREE_TYPE (*pc) = unshare_expr (TREE_TYPE (c));
15373 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c))
15375 if (pass != last)
15376 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (*pc) = 1;
15377 else
15378 lang_hooks.decls.omp_finish_clause (*pc, NULL, false);
15379 OMP_CLAUSE_LASTPRIVATE_LOOP_IV (*pc) = 0;
15381 pc = &OMP_CLAUSE_CHAIN (*pc);
15382 break;
15383 case OMP_CLAUSE_REDUCTION:
15384 *pc = copy_node (c);
15385 OMP_CLAUSE_DECL (*pc) = unshare_expr (OMP_CLAUSE_DECL (c));
15386 TREE_TYPE (*pc) = unshare_expr (TREE_TYPE (c));
15387 if (OMP_CLAUSE_REDUCTION_PLACEHOLDER (*pc))
15389 auto_vec<tree> no_context_vars;
15390 int walk_subtrees = 0;
15391 note_no_context_vars (&OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
15392 &walk_subtrees, &no_context_vars);
15393 if (tree p = OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c))
15394 note_no_context_vars (&p, &walk_subtrees, &no_context_vars);
15395 walk_tree_without_duplicates (&OMP_CLAUSE_REDUCTION_INIT (c),
15396 note_no_context_vars,
15397 &no_context_vars);
15398 walk_tree_without_duplicates (&OMP_CLAUSE_REDUCTION_MERGE (c),
15399 note_no_context_vars,
15400 &no_context_vars);
15402 OMP_CLAUSE_REDUCTION_PLACEHOLDER (*pc)
15403 = copy_node (OMP_CLAUSE_REDUCTION_PLACEHOLDER (c));
15404 if (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (*pc))
15405 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (*pc)
15406 = copy_node (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c));
15408 hash_map<tree, tree> decl_map;
15409 decl_map.put (OMP_CLAUSE_DECL (c), OMP_CLAUSE_DECL (c));
15410 decl_map.put (OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
15411 OMP_CLAUSE_REDUCTION_PLACEHOLDER (*pc));
15412 if (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (*pc))
15413 decl_map.put (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
15414 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (*pc));
15416 copy_body_data id;
15417 memset (&id, 0, sizeof (id));
15418 id.src_fn = current_function_decl;
15419 id.dst_fn = current_function_decl;
15420 id.src_cfun = cfun;
15421 id.decl_map = &decl_map;
15422 id.copy_decl = copy_decl_no_change;
15423 id.transform_call_graph_edges = CB_CGE_DUPLICATE;
15424 id.transform_new_cfg = true;
15425 id.transform_return_to_modify = false;
15426 id.eh_lp_nr = 0;
15427 walk_tree (&OMP_CLAUSE_REDUCTION_INIT (*pc), copy_tree_body_r,
15428 &id, NULL);
15429 walk_tree (&OMP_CLAUSE_REDUCTION_MERGE (*pc), copy_tree_body_r,
15430 &id, NULL);
15432 for (tree d : no_context_vars)
15434 DECL_CONTEXT (d) = NULL_TREE;
15435 DECL_CONTEXT (*decl_map.get (d)) = NULL_TREE;
15438 else
15440 OMP_CLAUSE_REDUCTION_INIT (*pc)
15441 = unshare_expr (OMP_CLAUSE_REDUCTION_INIT (c));
15442 OMP_CLAUSE_REDUCTION_MERGE (*pc)
15443 = unshare_expr (OMP_CLAUSE_REDUCTION_MERGE (c));
15445 pc = &OMP_CLAUSE_CHAIN (*pc);
15446 break;
15447 default:
15448 gcc_unreachable ();
15450 *pc = NULL_TREE;
15451 *expr_p = t;
15453 return gimplify_expr (expr_p, pre_p, NULL, is_gimple_stmt, fb_none);
15457 /* Helper function of optimize_target_teams, find OMP_TEAMS inside
15458 of OMP_TARGET's body. */
15460 static tree
15461 find_omp_teams (tree *tp, int *walk_subtrees, void *)
15463 *walk_subtrees = 0;
15464 switch (TREE_CODE (*tp))
15466 case OMP_TEAMS:
15467 return *tp;
15468 case BIND_EXPR:
15469 case STATEMENT_LIST:
15470 *walk_subtrees = 1;
15471 break;
15472 default:
15473 break;
15475 return NULL_TREE;
15478 /* Helper function of optimize_target_teams, determine if the expression
15479 can be computed safely before the target construct on the host. */
15481 static tree
15482 computable_teams_clause (tree *tp, int *walk_subtrees, void *)
15484 splay_tree_node n;
15486 if (TYPE_P (*tp))
15488 *walk_subtrees = 0;
15489 return NULL_TREE;
15491 switch (TREE_CODE (*tp))
15493 case VAR_DECL:
15494 case PARM_DECL:
15495 case RESULT_DECL:
15496 *walk_subtrees = 0;
15497 if (error_operand_p (*tp)
15498 || !INTEGRAL_TYPE_P (TREE_TYPE (*tp))
15499 || DECL_HAS_VALUE_EXPR_P (*tp)
15500 || DECL_THREAD_LOCAL_P (*tp)
15501 || TREE_SIDE_EFFECTS (*tp)
15502 || TREE_THIS_VOLATILE (*tp))
15503 return *tp;
15504 if (is_global_var (*tp)
15505 && (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (*tp))
15506 || lookup_attribute ("omp declare target link",
15507 DECL_ATTRIBUTES (*tp))))
15508 return *tp;
15509 if (VAR_P (*tp)
15510 && !DECL_SEEN_IN_BIND_EXPR_P (*tp)
15511 && !is_global_var (*tp)
15512 && decl_function_context (*tp) == current_function_decl)
15513 return *tp;
15514 n = splay_tree_lookup (gimplify_omp_ctxp->variables,
15515 (splay_tree_key) *tp);
15516 if (n == NULL)
15518 if (gimplify_omp_ctxp->defaultmap[GDMK_SCALAR] & GOVD_FIRSTPRIVATE)
15519 return NULL_TREE;
15520 return *tp;
15522 else if (n->value & GOVD_LOCAL)
15523 return *tp;
15524 else if (n->value & GOVD_FIRSTPRIVATE)
15525 return NULL_TREE;
15526 else if ((n->value & (GOVD_MAP | GOVD_MAP_ALWAYS_TO))
15527 == (GOVD_MAP | GOVD_MAP_ALWAYS_TO))
15528 return NULL_TREE;
15529 return *tp;
15530 case INTEGER_CST:
15531 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp)))
15532 return *tp;
15533 return NULL_TREE;
15534 case TARGET_EXPR:
15535 if (TARGET_EXPR_INITIAL (*tp)
15536 || TREE_CODE (TARGET_EXPR_SLOT (*tp)) != VAR_DECL)
15537 return *tp;
15538 return computable_teams_clause (&TARGET_EXPR_SLOT (*tp),
15539 walk_subtrees, NULL);
15540 /* Allow some reasonable subset of integral arithmetics. */
15541 case PLUS_EXPR:
15542 case MINUS_EXPR:
15543 case MULT_EXPR:
15544 case TRUNC_DIV_EXPR:
15545 case CEIL_DIV_EXPR:
15546 case FLOOR_DIV_EXPR:
15547 case ROUND_DIV_EXPR:
15548 case TRUNC_MOD_EXPR:
15549 case CEIL_MOD_EXPR:
15550 case FLOOR_MOD_EXPR:
15551 case ROUND_MOD_EXPR:
15552 case RDIV_EXPR:
15553 case EXACT_DIV_EXPR:
15554 case MIN_EXPR:
15555 case MAX_EXPR:
15556 case LSHIFT_EXPR:
15557 case RSHIFT_EXPR:
15558 case BIT_IOR_EXPR:
15559 case BIT_XOR_EXPR:
15560 case BIT_AND_EXPR:
15561 case NEGATE_EXPR:
15562 case ABS_EXPR:
15563 case BIT_NOT_EXPR:
15564 case NON_LVALUE_EXPR:
15565 CASE_CONVERT:
15566 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp)))
15567 return *tp;
15568 return NULL_TREE;
15569 /* And disallow anything else, except for comparisons. */
15570 default:
15571 if (COMPARISON_CLASS_P (*tp))
15572 return NULL_TREE;
15573 return *tp;
15577 /* Try to determine if the num_teams and/or thread_limit expressions
15578 can have their values determined already before entering the
15579 target construct.
15580 INTEGER_CSTs trivially are,
15581 integral decls that are firstprivate (explicitly or implicitly)
15582 or explicitly map(always, to:) or map(always, tofrom:) on the target
15583 region too, and expressions involving simple arithmetics on those
15584 too, function calls are not ok, dereferencing something neither etc.
15585 Add NUM_TEAMS and THREAD_LIMIT clauses to the OMP_CLAUSES of
15586 EXPR based on what we find:
15587 0 stands for clause not specified at all, use implementation default
15588 -1 stands for value that can't be determined easily before entering
15589 the target construct.
15590 -2 means that no explicit teams construct was specified
15591 If teams construct is not present at all, use 1 for num_teams
15592 and 0 for thread_limit (only one team is involved, and the thread
15593 limit is implementation defined. */
15595 static void
15596 optimize_target_teams (tree target, gimple_seq *pre_p)
15598 tree body = OMP_BODY (target);
15599 tree teams = walk_tree (&body, find_omp_teams, NULL, NULL);
15600 tree num_teams_lower = NULL_TREE;
15601 tree num_teams_upper = integer_zero_node;
15602 tree thread_limit = integer_zero_node;
15603 location_t num_teams_loc = EXPR_LOCATION (target);
15604 location_t thread_limit_loc = EXPR_LOCATION (target);
15605 tree c, *p, expr;
15606 struct gimplify_omp_ctx *target_ctx = gimplify_omp_ctxp;
15608 if (teams == NULL_TREE)
15609 num_teams_upper = build_int_cst (integer_type_node, -2);
15610 else
15611 for (c = OMP_TEAMS_CLAUSES (teams); c; c = OMP_CLAUSE_CHAIN (c))
15613 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_NUM_TEAMS)
15615 p = &num_teams_upper;
15616 num_teams_loc = OMP_CLAUSE_LOCATION (c);
15617 if (OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c))
15619 expr = OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c);
15620 if (TREE_CODE (expr) == INTEGER_CST)
15621 num_teams_lower = expr;
15622 else if (walk_tree (&expr, computable_teams_clause,
15623 NULL, NULL))
15624 num_teams_lower = integer_minus_one_node;
15625 else
15627 num_teams_lower = expr;
15628 gimplify_omp_ctxp = gimplify_omp_ctxp->outer_context;
15629 if (gimplify_expr (&num_teams_lower, pre_p, NULL,
15630 is_gimple_val, fb_rvalue, false)
15631 == GS_ERROR)
15633 gimplify_omp_ctxp = target_ctx;
15634 num_teams_lower = integer_minus_one_node;
15636 else
15638 gimplify_omp_ctxp = target_ctx;
15639 if (!DECL_P (expr) && TREE_CODE (expr) != TARGET_EXPR)
15640 OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c)
15641 = num_teams_lower;
15646 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_THREAD_LIMIT)
15648 p = &thread_limit;
15649 thread_limit_loc = OMP_CLAUSE_LOCATION (c);
15651 else
15652 continue;
15653 expr = OMP_CLAUSE_OPERAND (c, 0);
15654 if (TREE_CODE (expr) == INTEGER_CST)
15656 *p = expr;
15657 continue;
15659 if (walk_tree (&expr, computable_teams_clause, NULL, NULL))
15661 *p = integer_minus_one_node;
15662 continue;
15664 *p = expr;
15665 gimplify_omp_ctxp = gimplify_omp_ctxp->outer_context;
15666 if (gimplify_expr (p, pre_p, NULL, is_gimple_val, fb_rvalue, false)
15667 == GS_ERROR)
15669 gimplify_omp_ctxp = target_ctx;
15670 *p = integer_minus_one_node;
15671 continue;
15673 gimplify_omp_ctxp = target_ctx;
15674 if (!DECL_P (expr) && TREE_CODE (expr) != TARGET_EXPR)
15675 OMP_CLAUSE_OPERAND (c, 0) = *p;
15677 if (!omp_find_clause (OMP_TARGET_CLAUSES (target), OMP_CLAUSE_THREAD_LIMIT))
15679 c = build_omp_clause (thread_limit_loc, OMP_CLAUSE_THREAD_LIMIT);
15680 OMP_CLAUSE_THREAD_LIMIT_EXPR (c) = thread_limit;
15681 OMP_CLAUSE_CHAIN (c) = OMP_TARGET_CLAUSES (target);
15682 OMP_TARGET_CLAUSES (target) = c;
15684 c = build_omp_clause (num_teams_loc, OMP_CLAUSE_NUM_TEAMS);
15685 OMP_CLAUSE_NUM_TEAMS_UPPER_EXPR (c) = num_teams_upper;
15686 OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c) = num_teams_lower;
15687 OMP_CLAUSE_CHAIN (c) = OMP_TARGET_CLAUSES (target);
15688 OMP_TARGET_CLAUSES (target) = c;
15691 /* Gimplify the gross structure of several OMP constructs. */
15693 static void
15694 gimplify_omp_workshare (tree *expr_p, gimple_seq *pre_p)
15696 tree expr = *expr_p;
15697 gimple *stmt;
15698 gimple_seq body = NULL;
15699 enum omp_region_type ort;
15701 switch (TREE_CODE (expr))
15703 case OMP_SECTIONS:
15704 case OMP_SINGLE:
15705 ort = ORT_WORKSHARE;
15706 break;
15707 case OMP_SCOPE:
15708 ort = ORT_TASKGROUP;
15709 break;
15710 case OMP_TARGET:
15711 ort = OMP_TARGET_COMBINED (expr) ? ORT_COMBINED_TARGET : ORT_TARGET;
15712 break;
15713 case OACC_KERNELS:
15714 ort = ORT_ACC_KERNELS;
15715 break;
15716 case OACC_PARALLEL:
15717 ort = ORT_ACC_PARALLEL;
15718 break;
15719 case OACC_SERIAL:
15720 ort = ORT_ACC_SERIAL;
15721 break;
15722 case OACC_DATA:
15723 ort = ORT_ACC_DATA;
15724 break;
15725 case OMP_TARGET_DATA:
15726 ort = ORT_TARGET_DATA;
15727 break;
15728 case OMP_TEAMS:
15729 ort = OMP_TEAMS_COMBINED (expr) ? ORT_COMBINED_TEAMS : ORT_TEAMS;
15730 if (gimplify_omp_ctxp == NULL
15731 || gimplify_omp_ctxp->region_type == ORT_IMPLICIT_TARGET)
15732 ort = (enum omp_region_type) (ort | ORT_HOST_TEAMS);
15733 break;
15734 case OACC_HOST_DATA:
15735 ort = ORT_ACC_HOST_DATA;
15736 break;
15737 default:
15738 gcc_unreachable ();
15741 bool save_in_omp_construct = in_omp_construct;
15742 if ((ort & ORT_ACC) == 0)
15743 in_omp_construct = false;
15744 gimplify_scan_omp_clauses (&OMP_CLAUSES (expr), pre_p, ort,
15745 TREE_CODE (expr));
15746 if (TREE_CODE (expr) == OMP_TARGET)
15747 optimize_target_teams (expr, pre_p);
15748 if ((ort & (ORT_TARGET | ORT_TARGET_DATA)) != 0
15749 || (ort & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
15751 push_gimplify_context ();
15752 gimple *g = gimplify_and_return_first (OMP_BODY (expr), &body);
15753 if (gimple_code (g) == GIMPLE_BIND)
15754 pop_gimplify_context (g);
15755 else
15756 pop_gimplify_context (NULL);
15757 if ((ort & ORT_TARGET_DATA) != 0)
15759 enum built_in_function end_ix;
15760 switch (TREE_CODE (expr))
15762 case OACC_DATA:
15763 case OACC_HOST_DATA:
15764 end_ix = BUILT_IN_GOACC_DATA_END;
15765 break;
15766 case OMP_TARGET_DATA:
15767 end_ix = BUILT_IN_GOMP_TARGET_END_DATA;
15768 break;
15769 default:
15770 gcc_unreachable ();
15772 tree fn = builtin_decl_explicit (end_ix);
15773 g = gimple_build_call (fn, 0);
15774 gimple_seq cleanup = NULL;
15775 gimple_seq_add_stmt (&cleanup, g);
15776 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
15777 body = NULL;
15778 gimple_seq_add_stmt (&body, g);
15781 else
15782 gimplify_and_add (OMP_BODY (expr), &body);
15783 gimplify_adjust_omp_clauses (pre_p, body, &OMP_CLAUSES (expr),
15784 TREE_CODE (expr));
15785 in_omp_construct = save_in_omp_construct;
15787 switch (TREE_CODE (expr))
15789 case OACC_DATA:
15790 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_DATA,
15791 OMP_CLAUSES (expr));
15792 break;
15793 case OACC_HOST_DATA:
15794 if (omp_find_clause (OMP_CLAUSES (expr), OMP_CLAUSE_IF_PRESENT))
15796 for (tree c = OMP_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
15797 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_USE_DEVICE_PTR)
15798 OMP_CLAUSE_USE_DEVICE_PTR_IF_PRESENT (c) = 1;
15801 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_HOST_DATA,
15802 OMP_CLAUSES (expr));
15803 break;
15804 case OACC_KERNELS:
15805 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_KERNELS,
15806 OMP_CLAUSES (expr));
15807 break;
15808 case OACC_PARALLEL:
15809 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_PARALLEL,
15810 OMP_CLAUSES (expr));
15811 break;
15812 case OACC_SERIAL:
15813 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_SERIAL,
15814 OMP_CLAUSES (expr));
15815 break;
15816 case OMP_SECTIONS:
15817 stmt = gimple_build_omp_sections (body, OMP_CLAUSES (expr));
15818 break;
15819 case OMP_SINGLE:
15820 stmt = gimple_build_omp_single (body, OMP_CLAUSES (expr));
15821 break;
15822 case OMP_SCOPE:
15823 stmt = gimple_build_omp_scope (body, OMP_CLAUSES (expr));
15824 break;
15825 case OMP_TARGET:
15826 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_REGION,
15827 OMP_CLAUSES (expr));
15828 break;
15829 case OMP_TARGET_DATA:
15830 /* Put use_device_{ptr,addr} clauses last, as map clauses are supposed
15831 to be evaluated before the use_device_{ptr,addr} clauses if they
15832 refer to the same variables. */
15834 tree use_device_clauses;
15835 tree *pc, *uc = &use_device_clauses;
15836 for (pc = &OMP_CLAUSES (expr); *pc; )
15837 if (OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_USE_DEVICE_PTR
15838 || OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_USE_DEVICE_ADDR)
15840 *uc = *pc;
15841 *pc = OMP_CLAUSE_CHAIN (*pc);
15842 uc = &OMP_CLAUSE_CHAIN (*uc);
15844 else
15845 pc = &OMP_CLAUSE_CHAIN (*pc);
15846 *uc = NULL_TREE;
15847 *pc = use_device_clauses;
15848 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_DATA,
15849 OMP_CLAUSES (expr));
15851 break;
15852 case OMP_TEAMS:
15853 stmt = gimple_build_omp_teams (body, OMP_CLAUSES (expr));
15854 if ((ort & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
15855 gimple_omp_teams_set_host (as_a <gomp_teams *> (stmt), true);
15856 break;
15857 default:
15858 gcc_unreachable ();
15861 gimplify_seq_add_stmt (pre_p, stmt);
15862 *expr_p = NULL_TREE;
15865 /* Gimplify the gross structure of OpenACC enter/exit data, update, and OpenMP
15866 target update constructs. */
15868 static void
15869 gimplify_omp_target_update (tree *expr_p, gimple_seq *pre_p)
15871 tree expr = *expr_p;
15872 int kind;
15873 gomp_target *stmt;
15874 enum omp_region_type ort = ORT_WORKSHARE;
15876 switch (TREE_CODE (expr))
15878 case OACC_ENTER_DATA:
15879 kind = GF_OMP_TARGET_KIND_OACC_ENTER_DATA;
15880 ort = ORT_ACC;
15881 break;
15882 case OACC_EXIT_DATA:
15883 kind = GF_OMP_TARGET_KIND_OACC_EXIT_DATA;
15884 ort = ORT_ACC;
15885 break;
15886 case OACC_UPDATE:
15887 kind = GF_OMP_TARGET_KIND_OACC_UPDATE;
15888 ort = ORT_ACC;
15889 break;
15890 case OMP_TARGET_UPDATE:
15891 kind = GF_OMP_TARGET_KIND_UPDATE;
15892 break;
15893 case OMP_TARGET_ENTER_DATA:
15894 kind = GF_OMP_TARGET_KIND_ENTER_DATA;
15895 break;
15896 case OMP_TARGET_EXIT_DATA:
15897 kind = GF_OMP_TARGET_KIND_EXIT_DATA;
15898 break;
15899 default:
15900 gcc_unreachable ();
15902 gimplify_scan_omp_clauses (&OMP_STANDALONE_CLAUSES (expr), pre_p,
15903 ort, TREE_CODE (expr));
15904 gimplify_adjust_omp_clauses (pre_p, NULL, &OMP_STANDALONE_CLAUSES (expr),
15905 TREE_CODE (expr));
15906 if (TREE_CODE (expr) == OACC_UPDATE
15907 && omp_find_clause (OMP_STANDALONE_CLAUSES (expr),
15908 OMP_CLAUSE_IF_PRESENT))
15910 /* The runtime uses GOMP_MAP_{TO,FROM} to denote the if_present
15911 clause. */
15912 for (tree c = OMP_STANDALONE_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
15913 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP)
15914 switch (OMP_CLAUSE_MAP_KIND (c))
15916 case GOMP_MAP_FORCE_TO:
15917 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_TO);
15918 break;
15919 case GOMP_MAP_FORCE_FROM:
15920 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FROM);
15921 break;
15922 default:
15923 break;
15926 else if (TREE_CODE (expr) == OACC_EXIT_DATA
15927 && omp_find_clause (OMP_STANDALONE_CLAUSES (expr),
15928 OMP_CLAUSE_FINALIZE))
15930 /* Use GOMP_MAP_DELETE/GOMP_MAP_FORCE_FROM to denote "finalize"
15931 semantics. */
15932 bool have_clause = false;
15933 for (tree c = OMP_STANDALONE_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
15934 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP)
15935 switch (OMP_CLAUSE_MAP_KIND (c))
15937 case GOMP_MAP_FROM:
15938 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FORCE_FROM);
15939 have_clause = true;
15940 break;
15941 case GOMP_MAP_RELEASE:
15942 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_DELETE);
15943 have_clause = true;
15944 break;
15945 case GOMP_MAP_TO_PSET:
15946 /* Fortran arrays with descriptors must map that descriptor when
15947 doing standalone "attach" operations (in OpenACC). In that
15948 case GOMP_MAP_TO_PSET appears by itself with no preceding
15949 clause (see trans-openmp.cc:gfc_trans_omp_clauses). */
15950 break;
15951 case GOMP_MAP_POINTER:
15952 /* TODO PR92929: we may see these here, but they'll always follow
15953 one of the clauses above, and will be handled by libgomp as
15954 one group, so no handling required here. */
15955 gcc_assert (have_clause);
15956 break;
15957 case GOMP_MAP_DETACH:
15958 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FORCE_DETACH);
15959 have_clause = false;
15960 break;
15961 case GOMP_MAP_STRUCT:
15962 have_clause = false;
15963 break;
15964 default:
15965 gcc_unreachable ();
15968 stmt = gimple_build_omp_target (NULL, kind, OMP_STANDALONE_CLAUSES (expr));
15970 gimplify_seq_add_stmt (pre_p, stmt);
15971 *expr_p = NULL_TREE;
15974 /* A subroutine of gimplify_omp_atomic. The front end is supposed to have
15975 stabilized the lhs of the atomic operation as *ADDR. Return true if
15976 EXPR is this stabilized form. */
15978 static bool
15979 goa_lhs_expr_p (tree expr, tree addr)
15981 /* Also include casts to other type variants. The C front end is fond
15982 of adding these for e.g. volatile variables. This is like
15983 STRIP_TYPE_NOPS but includes the main variant lookup. */
15984 STRIP_USELESS_TYPE_CONVERSION (expr);
15986 if (INDIRECT_REF_P (expr))
15988 expr = TREE_OPERAND (expr, 0);
15989 while (expr != addr
15990 && (CONVERT_EXPR_P (expr)
15991 || TREE_CODE (expr) == NON_LVALUE_EXPR)
15992 && TREE_CODE (expr) == TREE_CODE (addr)
15993 && types_compatible_p (TREE_TYPE (expr), TREE_TYPE (addr)))
15995 expr = TREE_OPERAND (expr, 0);
15996 addr = TREE_OPERAND (addr, 0);
15998 if (expr == addr)
15999 return true;
16000 return (TREE_CODE (addr) == ADDR_EXPR
16001 && TREE_CODE (expr) == ADDR_EXPR
16002 && TREE_OPERAND (addr, 0) == TREE_OPERAND (expr, 0));
16004 if (TREE_CODE (addr) == ADDR_EXPR && expr == TREE_OPERAND (addr, 0))
16005 return true;
16006 return false;
16009 /* Walk *EXPR_P and replace appearances of *LHS_ADDR with LHS_VAR. If an
16010 expression does not involve the lhs, evaluate it into a temporary.
16011 Return 1 if the lhs appeared as a subexpression, 0 if it did not,
16012 or -1 if an error was encountered. */
16014 static int
16015 goa_stabilize_expr (tree *expr_p, gimple_seq *pre_p, tree lhs_addr,
16016 tree lhs_var, tree &target_expr, bool rhs, int depth)
16018 tree expr = *expr_p;
16019 int saw_lhs = 0;
16021 if (goa_lhs_expr_p (expr, lhs_addr))
16023 if (pre_p)
16024 *expr_p = lhs_var;
16025 return 1;
16027 if (is_gimple_val (expr))
16028 return 0;
16030 /* Maximum depth of lhs in expression is for the
16031 __builtin_clear_padding (...), __builtin_clear_padding (...),
16032 __builtin_memcmp (&TARGET_EXPR <lhs, >, ...) == 0 ? ... : lhs; */
16033 if (++depth > 7)
16034 goto finish;
16036 switch (TREE_CODE_CLASS (TREE_CODE (expr)))
16038 case tcc_binary:
16039 case tcc_comparison:
16040 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p, lhs_addr,
16041 lhs_var, target_expr, true, depth);
16042 /* FALLTHRU */
16043 case tcc_unary:
16044 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p, lhs_addr,
16045 lhs_var, target_expr, true, depth);
16046 break;
16047 case tcc_expression:
16048 switch (TREE_CODE (expr))
16050 case TRUTH_ANDIF_EXPR:
16051 case TRUTH_ORIF_EXPR:
16052 case TRUTH_AND_EXPR:
16053 case TRUTH_OR_EXPR:
16054 case TRUTH_XOR_EXPR:
16055 case BIT_INSERT_EXPR:
16056 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
16057 lhs_addr, lhs_var, target_expr, true,
16058 depth);
16059 /* FALLTHRU */
16060 case TRUTH_NOT_EXPR:
16061 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
16062 lhs_addr, lhs_var, target_expr, true,
16063 depth);
16064 break;
16065 case MODIFY_EXPR:
16066 if (pre_p && !goa_stabilize_expr (expr_p, NULL, lhs_addr, lhs_var,
16067 target_expr, true, depth))
16068 break;
16069 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
16070 lhs_addr, lhs_var, target_expr, true,
16071 depth);
16072 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
16073 lhs_addr, lhs_var, target_expr, false,
16074 depth);
16075 break;
16076 /* FALLTHRU */
16077 case ADDR_EXPR:
16078 if (pre_p && !goa_stabilize_expr (expr_p, NULL, lhs_addr, lhs_var,
16079 target_expr, true, depth))
16080 break;
16081 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
16082 lhs_addr, lhs_var, target_expr, false,
16083 depth);
16084 break;
16085 case COMPOUND_EXPR:
16086 /* Break out any preevaluations from cp_build_modify_expr. */
16087 for (; TREE_CODE (expr) == COMPOUND_EXPR;
16088 expr = TREE_OPERAND (expr, 1))
16090 /* Special-case __builtin_clear_padding call before
16091 __builtin_memcmp. */
16092 if (TREE_CODE (TREE_OPERAND (expr, 0)) == CALL_EXPR)
16094 tree fndecl = get_callee_fndecl (TREE_OPERAND (expr, 0));
16095 if (fndecl
16096 && fndecl_built_in_p (fndecl, BUILT_IN_CLEAR_PADDING)
16097 && VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (expr, 0)))
16098 && (!pre_p
16099 || goa_stabilize_expr (&TREE_OPERAND (expr, 0), NULL,
16100 lhs_addr, lhs_var,
16101 target_expr, true, depth)))
16103 if (pre_p)
16104 *expr_p = expr;
16105 saw_lhs = goa_stabilize_expr (&TREE_OPERAND (expr, 0),
16106 pre_p, lhs_addr, lhs_var,
16107 target_expr, true, depth);
16108 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1),
16109 pre_p, lhs_addr, lhs_var,
16110 target_expr, rhs, depth);
16111 return saw_lhs;
16115 if (pre_p)
16116 gimplify_stmt (&TREE_OPERAND (expr, 0), pre_p);
16118 if (!pre_p)
16119 return goa_stabilize_expr (&expr, pre_p, lhs_addr, lhs_var,
16120 target_expr, rhs, depth);
16121 *expr_p = expr;
16122 return goa_stabilize_expr (expr_p, pre_p, lhs_addr, lhs_var,
16123 target_expr, rhs, depth);
16124 case COND_EXPR:
16125 if (!goa_stabilize_expr (&TREE_OPERAND (expr, 0), NULL, lhs_addr,
16126 lhs_var, target_expr, true, depth))
16127 break;
16128 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
16129 lhs_addr, lhs_var, target_expr, true,
16130 depth);
16131 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
16132 lhs_addr, lhs_var, target_expr, true,
16133 depth);
16134 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 2), pre_p,
16135 lhs_addr, lhs_var, target_expr, true,
16136 depth);
16137 break;
16138 case TARGET_EXPR:
16139 if (TARGET_EXPR_INITIAL (expr))
16141 if (pre_p && !goa_stabilize_expr (expr_p, NULL, lhs_addr,
16142 lhs_var, target_expr, true,
16143 depth))
16144 break;
16145 if (expr == target_expr)
16146 saw_lhs = 1;
16147 else
16149 saw_lhs = goa_stabilize_expr (&TARGET_EXPR_INITIAL (expr),
16150 pre_p, lhs_addr, lhs_var,
16151 target_expr, true, depth);
16152 if (saw_lhs && target_expr == NULL_TREE && pre_p)
16153 target_expr = expr;
16156 break;
16157 default:
16158 break;
16160 break;
16161 case tcc_reference:
16162 if (TREE_CODE (expr) == BIT_FIELD_REF
16163 || TREE_CODE (expr) == VIEW_CONVERT_EXPR)
16164 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
16165 lhs_addr, lhs_var, target_expr, true,
16166 depth);
16167 break;
16168 case tcc_vl_exp:
16169 if (TREE_CODE (expr) == CALL_EXPR)
16171 if (tree fndecl = get_callee_fndecl (expr))
16172 if (fndecl_built_in_p (fndecl, BUILT_IN_CLEAR_PADDING,
16173 BUILT_IN_MEMCMP))
16175 int nargs = call_expr_nargs (expr);
16176 for (int i = 0; i < nargs; i++)
16177 saw_lhs |= goa_stabilize_expr (&CALL_EXPR_ARG (expr, i),
16178 pre_p, lhs_addr, lhs_var,
16179 target_expr, true, depth);
16182 break;
16183 default:
16184 break;
16187 finish:
16188 if (saw_lhs == 0 && pre_p)
16190 enum gimplify_status gs;
16191 if (TREE_CODE (expr) == CALL_EXPR && VOID_TYPE_P (TREE_TYPE (expr)))
16193 gimplify_stmt (&expr, pre_p);
16194 return saw_lhs;
16196 else if (rhs)
16197 gs = gimplify_expr (expr_p, pre_p, NULL, is_gimple_val, fb_rvalue);
16198 else
16199 gs = gimplify_expr (expr_p, pre_p, NULL, is_gimple_lvalue, fb_lvalue);
16200 if (gs != GS_ALL_DONE)
16201 saw_lhs = -1;
16204 return saw_lhs;
16207 /* Gimplify an OMP_ATOMIC statement. */
16209 static enum gimplify_status
16210 gimplify_omp_atomic (tree *expr_p, gimple_seq *pre_p)
16212 tree addr = TREE_OPERAND (*expr_p, 0);
16213 tree rhs = TREE_CODE (*expr_p) == OMP_ATOMIC_READ
16214 ? NULL : TREE_OPERAND (*expr_p, 1);
16215 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (addr)));
16216 tree tmp_load;
16217 gomp_atomic_load *loadstmt;
16218 gomp_atomic_store *storestmt;
16219 tree target_expr = NULL_TREE;
16221 tmp_load = create_tmp_reg (type);
16222 if (rhs
16223 && goa_stabilize_expr (&rhs, pre_p, addr, tmp_load, target_expr,
16224 true, 0) < 0)
16225 return GS_ERROR;
16227 if (gimplify_expr (&addr, pre_p, NULL, is_gimple_val, fb_rvalue)
16228 != GS_ALL_DONE)
16229 return GS_ERROR;
16231 loadstmt = gimple_build_omp_atomic_load (tmp_load, addr,
16232 OMP_ATOMIC_MEMORY_ORDER (*expr_p));
16233 gimplify_seq_add_stmt (pre_p, loadstmt);
16234 if (rhs)
16236 /* BIT_INSERT_EXPR is not valid for non-integral bitfield
16237 representatives. Use BIT_FIELD_REF on the lhs instead. */
16238 tree rhsarg = rhs;
16239 if (TREE_CODE (rhs) == COND_EXPR)
16240 rhsarg = TREE_OPERAND (rhs, 1);
16241 if (TREE_CODE (rhsarg) == BIT_INSERT_EXPR
16242 && !INTEGRAL_TYPE_P (TREE_TYPE (tmp_load)))
16244 tree bitpos = TREE_OPERAND (rhsarg, 2);
16245 tree op1 = TREE_OPERAND (rhsarg, 1);
16246 tree bitsize;
16247 tree tmp_store = tmp_load;
16248 if (TREE_CODE (*expr_p) == OMP_ATOMIC_CAPTURE_OLD)
16249 tmp_store = get_initialized_tmp_var (tmp_load, pre_p);
16250 if (INTEGRAL_TYPE_P (TREE_TYPE (op1)))
16251 bitsize = bitsize_int (TYPE_PRECISION (TREE_TYPE (op1)));
16252 else
16253 bitsize = TYPE_SIZE (TREE_TYPE (op1));
16254 gcc_assert (TREE_OPERAND (rhsarg, 0) == tmp_load);
16255 tree t = build2_loc (EXPR_LOCATION (rhsarg),
16256 MODIFY_EXPR, void_type_node,
16257 build3_loc (EXPR_LOCATION (rhsarg),
16258 BIT_FIELD_REF, TREE_TYPE (op1),
16259 tmp_store, bitsize, bitpos), op1);
16260 if (TREE_CODE (rhs) == COND_EXPR)
16261 t = build3_loc (EXPR_LOCATION (rhs), COND_EXPR, void_type_node,
16262 TREE_OPERAND (rhs, 0), t, void_node);
16263 gimplify_and_add (t, pre_p);
16264 rhs = tmp_store;
16266 bool save_allow_rhs_cond_expr = gimplify_ctxp->allow_rhs_cond_expr;
16267 if (TREE_CODE (rhs) == COND_EXPR)
16268 gimplify_ctxp->allow_rhs_cond_expr = true;
16269 enum gimplify_status gs = gimplify_expr (&rhs, pre_p, NULL,
16270 is_gimple_val, fb_rvalue);
16271 gimplify_ctxp->allow_rhs_cond_expr = save_allow_rhs_cond_expr;
16272 if (gs != GS_ALL_DONE)
16273 return GS_ERROR;
16276 if (TREE_CODE (*expr_p) == OMP_ATOMIC_READ)
16277 rhs = tmp_load;
16278 storestmt
16279 = gimple_build_omp_atomic_store (rhs, OMP_ATOMIC_MEMORY_ORDER (*expr_p));
16280 if (TREE_CODE (*expr_p) != OMP_ATOMIC_READ && OMP_ATOMIC_WEAK (*expr_p))
16282 gimple_omp_atomic_set_weak (loadstmt);
16283 gimple_omp_atomic_set_weak (storestmt);
16285 gimplify_seq_add_stmt (pre_p, storestmt);
16286 switch (TREE_CODE (*expr_p))
16288 case OMP_ATOMIC_READ:
16289 case OMP_ATOMIC_CAPTURE_OLD:
16290 *expr_p = tmp_load;
16291 gimple_omp_atomic_set_need_value (loadstmt);
16292 break;
16293 case OMP_ATOMIC_CAPTURE_NEW:
16294 *expr_p = rhs;
16295 gimple_omp_atomic_set_need_value (storestmt);
16296 break;
16297 default:
16298 *expr_p = NULL;
16299 break;
16302 return GS_ALL_DONE;
16305 /* Gimplify a TRANSACTION_EXPR. This involves gimplification of the
16306 body, and adding some EH bits. */
16308 static enum gimplify_status
16309 gimplify_transaction (tree *expr_p, gimple_seq *pre_p)
16311 tree expr = *expr_p, temp, tbody = TRANSACTION_EXPR_BODY (expr);
16312 gimple *body_stmt;
16313 gtransaction *trans_stmt;
16314 gimple_seq body = NULL;
16315 int subcode = 0;
16317 /* Wrap the transaction body in a BIND_EXPR so we have a context
16318 where to put decls for OMP. */
16319 if (TREE_CODE (tbody) != BIND_EXPR)
16321 tree bind = build3 (BIND_EXPR, void_type_node, NULL, tbody, NULL);
16322 TREE_SIDE_EFFECTS (bind) = 1;
16323 SET_EXPR_LOCATION (bind, EXPR_LOCATION (tbody));
16324 TRANSACTION_EXPR_BODY (expr) = bind;
16327 push_gimplify_context ();
16328 temp = voidify_wrapper_expr (*expr_p, NULL);
16330 body_stmt = gimplify_and_return_first (TRANSACTION_EXPR_BODY (expr), &body);
16331 pop_gimplify_context (body_stmt);
16333 trans_stmt = gimple_build_transaction (body);
16334 if (TRANSACTION_EXPR_OUTER (expr))
16335 subcode = GTMA_IS_OUTER;
16336 else if (TRANSACTION_EXPR_RELAXED (expr))
16337 subcode = GTMA_IS_RELAXED;
16338 gimple_transaction_set_subcode (trans_stmt, subcode);
16340 gimplify_seq_add_stmt (pre_p, trans_stmt);
16342 if (temp)
16344 *expr_p = temp;
16345 return GS_OK;
16348 *expr_p = NULL_TREE;
16349 return GS_ALL_DONE;
16352 /* Gimplify an OMP_ORDERED construct. EXPR is the tree version. BODY
16353 is the OMP_BODY of the original EXPR (which has already been
16354 gimplified so it's not present in the EXPR).
16356 Return the gimplified GIMPLE_OMP_ORDERED tuple. */
16358 static gimple *
16359 gimplify_omp_ordered (tree expr, gimple_seq body)
16361 tree c, decls;
16362 int failures = 0;
16363 unsigned int i;
16364 tree source_c = NULL_TREE;
16365 tree sink_c = NULL_TREE;
16367 if (gimplify_omp_ctxp)
16369 for (c = OMP_ORDERED_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
16370 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DOACROSS
16371 && gimplify_omp_ctxp->loop_iter_var.is_empty ())
16373 error_at (OMP_CLAUSE_LOCATION (c),
16374 "%<ordered%> construct with %qs clause must be "
16375 "closely nested inside a loop with %<ordered%> clause",
16376 OMP_CLAUSE_DOACROSS_DEPEND (c) ? "depend" : "doacross");
16377 failures++;
16379 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DOACROSS
16380 && OMP_CLAUSE_DOACROSS_KIND (c) == OMP_CLAUSE_DOACROSS_SINK)
16382 bool fail = false;
16383 sink_c = c;
16384 if (OMP_CLAUSE_DECL (c) == NULL_TREE)
16385 continue; /* omp_cur_iteration - 1 */
16386 for (decls = OMP_CLAUSE_DECL (c), i = 0;
16387 decls && TREE_CODE (decls) == TREE_LIST;
16388 decls = TREE_CHAIN (decls), ++i)
16389 if (i >= gimplify_omp_ctxp->loop_iter_var.length () / 2)
16390 continue;
16391 else if (TREE_VALUE (decls)
16392 != gimplify_omp_ctxp->loop_iter_var[2 * i])
16394 error_at (OMP_CLAUSE_LOCATION (c),
16395 "variable %qE is not an iteration "
16396 "of outermost loop %d, expected %qE",
16397 TREE_VALUE (decls), i + 1,
16398 gimplify_omp_ctxp->loop_iter_var[2 * i]);
16399 fail = true;
16400 failures++;
16402 else
16403 TREE_VALUE (decls)
16404 = gimplify_omp_ctxp->loop_iter_var[2 * i + 1];
16405 if (!fail && i != gimplify_omp_ctxp->loop_iter_var.length () / 2)
16407 error_at (OMP_CLAUSE_LOCATION (c),
16408 "number of variables in %qs clause with "
16409 "%<sink%> modifier does not match number of "
16410 "iteration variables",
16411 OMP_CLAUSE_DOACROSS_DEPEND (c)
16412 ? "depend" : "doacross");
16413 failures++;
16416 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DOACROSS
16417 && OMP_CLAUSE_DOACROSS_KIND (c) == OMP_CLAUSE_DOACROSS_SOURCE)
16419 if (source_c)
16421 error_at (OMP_CLAUSE_LOCATION (c),
16422 "more than one %qs clause with %<source%> "
16423 "modifier on an %<ordered%> construct",
16424 OMP_CLAUSE_DOACROSS_DEPEND (source_c)
16425 ? "depend" : "doacross");
16426 failures++;
16428 else
16429 source_c = c;
16432 if (source_c && sink_c)
16434 error_at (OMP_CLAUSE_LOCATION (source_c),
16435 "%qs clause with %<source%> modifier specified "
16436 "together with %qs clauses with %<sink%> modifier "
16437 "on the same construct",
16438 OMP_CLAUSE_DOACROSS_DEPEND (source_c) ? "depend" : "doacross",
16439 OMP_CLAUSE_DOACROSS_DEPEND (sink_c) ? "depend" : "doacross");
16440 failures++;
16443 if (failures)
16444 return gimple_build_nop ();
16445 return gimple_build_omp_ordered (body, OMP_ORDERED_CLAUSES (expr));
16448 /* Convert the GENERIC expression tree *EXPR_P to GIMPLE. If the
16449 expression produces a value to be used as an operand inside a GIMPLE
16450 statement, the value will be stored back in *EXPR_P. This value will
16451 be a tree of class tcc_declaration, tcc_constant, tcc_reference or
16452 an SSA_NAME. The corresponding sequence of GIMPLE statements is
16453 emitted in PRE_P and POST_P.
16455 Additionally, this process may overwrite parts of the input
16456 expression during gimplification. Ideally, it should be
16457 possible to do non-destructive gimplification.
16459 EXPR_P points to the GENERIC expression to convert to GIMPLE. If
16460 the expression needs to evaluate to a value to be used as
16461 an operand in a GIMPLE statement, this value will be stored in
16462 *EXPR_P on exit. This happens when the caller specifies one
16463 of fb_lvalue or fb_rvalue fallback flags.
16465 PRE_P will contain the sequence of GIMPLE statements corresponding
16466 to the evaluation of EXPR and all the side-effects that must
16467 be executed before the main expression. On exit, the last
16468 statement of PRE_P is the core statement being gimplified. For
16469 instance, when gimplifying 'if (++a)' the last statement in
16470 PRE_P will be 'if (t.1)' where t.1 is the result of
16471 pre-incrementing 'a'.
16473 POST_P will contain the sequence of GIMPLE statements corresponding
16474 to the evaluation of all the side-effects that must be executed
16475 after the main expression. If this is NULL, the post
16476 side-effects are stored at the end of PRE_P.
16478 The reason why the output is split in two is to handle post
16479 side-effects explicitly. In some cases, an expression may have
16480 inner and outer post side-effects which need to be emitted in
16481 an order different from the one given by the recursive
16482 traversal. For instance, for the expression (*p--)++ the post
16483 side-effects of '--' must actually occur *after* the post
16484 side-effects of '++'. However, gimplification will first visit
16485 the inner expression, so if a separate POST sequence was not
16486 used, the resulting sequence would be:
16488 1 t.1 = *p
16489 2 p = p - 1
16490 3 t.2 = t.1 + 1
16491 4 *p = t.2
16493 However, the post-decrement operation in line #2 must not be
16494 evaluated until after the store to *p at line #4, so the
16495 correct sequence should be:
16497 1 t.1 = *p
16498 2 t.2 = t.1 + 1
16499 3 *p = t.2
16500 4 p = p - 1
16502 So, by specifying a separate post queue, it is possible
16503 to emit the post side-effects in the correct order.
16504 If POST_P is NULL, an internal queue will be used. Before
16505 returning to the caller, the sequence POST_P is appended to
16506 the main output sequence PRE_P.
16508 GIMPLE_TEST_F points to a function that takes a tree T and
16509 returns nonzero if T is in the GIMPLE form requested by the
16510 caller. The GIMPLE predicates are in gimple.cc.
16512 FALLBACK tells the function what sort of a temporary we want if
16513 gimplification cannot produce an expression that complies with
16514 GIMPLE_TEST_F.
16516 fb_none means that no temporary should be generated
16517 fb_rvalue means that an rvalue is OK to generate
16518 fb_lvalue means that an lvalue is OK to generate
16519 fb_either means that either is OK, but an lvalue is preferable.
16520 fb_mayfail means that gimplification may fail (in which case
16521 GS_ERROR will be returned)
16523 The return value is either GS_ERROR or GS_ALL_DONE, since this
16524 function iterates until EXPR is completely gimplified or an error
16525 occurs. */
16527 enum gimplify_status
16528 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
16529 bool (*gimple_test_f) (tree), fallback_t fallback)
16531 tree tmp;
16532 gimple_seq internal_pre = NULL;
16533 gimple_seq internal_post = NULL;
16534 tree save_expr;
16535 bool is_statement;
16536 location_t saved_location;
16537 enum gimplify_status ret;
16538 gimple_stmt_iterator pre_last_gsi, post_last_gsi;
16539 tree label;
16541 save_expr = *expr_p;
16542 if (save_expr == NULL_TREE)
16543 return GS_ALL_DONE;
16545 /* If we are gimplifying a top-level statement, PRE_P must be valid. */
16546 is_statement = gimple_test_f == is_gimple_stmt;
16547 if (is_statement)
16548 gcc_assert (pre_p);
16550 /* Consistency checks. */
16551 if (gimple_test_f == is_gimple_reg)
16552 gcc_assert (fallback & (fb_rvalue | fb_lvalue));
16553 else if (gimple_test_f == is_gimple_val
16554 || gimple_test_f == is_gimple_call_addr
16555 || gimple_test_f == is_gimple_condexpr_for_cond
16556 || gimple_test_f == is_gimple_mem_rhs
16557 || gimple_test_f == is_gimple_mem_rhs_or_call
16558 || gimple_test_f == is_gimple_reg_rhs
16559 || gimple_test_f == is_gimple_reg_rhs_or_call
16560 || gimple_test_f == is_gimple_asm_val
16561 || gimple_test_f == is_gimple_mem_ref_addr)
16562 gcc_assert (fallback & fb_rvalue);
16563 else if (gimple_test_f == is_gimple_min_lval
16564 || gimple_test_f == is_gimple_lvalue)
16565 gcc_assert (fallback & fb_lvalue);
16566 else if (gimple_test_f == is_gimple_addressable)
16567 gcc_assert (fallback & fb_either);
16568 else if (gimple_test_f == is_gimple_stmt)
16569 gcc_assert (fallback == fb_none);
16570 else
16572 /* We should have recognized the GIMPLE_TEST_F predicate to
16573 know what kind of fallback to use in case a temporary is
16574 needed to hold the value or address of *EXPR_P. */
16575 gcc_unreachable ();
16578 /* We used to check the predicate here and return immediately if it
16579 succeeds. This is wrong; the design is for gimplification to be
16580 idempotent, and for the predicates to only test for valid forms, not
16581 whether they are fully simplified. */
16582 if (pre_p == NULL)
16583 pre_p = &internal_pre;
16585 if (post_p == NULL)
16586 post_p = &internal_post;
16588 /* Remember the last statements added to PRE_P and POST_P. Every
16589 new statement added by the gimplification helpers needs to be
16590 annotated with location information. To centralize the
16591 responsibility, we remember the last statement that had been
16592 added to both queues before gimplifying *EXPR_P. If
16593 gimplification produces new statements in PRE_P and POST_P, those
16594 statements will be annotated with the same location information
16595 as *EXPR_P. */
16596 pre_last_gsi = gsi_last (*pre_p);
16597 post_last_gsi = gsi_last (*post_p);
16599 saved_location = input_location;
16600 if (save_expr != error_mark_node
16601 && EXPR_HAS_LOCATION (*expr_p))
16602 input_location = EXPR_LOCATION (*expr_p);
16604 /* Loop over the specific gimplifiers until the toplevel node
16605 remains the same. */
16608 /* Strip away as many useless type conversions as possible
16609 at the toplevel. */
16610 STRIP_USELESS_TYPE_CONVERSION (*expr_p);
16612 /* Remember the expr. */
16613 save_expr = *expr_p;
16615 /* Die, die, die, my darling. */
16616 if (error_operand_p (save_expr))
16618 ret = GS_ERROR;
16619 break;
16622 /* Do any language-specific gimplification. */
16623 ret = ((enum gimplify_status)
16624 lang_hooks.gimplify_expr (expr_p, pre_p, post_p));
16625 if (ret == GS_OK)
16627 if (*expr_p == NULL_TREE)
16628 break;
16629 if (*expr_p != save_expr)
16630 continue;
16632 else if (ret != GS_UNHANDLED)
16633 break;
16635 /* Make sure that all the cases set 'ret' appropriately. */
16636 ret = GS_UNHANDLED;
16637 switch (TREE_CODE (*expr_p))
16639 /* First deal with the special cases. */
16641 case POSTINCREMENT_EXPR:
16642 case POSTDECREMENT_EXPR:
16643 case PREINCREMENT_EXPR:
16644 case PREDECREMENT_EXPR:
16645 ret = gimplify_self_mod_expr (expr_p, pre_p, post_p,
16646 fallback != fb_none,
16647 TREE_TYPE (*expr_p));
16648 break;
16650 case VIEW_CONVERT_EXPR:
16651 if ((fallback & fb_rvalue)
16652 && is_gimple_reg_type (TREE_TYPE (*expr_p))
16653 && is_gimple_reg_type (TREE_TYPE (TREE_OPERAND (*expr_p, 0))))
16655 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
16656 post_p, is_gimple_val, fb_rvalue);
16657 recalculate_side_effects (*expr_p);
16658 break;
16660 /* Fallthru. */
16662 case ARRAY_REF:
16663 case ARRAY_RANGE_REF:
16664 case REALPART_EXPR:
16665 case IMAGPART_EXPR:
16666 case COMPONENT_REF:
16667 ret = gimplify_compound_lval (expr_p, pre_p, post_p,
16668 fallback ? fallback : fb_rvalue);
16669 break;
16671 case COND_EXPR:
16672 ret = gimplify_cond_expr (expr_p, pre_p, fallback);
16674 /* C99 code may assign to an array in a structure value of a
16675 conditional expression, and this has undefined behavior
16676 only on execution, so create a temporary if an lvalue is
16677 required. */
16678 if (fallback == fb_lvalue)
16680 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
16681 mark_addressable (*expr_p);
16682 ret = GS_OK;
16684 break;
16686 case CALL_EXPR:
16687 ret = gimplify_call_expr (expr_p, pre_p, fallback != fb_none);
16689 /* C99 code may assign to an array in a structure returned
16690 from a function, and this has undefined behavior only on
16691 execution, so create a temporary if an lvalue is
16692 required. */
16693 if (fallback == fb_lvalue)
16695 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
16696 mark_addressable (*expr_p);
16697 ret = GS_OK;
16699 break;
16701 case TREE_LIST:
16702 gcc_unreachable ();
16704 case COMPOUND_EXPR:
16705 ret = gimplify_compound_expr (expr_p, pre_p, fallback != fb_none);
16706 break;
16708 case COMPOUND_LITERAL_EXPR:
16709 ret = gimplify_compound_literal_expr (expr_p, pre_p,
16710 gimple_test_f, fallback);
16711 break;
16713 case MODIFY_EXPR:
16714 case INIT_EXPR:
16715 ret = gimplify_modify_expr (expr_p, pre_p, post_p,
16716 fallback != fb_none);
16717 break;
16719 case TRUTH_ANDIF_EXPR:
16720 case TRUTH_ORIF_EXPR:
16722 /* Preserve the original type of the expression and the
16723 source location of the outer expression. */
16724 tree org_type = TREE_TYPE (*expr_p);
16725 *expr_p = gimple_boolify (*expr_p);
16726 *expr_p = build3_loc (input_location, COND_EXPR,
16727 org_type, *expr_p,
16728 fold_convert_loc
16729 (input_location,
16730 org_type, boolean_true_node),
16731 fold_convert_loc
16732 (input_location,
16733 org_type, boolean_false_node));
16734 ret = GS_OK;
16735 break;
16738 case TRUTH_NOT_EXPR:
16740 tree type = TREE_TYPE (*expr_p);
16741 /* The parsers are careful to generate TRUTH_NOT_EXPR
16742 only with operands that are always zero or one.
16743 We do not fold here but handle the only interesting case
16744 manually, as fold may re-introduce the TRUTH_NOT_EXPR. */
16745 *expr_p = gimple_boolify (*expr_p);
16746 if (TYPE_PRECISION (TREE_TYPE (*expr_p)) == 1)
16747 *expr_p = build1_loc (input_location, BIT_NOT_EXPR,
16748 TREE_TYPE (*expr_p),
16749 TREE_OPERAND (*expr_p, 0));
16750 else
16751 *expr_p = build2_loc (input_location, BIT_XOR_EXPR,
16752 TREE_TYPE (*expr_p),
16753 TREE_OPERAND (*expr_p, 0),
16754 build_int_cst (TREE_TYPE (*expr_p), 1));
16755 if (!useless_type_conversion_p (type, TREE_TYPE (*expr_p)))
16756 *expr_p = fold_convert_loc (input_location, type, *expr_p);
16757 ret = GS_OK;
16758 break;
16761 case ADDR_EXPR:
16762 ret = gimplify_addr_expr (expr_p, pre_p, post_p);
16763 break;
16765 case ANNOTATE_EXPR:
16767 tree cond = TREE_OPERAND (*expr_p, 0);
16768 tree kind = TREE_OPERAND (*expr_p, 1);
16769 tree data = TREE_OPERAND (*expr_p, 2);
16770 tree type = TREE_TYPE (cond);
16771 if (!INTEGRAL_TYPE_P (type))
16773 *expr_p = cond;
16774 ret = GS_OK;
16775 break;
16777 tree tmp = create_tmp_var (type);
16778 gimplify_arg (&cond, pre_p, EXPR_LOCATION (*expr_p));
16779 gcall *call
16780 = gimple_build_call_internal (IFN_ANNOTATE, 3, cond, kind, data);
16781 gimple_call_set_lhs (call, tmp);
16782 gimplify_seq_add_stmt (pre_p, call);
16783 *expr_p = tmp;
16784 ret = GS_ALL_DONE;
16785 break;
16788 case VA_ARG_EXPR:
16789 ret = gimplify_va_arg_expr (expr_p, pre_p, post_p);
16790 break;
16792 CASE_CONVERT:
16793 if (IS_EMPTY_STMT (*expr_p))
16795 ret = GS_ALL_DONE;
16796 break;
16799 if (VOID_TYPE_P (TREE_TYPE (*expr_p))
16800 || fallback == fb_none)
16802 /* Just strip a conversion to void (or in void context) and
16803 try again. */
16804 *expr_p = TREE_OPERAND (*expr_p, 0);
16805 ret = GS_OK;
16806 break;
16809 ret = gimplify_conversion (expr_p);
16810 if (ret == GS_ERROR)
16811 break;
16812 if (*expr_p != save_expr)
16813 break;
16814 /* FALLTHRU */
16816 case FIX_TRUNC_EXPR:
16817 /* unary_expr: ... | '(' cast ')' val | ... */
16818 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
16819 is_gimple_val, fb_rvalue);
16820 recalculate_side_effects (*expr_p);
16821 break;
16823 case INDIRECT_REF:
16825 bool volatilep = TREE_THIS_VOLATILE (*expr_p);
16826 bool notrap = TREE_THIS_NOTRAP (*expr_p);
16827 tree saved_ptr_type = TREE_TYPE (TREE_OPERAND (*expr_p, 0));
16829 *expr_p = fold_indirect_ref_loc (input_location, *expr_p);
16830 if (*expr_p != save_expr)
16832 ret = GS_OK;
16833 break;
16836 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
16837 is_gimple_reg, fb_rvalue);
16838 if (ret == GS_ERROR)
16839 break;
16841 recalculate_side_effects (*expr_p);
16842 *expr_p = fold_build2_loc (input_location, MEM_REF,
16843 TREE_TYPE (*expr_p),
16844 TREE_OPERAND (*expr_p, 0),
16845 build_int_cst (saved_ptr_type, 0));
16846 TREE_THIS_VOLATILE (*expr_p) = volatilep;
16847 TREE_THIS_NOTRAP (*expr_p) = notrap;
16848 ret = GS_OK;
16849 break;
16852 /* We arrive here through the various re-gimplifcation paths. */
16853 case MEM_REF:
16854 /* First try re-folding the whole thing. */
16855 tmp = fold_binary (MEM_REF, TREE_TYPE (*expr_p),
16856 TREE_OPERAND (*expr_p, 0),
16857 TREE_OPERAND (*expr_p, 1));
16858 if (tmp)
16860 REF_REVERSE_STORAGE_ORDER (tmp)
16861 = REF_REVERSE_STORAGE_ORDER (*expr_p);
16862 *expr_p = tmp;
16863 recalculate_side_effects (*expr_p);
16864 ret = GS_OK;
16865 break;
16867 /* Avoid re-gimplifying the address operand if it is already
16868 in suitable form. Re-gimplifying would mark the address
16869 operand addressable. Always gimplify when not in SSA form
16870 as we still may have to gimplify decls with value-exprs. */
16871 if (!gimplify_ctxp || !gimple_in_ssa_p (cfun)
16872 || !is_gimple_mem_ref_addr (TREE_OPERAND (*expr_p, 0)))
16874 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
16875 is_gimple_mem_ref_addr, fb_rvalue);
16876 if (ret == GS_ERROR)
16877 break;
16879 recalculate_side_effects (*expr_p);
16880 ret = GS_ALL_DONE;
16881 break;
16883 /* Constants need not be gimplified. */
16884 case INTEGER_CST:
16885 case REAL_CST:
16886 case FIXED_CST:
16887 case STRING_CST:
16888 case COMPLEX_CST:
16889 case VECTOR_CST:
16890 /* Drop the overflow flag on constants, we do not want
16891 that in the GIMPLE IL. */
16892 if (TREE_OVERFLOW_P (*expr_p))
16893 *expr_p = drop_tree_overflow (*expr_p);
16894 ret = GS_ALL_DONE;
16895 break;
16897 case CONST_DECL:
16898 /* If we require an lvalue, such as for ADDR_EXPR, retain the
16899 CONST_DECL node. Otherwise the decl is replaceable by its
16900 value. */
16901 /* ??? Should be == fb_lvalue, but ADDR_EXPR passes fb_either. */
16902 if (fallback & fb_lvalue)
16903 ret = GS_ALL_DONE;
16904 else
16906 *expr_p = DECL_INITIAL (*expr_p);
16907 ret = GS_OK;
16909 break;
16911 case DECL_EXPR:
16912 ret = gimplify_decl_expr (expr_p, pre_p);
16913 break;
16915 case BIND_EXPR:
16916 ret = gimplify_bind_expr (expr_p, pre_p);
16917 break;
16919 case LOOP_EXPR:
16920 ret = gimplify_loop_expr (expr_p, pre_p);
16921 break;
16923 case SWITCH_EXPR:
16924 ret = gimplify_switch_expr (expr_p, pre_p);
16925 break;
16927 case EXIT_EXPR:
16928 ret = gimplify_exit_expr (expr_p);
16929 break;
16931 case GOTO_EXPR:
16932 /* If the target is not LABEL, then it is a computed jump
16933 and the target needs to be gimplified. */
16934 if (TREE_CODE (GOTO_DESTINATION (*expr_p)) != LABEL_DECL)
16936 ret = gimplify_expr (&GOTO_DESTINATION (*expr_p), pre_p,
16937 NULL, is_gimple_val, fb_rvalue);
16938 if (ret == GS_ERROR)
16939 break;
16941 gimplify_seq_add_stmt (pre_p,
16942 gimple_build_goto (GOTO_DESTINATION (*expr_p)));
16943 ret = GS_ALL_DONE;
16944 break;
16946 case PREDICT_EXPR:
16947 gimplify_seq_add_stmt (pre_p,
16948 gimple_build_predict (PREDICT_EXPR_PREDICTOR (*expr_p),
16949 PREDICT_EXPR_OUTCOME (*expr_p)));
16950 ret = GS_ALL_DONE;
16951 break;
16953 case LABEL_EXPR:
16954 ret = gimplify_label_expr (expr_p, pre_p);
16955 label = LABEL_EXPR_LABEL (*expr_p);
16956 gcc_assert (decl_function_context (label) == current_function_decl);
16958 /* If the label is used in a goto statement, or address of the label
16959 is taken, we need to unpoison all variables that were seen so far.
16960 Doing so would prevent us from reporting a false positives. */
16961 if (asan_poisoned_variables
16962 && asan_used_labels != NULL
16963 && asan_used_labels->contains (label)
16964 && !gimplify_omp_ctxp)
16965 asan_poison_variables (asan_poisoned_variables, false, pre_p);
16966 break;
16968 case CASE_LABEL_EXPR:
16969 ret = gimplify_case_label_expr (expr_p, pre_p);
16971 if (gimplify_ctxp->live_switch_vars)
16972 asan_poison_variables (gimplify_ctxp->live_switch_vars, false,
16973 pre_p);
16974 break;
16976 case RETURN_EXPR:
16977 ret = gimplify_return_expr (*expr_p, pre_p);
16978 break;
16980 case CONSTRUCTOR:
16981 /* Don't reduce this in place; let gimplify_init_constructor work its
16982 magic. Buf if we're just elaborating this for side effects, just
16983 gimplify any element that has side-effects. */
16984 if (fallback == fb_none)
16986 unsigned HOST_WIDE_INT ix;
16987 tree val;
16988 tree temp = NULL_TREE;
16989 FOR_EACH_CONSTRUCTOR_VALUE (CONSTRUCTOR_ELTS (*expr_p), ix, val)
16990 if (TREE_SIDE_EFFECTS (val))
16991 append_to_statement_list (val, &temp);
16993 *expr_p = temp;
16994 ret = temp ? GS_OK : GS_ALL_DONE;
16996 /* C99 code may assign to an array in a constructed
16997 structure or union, and this has undefined behavior only
16998 on execution, so create a temporary if an lvalue is
16999 required. */
17000 else if (fallback == fb_lvalue)
17002 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
17003 mark_addressable (*expr_p);
17004 ret = GS_OK;
17006 else
17007 ret = GS_ALL_DONE;
17008 break;
17010 /* The following are special cases that are not handled by the
17011 original GIMPLE grammar. */
17013 /* SAVE_EXPR nodes are converted into a GIMPLE identifier and
17014 eliminated. */
17015 case SAVE_EXPR:
17016 ret = gimplify_save_expr (expr_p, pre_p, post_p);
17017 break;
17019 case BIT_FIELD_REF:
17020 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
17021 post_p, is_gimple_lvalue, fb_either);
17022 recalculate_side_effects (*expr_p);
17023 break;
17025 case TARGET_MEM_REF:
17027 enum gimplify_status r0 = GS_ALL_DONE, r1 = GS_ALL_DONE;
17029 if (TMR_BASE (*expr_p))
17030 r0 = gimplify_expr (&TMR_BASE (*expr_p), pre_p,
17031 post_p, is_gimple_mem_ref_addr, fb_either);
17032 if (TMR_INDEX (*expr_p))
17033 r1 = gimplify_expr (&TMR_INDEX (*expr_p), pre_p,
17034 post_p, is_gimple_val, fb_rvalue);
17035 if (TMR_INDEX2 (*expr_p))
17036 r1 = gimplify_expr (&TMR_INDEX2 (*expr_p), pre_p,
17037 post_p, is_gimple_val, fb_rvalue);
17038 /* TMR_STEP and TMR_OFFSET are always integer constants. */
17039 ret = MIN (r0, r1);
17041 break;
17043 case NON_LVALUE_EXPR:
17044 /* This should have been stripped above. */
17045 gcc_unreachable ();
17047 case ASM_EXPR:
17048 ret = gimplify_asm_expr (expr_p, pre_p, post_p);
17049 break;
17051 case TRY_FINALLY_EXPR:
17052 case TRY_CATCH_EXPR:
17054 gimple_seq eval, cleanup;
17055 gtry *try_;
17057 /* Calls to destructors are generated automatically in FINALLY/CATCH
17058 block. They should have location as UNKNOWN_LOCATION. However,
17059 gimplify_call_expr will reset these call stmts to input_location
17060 if it finds stmt's location is unknown. To prevent resetting for
17061 destructors, we set the input_location to unknown.
17062 Note that this only affects the destructor calls in FINALLY/CATCH
17063 block, and will automatically reset to its original value by the
17064 end of gimplify_expr. */
17065 input_location = UNKNOWN_LOCATION;
17066 eval = cleanup = NULL;
17067 gimplify_and_add (TREE_OPERAND (*expr_p, 0), &eval);
17068 if (TREE_CODE (*expr_p) == TRY_FINALLY_EXPR
17069 && TREE_CODE (TREE_OPERAND (*expr_p, 1)) == EH_ELSE_EXPR)
17071 gimple_seq n = NULL, e = NULL;
17072 gimplify_and_add (TREE_OPERAND (TREE_OPERAND (*expr_p, 1),
17073 0), &n);
17074 gimplify_and_add (TREE_OPERAND (TREE_OPERAND (*expr_p, 1),
17075 1), &e);
17076 if (!gimple_seq_empty_p (n) && !gimple_seq_empty_p (e))
17078 geh_else *stmt = gimple_build_eh_else (n, e);
17079 gimple_seq_add_stmt (&cleanup, stmt);
17082 else
17083 gimplify_and_add (TREE_OPERAND (*expr_p, 1), &cleanup);
17084 /* Don't create bogus GIMPLE_TRY with empty cleanup. */
17085 if (gimple_seq_empty_p (cleanup))
17087 gimple_seq_add_seq (pre_p, eval);
17088 ret = GS_ALL_DONE;
17089 break;
17091 try_ = gimple_build_try (eval, cleanup,
17092 TREE_CODE (*expr_p) == TRY_FINALLY_EXPR
17093 ? GIMPLE_TRY_FINALLY
17094 : GIMPLE_TRY_CATCH);
17095 if (EXPR_HAS_LOCATION (save_expr))
17096 gimple_set_location (try_, EXPR_LOCATION (save_expr));
17097 else if (LOCATION_LOCUS (saved_location) != UNKNOWN_LOCATION)
17098 gimple_set_location (try_, saved_location);
17099 if (TREE_CODE (*expr_p) == TRY_CATCH_EXPR)
17100 gimple_try_set_catch_is_cleanup (try_,
17101 TRY_CATCH_IS_CLEANUP (*expr_p));
17102 gimplify_seq_add_stmt (pre_p, try_);
17103 ret = GS_ALL_DONE;
17104 break;
17107 case CLEANUP_POINT_EXPR:
17108 ret = gimplify_cleanup_point_expr (expr_p, pre_p);
17109 break;
17111 case TARGET_EXPR:
17112 ret = gimplify_target_expr (expr_p, pre_p, post_p);
17113 break;
17115 case CATCH_EXPR:
17117 gimple *c;
17118 gimple_seq handler = NULL;
17119 gimplify_and_add (CATCH_BODY (*expr_p), &handler);
17120 c = gimple_build_catch (CATCH_TYPES (*expr_p), handler);
17121 gimplify_seq_add_stmt (pre_p, c);
17122 ret = GS_ALL_DONE;
17123 break;
17126 case EH_FILTER_EXPR:
17128 gimple *ehf;
17129 gimple_seq failure = NULL;
17131 gimplify_and_add (EH_FILTER_FAILURE (*expr_p), &failure);
17132 ehf = gimple_build_eh_filter (EH_FILTER_TYPES (*expr_p), failure);
17133 copy_warning (ehf, *expr_p);
17134 gimplify_seq_add_stmt (pre_p, ehf);
17135 ret = GS_ALL_DONE;
17136 break;
17139 case OBJ_TYPE_REF:
17141 enum gimplify_status r0, r1;
17142 r0 = gimplify_expr (&OBJ_TYPE_REF_OBJECT (*expr_p), pre_p,
17143 post_p, is_gimple_val, fb_rvalue);
17144 r1 = gimplify_expr (&OBJ_TYPE_REF_EXPR (*expr_p), pre_p,
17145 post_p, is_gimple_val, fb_rvalue);
17146 TREE_SIDE_EFFECTS (*expr_p) = 0;
17147 ret = MIN (r0, r1);
17149 break;
17151 case LABEL_DECL:
17152 /* We get here when taking the address of a label. We mark
17153 the label as "forced"; meaning it can never be removed and
17154 it is a potential target for any computed goto. */
17155 FORCED_LABEL (*expr_p) = 1;
17156 ret = GS_ALL_DONE;
17157 break;
17159 case STATEMENT_LIST:
17160 ret = gimplify_statement_list (expr_p, pre_p);
17161 break;
17163 case WITH_SIZE_EXPR:
17165 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
17166 post_p == &internal_post ? NULL : post_p,
17167 gimple_test_f, fallback);
17168 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
17169 is_gimple_val, fb_rvalue);
17170 ret = GS_ALL_DONE;
17172 break;
17174 case VAR_DECL:
17175 case PARM_DECL:
17176 ret = gimplify_var_or_parm_decl (expr_p);
17177 break;
17179 case RESULT_DECL:
17180 /* When within an OMP context, notice uses of variables. */
17181 if (gimplify_omp_ctxp)
17182 omp_notice_variable (gimplify_omp_ctxp, *expr_p, true);
17183 ret = GS_ALL_DONE;
17184 break;
17186 case DEBUG_EXPR_DECL:
17187 gcc_unreachable ();
17189 case DEBUG_BEGIN_STMT:
17190 gimplify_seq_add_stmt (pre_p,
17191 gimple_build_debug_begin_stmt
17192 (TREE_BLOCK (*expr_p),
17193 EXPR_LOCATION (*expr_p)));
17194 ret = GS_ALL_DONE;
17195 *expr_p = NULL;
17196 break;
17198 case SSA_NAME:
17199 /* Allow callbacks into the gimplifier during optimization. */
17200 ret = GS_ALL_DONE;
17201 break;
17203 case OMP_PARALLEL:
17204 gimplify_omp_parallel (expr_p, pre_p);
17205 ret = GS_ALL_DONE;
17206 break;
17208 case OMP_TASK:
17209 gimplify_omp_task (expr_p, pre_p);
17210 ret = GS_ALL_DONE;
17211 break;
17213 case OMP_SIMD:
17215 /* Temporarily disable into_ssa, as scan_omp_simd
17216 which calls copy_gimple_seq_and_replace_locals can't deal
17217 with SSA_NAMEs defined outside of the body properly. */
17218 bool saved_into_ssa = gimplify_ctxp->into_ssa;
17219 gimplify_ctxp->into_ssa = false;
17220 ret = gimplify_omp_for (expr_p, pre_p);
17221 gimplify_ctxp->into_ssa = saved_into_ssa;
17222 break;
17225 case OMP_FOR:
17226 case OMP_DISTRIBUTE:
17227 case OMP_TASKLOOP:
17228 case OACC_LOOP:
17229 ret = gimplify_omp_for (expr_p, pre_p);
17230 break;
17232 case OMP_LOOP:
17233 ret = gimplify_omp_loop (expr_p, pre_p);
17234 break;
17236 case OACC_CACHE:
17237 gimplify_oacc_cache (expr_p, pre_p);
17238 ret = GS_ALL_DONE;
17239 break;
17241 case OACC_DECLARE:
17242 gimplify_oacc_declare (expr_p, pre_p);
17243 ret = GS_ALL_DONE;
17244 break;
17246 case OACC_HOST_DATA:
17247 case OACC_DATA:
17248 case OACC_KERNELS:
17249 case OACC_PARALLEL:
17250 case OACC_SERIAL:
17251 case OMP_SCOPE:
17252 case OMP_SECTIONS:
17253 case OMP_SINGLE:
17254 case OMP_TARGET:
17255 case OMP_TARGET_DATA:
17256 case OMP_TEAMS:
17257 gimplify_omp_workshare (expr_p, pre_p);
17258 ret = GS_ALL_DONE;
17259 break;
17261 case OACC_ENTER_DATA:
17262 case OACC_EXIT_DATA:
17263 case OACC_UPDATE:
17264 case OMP_TARGET_UPDATE:
17265 case OMP_TARGET_ENTER_DATA:
17266 case OMP_TARGET_EXIT_DATA:
17267 gimplify_omp_target_update (expr_p, pre_p);
17268 ret = GS_ALL_DONE;
17269 break;
17271 case OMP_SECTION:
17272 case OMP_STRUCTURED_BLOCK:
17273 case OMP_MASTER:
17274 case OMP_MASKED:
17275 case OMP_ORDERED:
17276 case OMP_CRITICAL:
17277 case OMP_SCAN:
17279 gimple_seq body = NULL;
17280 gimple *g;
17281 bool saved_in_omp_construct = in_omp_construct;
17283 in_omp_construct = true;
17284 gimplify_and_add (OMP_BODY (*expr_p), &body);
17285 in_omp_construct = saved_in_omp_construct;
17286 switch (TREE_CODE (*expr_p))
17288 case OMP_SECTION:
17289 g = gimple_build_omp_section (body);
17290 break;
17291 case OMP_STRUCTURED_BLOCK:
17292 g = gimple_build_omp_structured_block (body);
17293 break;
17294 case OMP_MASTER:
17295 g = gimple_build_omp_master (body);
17296 break;
17297 case OMP_ORDERED:
17298 g = gimplify_omp_ordered (*expr_p, body);
17299 if (OMP_BODY (*expr_p) == NULL_TREE
17300 && gimple_code (g) == GIMPLE_OMP_ORDERED)
17301 gimple_omp_ordered_standalone (g);
17302 break;
17303 case OMP_MASKED:
17304 gimplify_scan_omp_clauses (&OMP_MASKED_CLAUSES (*expr_p),
17305 pre_p, ORT_WORKSHARE, OMP_MASKED);
17306 gimplify_adjust_omp_clauses (pre_p, body,
17307 &OMP_MASKED_CLAUSES (*expr_p),
17308 OMP_MASKED);
17309 g = gimple_build_omp_masked (body,
17310 OMP_MASKED_CLAUSES (*expr_p));
17311 break;
17312 case OMP_CRITICAL:
17313 gimplify_scan_omp_clauses (&OMP_CRITICAL_CLAUSES (*expr_p),
17314 pre_p, ORT_WORKSHARE, OMP_CRITICAL);
17315 gimplify_adjust_omp_clauses (pre_p, body,
17316 &OMP_CRITICAL_CLAUSES (*expr_p),
17317 OMP_CRITICAL);
17318 g = gimple_build_omp_critical (body,
17319 OMP_CRITICAL_NAME (*expr_p),
17320 OMP_CRITICAL_CLAUSES (*expr_p));
17321 break;
17322 case OMP_SCAN:
17323 gimplify_scan_omp_clauses (&OMP_SCAN_CLAUSES (*expr_p),
17324 pre_p, ORT_WORKSHARE, OMP_SCAN);
17325 gimplify_adjust_omp_clauses (pre_p, body,
17326 &OMP_SCAN_CLAUSES (*expr_p),
17327 OMP_SCAN);
17328 g = gimple_build_omp_scan (body, OMP_SCAN_CLAUSES (*expr_p));
17329 break;
17330 default:
17331 gcc_unreachable ();
17333 gimplify_seq_add_stmt (pre_p, g);
17334 ret = GS_ALL_DONE;
17335 break;
17338 case OMP_TASKGROUP:
17340 gimple_seq body = NULL;
17342 tree *pclauses = &OMP_TASKGROUP_CLAUSES (*expr_p);
17343 bool saved_in_omp_construct = in_omp_construct;
17344 gimplify_scan_omp_clauses (pclauses, pre_p, ORT_TASKGROUP,
17345 OMP_TASKGROUP);
17346 gimplify_adjust_omp_clauses (pre_p, NULL, pclauses, OMP_TASKGROUP);
17348 in_omp_construct = true;
17349 gimplify_and_add (OMP_BODY (*expr_p), &body);
17350 in_omp_construct = saved_in_omp_construct;
17351 gimple_seq cleanup = NULL;
17352 tree fn = builtin_decl_explicit (BUILT_IN_GOMP_TASKGROUP_END);
17353 gimple *g = gimple_build_call (fn, 0);
17354 gimple_seq_add_stmt (&cleanup, g);
17355 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
17356 body = NULL;
17357 gimple_seq_add_stmt (&body, g);
17358 g = gimple_build_omp_taskgroup (body, *pclauses);
17359 gimplify_seq_add_stmt (pre_p, g);
17360 ret = GS_ALL_DONE;
17361 break;
17364 case OMP_ATOMIC:
17365 case OMP_ATOMIC_READ:
17366 case OMP_ATOMIC_CAPTURE_OLD:
17367 case OMP_ATOMIC_CAPTURE_NEW:
17368 ret = gimplify_omp_atomic (expr_p, pre_p);
17369 break;
17371 case TRANSACTION_EXPR:
17372 ret = gimplify_transaction (expr_p, pre_p);
17373 break;
17375 case TRUTH_AND_EXPR:
17376 case TRUTH_OR_EXPR:
17377 case TRUTH_XOR_EXPR:
17379 tree orig_type = TREE_TYPE (*expr_p);
17380 tree new_type, xop0, xop1;
17381 *expr_p = gimple_boolify (*expr_p);
17382 new_type = TREE_TYPE (*expr_p);
17383 if (!useless_type_conversion_p (orig_type, new_type))
17385 *expr_p = fold_convert_loc (input_location, orig_type, *expr_p);
17386 ret = GS_OK;
17387 break;
17390 /* Boolified binary truth expressions are semantically equivalent
17391 to bitwise binary expressions. Canonicalize them to the
17392 bitwise variant. */
17393 switch (TREE_CODE (*expr_p))
17395 case TRUTH_AND_EXPR:
17396 TREE_SET_CODE (*expr_p, BIT_AND_EXPR);
17397 break;
17398 case TRUTH_OR_EXPR:
17399 TREE_SET_CODE (*expr_p, BIT_IOR_EXPR);
17400 break;
17401 case TRUTH_XOR_EXPR:
17402 TREE_SET_CODE (*expr_p, BIT_XOR_EXPR);
17403 break;
17404 default:
17405 break;
17407 /* Now make sure that operands have compatible type to
17408 expression's new_type. */
17409 xop0 = TREE_OPERAND (*expr_p, 0);
17410 xop1 = TREE_OPERAND (*expr_p, 1);
17411 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop0)))
17412 TREE_OPERAND (*expr_p, 0) = fold_convert_loc (input_location,
17413 new_type,
17414 xop0);
17415 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop1)))
17416 TREE_OPERAND (*expr_p, 1) = fold_convert_loc (input_location,
17417 new_type,
17418 xop1);
17419 /* Continue classified as tcc_binary. */
17420 goto expr_2;
17423 case VEC_COND_EXPR:
17424 goto expr_3;
17426 case VEC_PERM_EXPR:
17427 /* Classified as tcc_expression. */
17428 goto expr_3;
17430 case BIT_INSERT_EXPR:
17431 /* Argument 3 is a constant. */
17432 goto expr_2;
17434 case POINTER_PLUS_EXPR:
17436 enum gimplify_status r0, r1;
17437 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
17438 post_p, is_gimple_val, fb_rvalue);
17439 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
17440 post_p, is_gimple_val, fb_rvalue);
17441 recalculate_side_effects (*expr_p);
17442 ret = MIN (r0, r1);
17443 break;
17446 default:
17447 switch (TREE_CODE_CLASS (TREE_CODE (*expr_p)))
17449 case tcc_comparison:
17450 /* Handle comparison of objects of non scalar mode aggregates
17451 with a call to memcmp. It would be nice to only have to do
17452 this for variable-sized objects, but then we'd have to allow
17453 the same nest of reference nodes we allow for MODIFY_EXPR and
17454 that's too complex.
17456 Compare scalar mode aggregates as scalar mode values. Using
17457 memcmp for them would be very inefficient at best, and is
17458 plain wrong if bitfields are involved. */
17459 if (error_operand_p (TREE_OPERAND (*expr_p, 1)))
17460 ret = GS_ERROR;
17461 else
17463 tree type = TREE_TYPE (TREE_OPERAND (*expr_p, 1));
17465 /* Vector comparisons need no boolification. */
17466 if (TREE_CODE (type) == VECTOR_TYPE)
17467 goto expr_2;
17468 else if (!AGGREGATE_TYPE_P (type))
17470 tree org_type = TREE_TYPE (*expr_p);
17471 *expr_p = gimple_boolify (*expr_p);
17472 if (!useless_type_conversion_p (org_type,
17473 TREE_TYPE (*expr_p)))
17475 *expr_p = fold_convert_loc (input_location,
17476 org_type, *expr_p);
17477 ret = GS_OK;
17479 else
17480 goto expr_2;
17482 else if (TYPE_MODE (type) != BLKmode)
17483 ret = gimplify_scalar_mode_aggregate_compare (expr_p);
17484 else
17485 ret = gimplify_variable_sized_compare (expr_p);
17487 break;
17489 /* If *EXPR_P does not need to be special-cased, handle it
17490 according to its class. */
17491 case tcc_unary:
17492 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
17493 post_p, is_gimple_val, fb_rvalue);
17494 break;
17496 case tcc_binary:
17497 expr_2:
17499 enum gimplify_status r0, r1;
17501 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
17502 post_p, is_gimple_val, fb_rvalue);
17503 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
17504 post_p, is_gimple_val, fb_rvalue);
17506 ret = MIN (r0, r1);
17507 break;
17510 expr_3:
17512 enum gimplify_status r0, r1, r2;
17514 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
17515 post_p, is_gimple_val, fb_rvalue);
17516 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
17517 post_p, is_gimple_val, fb_rvalue);
17518 r2 = gimplify_expr (&TREE_OPERAND (*expr_p, 2), pre_p,
17519 post_p, is_gimple_val, fb_rvalue);
17521 ret = MIN (MIN (r0, r1), r2);
17522 break;
17525 case tcc_declaration:
17526 case tcc_constant:
17527 ret = GS_ALL_DONE;
17528 goto dont_recalculate;
17530 default:
17531 gcc_unreachable ();
17534 recalculate_side_effects (*expr_p);
17536 dont_recalculate:
17537 break;
17540 gcc_assert (*expr_p || ret != GS_OK);
17542 while (ret == GS_OK);
17544 /* If we encountered an error_mark somewhere nested inside, either
17545 stub out the statement or propagate the error back out. */
17546 if (ret == GS_ERROR)
17548 if (is_statement)
17549 *expr_p = NULL;
17550 goto out;
17553 /* This was only valid as a return value from the langhook, which
17554 we handled. Make sure it doesn't escape from any other context. */
17555 gcc_assert (ret != GS_UNHANDLED);
17557 if (fallback == fb_none && *expr_p && !is_gimple_stmt (*expr_p))
17559 /* We aren't looking for a value, and we don't have a valid
17560 statement. If it doesn't have side-effects, throw it away.
17561 We can also get here with code such as "*&&L;", where L is
17562 a LABEL_DECL that is marked as FORCED_LABEL. */
17563 if (TREE_CODE (*expr_p) == LABEL_DECL
17564 || !TREE_SIDE_EFFECTS (*expr_p))
17565 *expr_p = NULL;
17566 else if (!TREE_THIS_VOLATILE (*expr_p))
17568 /* This is probably a _REF that contains something nested that
17569 has side effects. Recurse through the operands to find it. */
17570 enum tree_code code = TREE_CODE (*expr_p);
17572 switch (code)
17574 case COMPONENT_REF:
17575 case REALPART_EXPR:
17576 case IMAGPART_EXPR:
17577 case VIEW_CONVERT_EXPR:
17578 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
17579 gimple_test_f, fallback);
17580 break;
17582 case ARRAY_REF:
17583 case ARRAY_RANGE_REF:
17584 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
17585 gimple_test_f, fallback);
17586 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
17587 gimple_test_f, fallback);
17588 break;
17590 default:
17591 /* Anything else with side-effects must be converted to
17592 a valid statement before we get here. */
17593 gcc_unreachable ();
17596 *expr_p = NULL;
17598 else if (COMPLETE_TYPE_P (TREE_TYPE (*expr_p))
17599 && TYPE_MODE (TREE_TYPE (*expr_p)) != BLKmode
17600 && !is_empty_type (TREE_TYPE (*expr_p)))
17602 /* Historically, the compiler has treated a bare reference
17603 to a non-BLKmode volatile lvalue as forcing a load. */
17604 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (*expr_p));
17606 /* Normally, we do not want to create a temporary for a
17607 TREE_ADDRESSABLE type because such a type should not be
17608 copied by bitwise-assignment. However, we make an
17609 exception here, as all we are doing here is ensuring that
17610 we read the bytes that make up the type. We use
17611 create_tmp_var_raw because create_tmp_var will abort when
17612 given a TREE_ADDRESSABLE type. */
17613 tree tmp = create_tmp_var_raw (type, "vol");
17614 gimple_add_tmp_var (tmp);
17615 gimplify_assign (tmp, *expr_p, pre_p);
17616 *expr_p = NULL;
17618 else
17619 /* We can't do anything useful with a volatile reference to
17620 an incomplete type, so just throw it away. Likewise for
17621 a BLKmode type, since any implicit inner load should
17622 already have been turned into an explicit one by the
17623 gimplification process. */
17624 *expr_p = NULL;
17627 /* If we are gimplifying at the statement level, we're done. Tack
17628 everything together and return. */
17629 if (fallback == fb_none || is_statement)
17631 /* Since *EXPR_P has been converted into a GIMPLE tuple, clear
17632 it out for GC to reclaim it. */
17633 *expr_p = NULL_TREE;
17635 if (!gimple_seq_empty_p (internal_pre)
17636 || !gimple_seq_empty_p (internal_post))
17638 gimplify_seq_add_seq (&internal_pre, internal_post);
17639 gimplify_seq_add_seq (pre_p, internal_pre);
17642 /* The result of gimplifying *EXPR_P is going to be the last few
17643 statements in *PRE_P and *POST_P. Add location information
17644 to all the statements that were added by the gimplification
17645 helpers. */
17646 if (!gimple_seq_empty_p (*pre_p))
17647 annotate_all_with_location_after (*pre_p, pre_last_gsi, input_location);
17649 if (!gimple_seq_empty_p (*post_p))
17650 annotate_all_with_location_after (*post_p, post_last_gsi,
17651 input_location);
17653 goto out;
17656 #ifdef ENABLE_GIMPLE_CHECKING
17657 if (*expr_p)
17659 enum tree_code code = TREE_CODE (*expr_p);
17660 /* These expressions should already be in gimple IR form. */
17661 gcc_assert (code != MODIFY_EXPR
17662 && code != ASM_EXPR
17663 && code != BIND_EXPR
17664 && code != CATCH_EXPR
17665 && (code != COND_EXPR || gimplify_ctxp->allow_rhs_cond_expr)
17666 && code != EH_FILTER_EXPR
17667 && code != GOTO_EXPR
17668 && code != LABEL_EXPR
17669 && code != LOOP_EXPR
17670 && code != SWITCH_EXPR
17671 && code != TRY_FINALLY_EXPR
17672 && code != EH_ELSE_EXPR
17673 && code != OACC_PARALLEL
17674 && code != OACC_KERNELS
17675 && code != OACC_SERIAL
17676 && code != OACC_DATA
17677 && code != OACC_HOST_DATA
17678 && code != OACC_DECLARE
17679 && code != OACC_UPDATE
17680 && code != OACC_ENTER_DATA
17681 && code != OACC_EXIT_DATA
17682 && code != OACC_CACHE
17683 && code != OMP_CRITICAL
17684 && code != OMP_FOR
17685 && code != OACC_LOOP
17686 && code != OMP_MASTER
17687 && code != OMP_MASKED
17688 && code != OMP_TASKGROUP
17689 && code != OMP_ORDERED
17690 && code != OMP_PARALLEL
17691 && code != OMP_SCAN
17692 && code != OMP_SECTIONS
17693 && code != OMP_SECTION
17694 && code != OMP_STRUCTURED_BLOCK
17695 && code != OMP_SINGLE
17696 && code != OMP_SCOPE);
17698 #endif
17700 /* Otherwise we're gimplifying a subexpression, so the resulting
17701 value is interesting. If it's a valid operand that matches
17702 GIMPLE_TEST_F, we're done. Unless we are handling some
17703 post-effects internally; if that's the case, we need to copy into
17704 a temporary before adding the post-effects to POST_P. */
17705 if (gimple_seq_empty_p (internal_post) && (*gimple_test_f) (*expr_p))
17706 goto out;
17708 /* Otherwise, we need to create a new temporary for the gimplified
17709 expression. */
17711 /* We can't return an lvalue if we have an internal postqueue. The
17712 object the lvalue refers to would (probably) be modified by the
17713 postqueue; we need to copy the value out first, which means an
17714 rvalue. */
17715 if ((fallback & fb_lvalue)
17716 && gimple_seq_empty_p (internal_post)
17717 && is_gimple_addressable (*expr_p))
17719 /* An lvalue will do. Take the address of the expression, store it
17720 in a temporary, and replace the expression with an INDIRECT_REF of
17721 that temporary. */
17722 tree ref_alias_type = reference_alias_ptr_type (*expr_p);
17723 unsigned int ref_align = get_object_alignment (*expr_p);
17724 tree ref_type = TREE_TYPE (*expr_p);
17725 tmp = build_fold_addr_expr_loc (input_location, *expr_p);
17726 gimplify_expr (&tmp, pre_p, post_p, is_gimple_reg, fb_rvalue);
17727 if (TYPE_ALIGN (ref_type) != ref_align)
17728 ref_type = build_aligned_type (ref_type, ref_align);
17729 *expr_p = build2 (MEM_REF, ref_type,
17730 tmp, build_zero_cst (ref_alias_type));
17732 else if ((fallback & fb_rvalue) && is_gimple_reg_rhs_or_call (*expr_p))
17734 /* An rvalue will do. Assign the gimplified expression into a
17735 new temporary TMP and replace the original expression with
17736 TMP. First, make sure that the expression has a type so that
17737 it can be assigned into a temporary. */
17738 gcc_assert (!VOID_TYPE_P (TREE_TYPE (*expr_p)));
17739 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
17741 else
17743 #ifdef ENABLE_GIMPLE_CHECKING
17744 if (!(fallback & fb_mayfail))
17746 fprintf (stderr, "gimplification failed:\n");
17747 print_generic_expr (stderr, *expr_p);
17748 debug_tree (*expr_p);
17749 internal_error ("gimplification failed");
17751 #endif
17752 gcc_assert (fallback & fb_mayfail);
17754 /* If this is an asm statement, and the user asked for the
17755 impossible, don't die. Fail and let gimplify_asm_expr
17756 issue an error. */
17757 ret = GS_ERROR;
17758 goto out;
17761 /* Make sure the temporary matches our predicate. */
17762 gcc_assert ((*gimple_test_f) (*expr_p));
17764 if (!gimple_seq_empty_p (internal_post))
17766 annotate_all_with_location (internal_post, input_location);
17767 gimplify_seq_add_seq (pre_p, internal_post);
17770 out:
17771 input_location = saved_location;
17772 return ret;
17775 /* Like gimplify_expr but make sure the gimplified result is not itself
17776 a SSA name (but a decl if it were). Temporaries required by
17777 evaluating *EXPR_P may be still SSA names. */
17779 static enum gimplify_status
17780 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
17781 bool (*gimple_test_f) (tree), fallback_t fallback,
17782 bool allow_ssa)
17784 enum gimplify_status ret = gimplify_expr (expr_p, pre_p, post_p,
17785 gimple_test_f, fallback);
17786 if (! allow_ssa
17787 && TREE_CODE (*expr_p) == SSA_NAME)
17788 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, NULL, false);
17789 return ret;
17792 /* Look through TYPE for variable-sized objects and gimplify each such
17793 size that we find. Add to LIST_P any statements generated. */
17795 void
17796 gimplify_type_sizes (tree type, gimple_seq *list_p)
17798 if (type == NULL || type == error_mark_node)
17799 return;
17801 const bool ignored_p
17802 = TYPE_NAME (type)
17803 && TREE_CODE (TYPE_NAME (type)) == TYPE_DECL
17804 && DECL_IGNORED_P (TYPE_NAME (type));
17805 tree t;
17807 /* We first do the main variant, then copy into any other variants. */
17808 type = TYPE_MAIN_VARIANT (type);
17810 /* Avoid infinite recursion. */
17811 if (TYPE_SIZES_GIMPLIFIED (type))
17812 return;
17814 TYPE_SIZES_GIMPLIFIED (type) = 1;
17816 switch (TREE_CODE (type))
17818 case INTEGER_TYPE:
17819 case ENUMERAL_TYPE:
17820 case BOOLEAN_TYPE:
17821 case REAL_TYPE:
17822 case FIXED_POINT_TYPE:
17823 gimplify_one_sizepos (&TYPE_MIN_VALUE (type), list_p);
17824 gimplify_one_sizepos (&TYPE_MAX_VALUE (type), list_p);
17826 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
17828 TYPE_MIN_VALUE (t) = TYPE_MIN_VALUE (type);
17829 TYPE_MAX_VALUE (t) = TYPE_MAX_VALUE (type);
17831 break;
17833 case ARRAY_TYPE:
17834 /* These types may not have declarations, so handle them here. */
17835 gimplify_type_sizes (TREE_TYPE (type), list_p);
17836 gimplify_type_sizes (TYPE_DOMAIN (type), list_p);
17837 /* Ensure VLA bounds aren't removed, for -O0 they should be variables
17838 with assigned stack slots, for -O1+ -g they should be tracked
17839 by VTA. */
17840 if (!ignored_p
17841 && TYPE_DOMAIN (type)
17842 && INTEGRAL_TYPE_P (TYPE_DOMAIN (type)))
17844 t = TYPE_MIN_VALUE (TYPE_DOMAIN (type));
17845 if (t && VAR_P (t) && DECL_ARTIFICIAL (t))
17846 DECL_IGNORED_P (t) = 0;
17847 t = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
17848 if (t && VAR_P (t) && DECL_ARTIFICIAL (t))
17849 DECL_IGNORED_P (t) = 0;
17851 break;
17853 case RECORD_TYPE:
17854 case UNION_TYPE:
17855 case QUAL_UNION_TYPE:
17856 for (tree field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
17857 if (TREE_CODE (field) == FIELD_DECL)
17859 gimplify_one_sizepos (&DECL_FIELD_OFFSET (field), list_p);
17860 /* Likewise, ensure variable offsets aren't removed. */
17861 if (!ignored_p
17862 && (t = DECL_FIELD_OFFSET (field))
17863 && VAR_P (t)
17864 && DECL_ARTIFICIAL (t))
17865 DECL_IGNORED_P (t) = 0;
17866 gimplify_one_sizepos (&DECL_SIZE (field), list_p);
17867 gimplify_one_sizepos (&DECL_SIZE_UNIT (field), list_p);
17868 gimplify_type_sizes (TREE_TYPE (field), list_p);
17870 break;
17872 case POINTER_TYPE:
17873 case REFERENCE_TYPE:
17874 /* We used to recurse on the pointed-to type here, which turned out to
17875 be incorrect because its definition might refer to variables not
17876 yet initialized at this point if a forward declaration is involved.
17878 It was actually useful for anonymous pointed-to types to ensure
17879 that the sizes evaluation dominates every possible later use of the
17880 values. Restricting to such types here would be safe since there
17881 is no possible forward declaration around, but would introduce an
17882 undesirable middle-end semantic to anonymity. We then defer to
17883 front-ends the responsibility of ensuring that the sizes are
17884 evaluated both early and late enough, e.g. by attaching artificial
17885 type declarations to the tree. */
17886 break;
17888 default:
17889 break;
17892 gimplify_one_sizepos (&TYPE_SIZE (type), list_p);
17893 gimplify_one_sizepos (&TYPE_SIZE_UNIT (type), list_p);
17895 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
17897 TYPE_SIZE (t) = TYPE_SIZE (type);
17898 TYPE_SIZE_UNIT (t) = TYPE_SIZE_UNIT (type);
17899 TYPE_SIZES_GIMPLIFIED (t) = 1;
17903 /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
17904 a size or position, has had all of its SAVE_EXPRs evaluated.
17905 We add any required statements to *STMT_P. */
17907 void
17908 gimplify_one_sizepos (tree *expr_p, gimple_seq *stmt_p)
17910 tree expr = *expr_p;
17912 /* We don't do anything if the value isn't there, is constant, or contains
17913 A PLACEHOLDER_EXPR. We also don't want to do anything if it's already
17914 a VAR_DECL. If it's a VAR_DECL from another function, the gimplifier
17915 will want to replace it with a new variable, but that will cause problems
17916 if this type is from outside the function. It's OK to have that here. */
17917 if (expr == NULL_TREE
17918 || is_gimple_constant (expr)
17919 || VAR_P (expr)
17920 || CONTAINS_PLACEHOLDER_P (expr))
17921 return;
17923 *expr_p = unshare_expr (expr);
17925 /* SSA names in decl/type fields are a bad idea - they'll get reclaimed
17926 if the def vanishes. */
17927 gimplify_expr (expr_p, stmt_p, NULL, is_gimple_val, fb_rvalue, false);
17929 /* If expr wasn't already is_gimple_sizepos or is_gimple_constant from the
17930 FE, ensure that it is a VAR_DECL, otherwise we might handle some decls
17931 as gimplify_vla_decl even when they would have all sizes INTEGER_CSTs. */
17932 if (is_gimple_constant (*expr_p))
17933 *expr_p = get_initialized_tmp_var (*expr_p, stmt_p, NULL, false);
17936 /* Gimplify the body of statements of FNDECL and return a GIMPLE_BIND node
17937 containing the sequence of corresponding GIMPLE statements. If DO_PARMS
17938 is true, also gimplify the parameters. */
17940 gbind *
17941 gimplify_body (tree fndecl, bool do_parms)
17943 location_t saved_location = input_location;
17944 gimple_seq parm_stmts, parm_cleanup = NULL, seq;
17945 gimple *outer_stmt;
17946 gbind *outer_bind;
17948 timevar_push (TV_TREE_GIMPLIFY);
17950 init_tree_ssa (cfun);
17952 /* Initialize for optimize_insn_for_s{ize,peed}_p possibly called during
17953 gimplification. */
17954 default_rtl_profile ();
17956 gcc_assert (gimplify_ctxp == NULL);
17957 push_gimplify_context (true);
17959 if (flag_openacc || flag_openmp)
17961 gcc_assert (gimplify_omp_ctxp == NULL);
17962 if (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (fndecl)))
17963 gimplify_omp_ctxp = new_omp_context (ORT_IMPLICIT_TARGET);
17966 /* Unshare most shared trees in the body and in that of any nested functions.
17967 It would seem we don't have to do this for nested functions because
17968 they are supposed to be output and then the outer function gimplified
17969 first, but the g++ front end doesn't always do it that way. */
17970 unshare_body (fndecl);
17971 unvisit_body (fndecl);
17973 /* Make sure input_location isn't set to something weird. */
17974 input_location = DECL_SOURCE_LOCATION (fndecl);
17976 /* Resolve callee-copies. This has to be done before processing
17977 the body so that DECL_VALUE_EXPR gets processed correctly. */
17978 parm_stmts = do_parms ? gimplify_parameters (&parm_cleanup) : NULL;
17980 /* Gimplify the function's body. */
17981 seq = NULL;
17982 gimplify_stmt (&DECL_SAVED_TREE (fndecl), &seq);
17983 outer_stmt = gimple_seq_first_nondebug_stmt (seq);
17984 if (!outer_stmt)
17986 outer_stmt = gimple_build_nop ();
17987 gimplify_seq_add_stmt (&seq, outer_stmt);
17990 /* The body must contain exactly one statement, a GIMPLE_BIND. If this is
17991 not the case, wrap everything in a GIMPLE_BIND to make it so. */
17992 if (gimple_code (outer_stmt) == GIMPLE_BIND
17993 && (gimple_seq_first_nondebug_stmt (seq)
17994 == gimple_seq_last_nondebug_stmt (seq)))
17996 outer_bind = as_a <gbind *> (outer_stmt);
17997 if (gimple_seq_first_stmt (seq) != outer_stmt
17998 || gimple_seq_last_stmt (seq) != outer_stmt)
18000 /* If there are debug stmts before or after outer_stmt, move them
18001 inside of outer_bind body. */
18002 gimple_stmt_iterator gsi = gsi_for_stmt (outer_stmt, &seq);
18003 gimple_seq second_seq = NULL;
18004 if (gimple_seq_first_stmt (seq) != outer_stmt
18005 && gimple_seq_last_stmt (seq) != outer_stmt)
18007 second_seq = gsi_split_seq_after (gsi);
18008 gsi_remove (&gsi, false);
18010 else if (gimple_seq_first_stmt (seq) != outer_stmt)
18011 gsi_remove (&gsi, false);
18012 else
18014 gsi_remove (&gsi, false);
18015 second_seq = seq;
18016 seq = NULL;
18018 gimple_seq_add_seq_without_update (&seq,
18019 gimple_bind_body (outer_bind));
18020 gimple_seq_add_seq_without_update (&seq, second_seq);
18021 gimple_bind_set_body (outer_bind, seq);
18024 else
18025 outer_bind = gimple_build_bind (NULL_TREE, seq, NULL);
18027 DECL_SAVED_TREE (fndecl) = NULL_TREE;
18029 /* If we had callee-copies statements, insert them at the beginning
18030 of the function and clear DECL_VALUE_EXPR_P on the parameters. */
18031 if (!gimple_seq_empty_p (parm_stmts))
18033 tree parm;
18035 gimplify_seq_add_seq (&parm_stmts, gimple_bind_body (outer_bind));
18036 if (parm_cleanup)
18038 gtry *g = gimple_build_try (parm_stmts, parm_cleanup,
18039 GIMPLE_TRY_FINALLY);
18040 parm_stmts = NULL;
18041 gimple_seq_add_stmt (&parm_stmts, g);
18043 gimple_bind_set_body (outer_bind, parm_stmts);
18045 for (parm = DECL_ARGUMENTS (current_function_decl);
18046 parm; parm = DECL_CHAIN (parm))
18047 if (DECL_HAS_VALUE_EXPR_P (parm))
18049 DECL_HAS_VALUE_EXPR_P (parm) = 0;
18050 DECL_IGNORED_P (parm) = 0;
18054 if ((flag_openacc || flag_openmp || flag_openmp_simd)
18055 && gimplify_omp_ctxp)
18057 delete_omp_context (gimplify_omp_ctxp);
18058 gimplify_omp_ctxp = NULL;
18061 pop_gimplify_context (outer_bind);
18062 gcc_assert (gimplify_ctxp == NULL);
18064 if (flag_checking && !seen_error ())
18065 verify_gimple_in_seq (gimple_bind_body (outer_bind));
18067 timevar_pop (TV_TREE_GIMPLIFY);
18068 input_location = saved_location;
18070 return outer_bind;
18073 typedef char *char_p; /* For DEF_VEC_P. */
18075 /* Return whether we should exclude FNDECL from instrumentation. */
18077 static bool
18078 flag_instrument_functions_exclude_p (tree fndecl)
18080 vec<char_p> *v;
18082 v = (vec<char_p> *) flag_instrument_functions_exclude_functions;
18083 if (v && v->length () > 0)
18085 const char *name;
18086 int i;
18087 char *s;
18089 name = lang_hooks.decl_printable_name (fndecl, 1);
18090 FOR_EACH_VEC_ELT (*v, i, s)
18091 if (strstr (name, s) != NULL)
18092 return true;
18095 v = (vec<char_p> *) flag_instrument_functions_exclude_files;
18096 if (v && v->length () > 0)
18098 const char *name;
18099 int i;
18100 char *s;
18102 name = DECL_SOURCE_FILE (fndecl);
18103 FOR_EACH_VEC_ELT (*v, i, s)
18104 if (strstr (name, s) != NULL)
18105 return true;
18108 return false;
18111 /* Build a call to the instrumentation function FNCODE and add it to SEQ.
18112 If COND_VAR is not NULL, it is a boolean variable guarding the call to
18113 the instrumentation function. IF STMT is not NULL, it is a statement
18114 to be executed just before the call to the instrumentation function. */
18116 static void
18117 build_instrumentation_call (gimple_seq *seq, enum built_in_function fncode,
18118 tree cond_var, gimple *stmt)
18120 /* The instrumentation hooks aren't going to call the instrumented
18121 function and the address they receive is expected to be matchable
18122 against symbol addresses. Make sure we don't create a trampoline,
18123 in case the current function is nested. */
18124 tree this_fn_addr = build_fold_addr_expr (current_function_decl);
18125 TREE_NO_TRAMPOLINE (this_fn_addr) = 1;
18127 tree label_true, label_false;
18128 if (cond_var)
18130 label_true = create_artificial_label (UNKNOWN_LOCATION);
18131 label_false = create_artificial_label (UNKNOWN_LOCATION);
18132 gcond *cond = gimple_build_cond (EQ_EXPR, cond_var, boolean_false_node,
18133 label_true, label_false);
18134 gimplify_seq_add_stmt (seq, cond);
18135 gimplify_seq_add_stmt (seq, gimple_build_label (label_true));
18136 gimplify_seq_add_stmt (seq, gimple_build_predict (PRED_COLD_LABEL,
18137 NOT_TAKEN));
18140 if (stmt)
18141 gimplify_seq_add_stmt (seq, stmt);
18143 tree x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
18144 gcall *call = gimple_build_call (x, 1, integer_zero_node);
18145 tree tmp_var = create_tmp_var (ptr_type_node, "return_addr");
18146 gimple_call_set_lhs (call, tmp_var);
18147 gimplify_seq_add_stmt (seq, call);
18148 x = builtin_decl_implicit (fncode);
18149 call = gimple_build_call (x, 2, this_fn_addr, tmp_var);
18150 gimplify_seq_add_stmt (seq, call);
18152 if (cond_var)
18153 gimplify_seq_add_stmt (seq, gimple_build_label (label_false));
18156 /* Entry point to the gimplification pass. FNDECL is the FUNCTION_DECL
18157 node for the function we want to gimplify.
18159 Return the sequence of GIMPLE statements corresponding to the body
18160 of FNDECL. */
18162 void
18163 gimplify_function_tree (tree fndecl)
18165 gimple_seq seq;
18166 gbind *bind;
18168 gcc_assert (!gimple_body (fndecl));
18170 if (DECL_STRUCT_FUNCTION (fndecl))
18171 push_cfun (DECL_STRUCT_FUNCTION (fndecl));
18172 else
18173 push_struct_function (fndecl);
18175 /* Tentatively set PROP_gimple_lva here, and reset it in gimplify_va_arg_expr
18176 if necessary. */
18177 cfun->curr_properties |= PROP_gimple_lva;
18179 if (asan_sanitize_use_after_scope ())
18180 asan_poisoned_variables = new hash_set<tree> ();
18181 bind = gimplify_body (fndecl, true);
18182 if (asan_poisoned_variables)
18184 delete asan_poisoned_variables;
18185 asan_poisoned_variables = NULL;
18188 /* The tree body of the function is no longer needed, replace it
18189 with the new GIMPLE body. */
18190 seq = NULL;
18191 gimple_seq_add_stmt (&seq, bind);
18192 gimple_set_body (fndecl, seq);
18194 /* If we're instrumenting function entry/exit, then prepend the call to
18195 the entry hook and wrap the whole function in a TRY_FINALLY_EXPR to
18196 catch the exit hook. */
18197 /* ??? Add some way to ignore exceptions for this TFE. */
18198 if (flag_instrument_function_entry_exit
18199 && !DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT (fndecl)
18200 /* Do not instrument extern inline functions. */
18201 && !(DECL_DECLARED_INLINE_P (fndecl)
18202 && DECL_EXTERNAL (fndecl)
18203 && DECL_DISREGARD_INLINE_LIMITS (fndecl))
18204 && !flag_instrument_functions_exclude_p (fndecl))
18206 gimple_seq body = NULL, cleanup = NULL;
18207 gassign *assign;
18208 tree cond_var;
18210 /* If -finstrument-functions-once is specified, generate:
18212 static volatile bool C.0 = false;
18213 bool tmp_called;
18215 tmp_called = C.0;
18216 if (!tmp_called)
18218 C.0 = true;
18219 [call profiling enter function]
18222 without specific protection for data races. */
18223 if (flag_instrument_function_entry_exit > 1)
18225 tree first_var
18226 = build_decl (DECL_SOURCE_LOCATION (current_function_decl),
18227 VAR_DECL,
18228 create_tmp_var_name ("C"),
18229 boolean_type_node);
18230 DECL_ARTIFICIAL (first_var) = 1;
18231 DECL_IGNORED_P (first_var) = 1;
18232 TREE_STATIC (first_var) = 1;
18233 TREE_THIS_VOLATILE (first_var) = 1;
18234 TREE_USED (first_var) = 1;
18235 DECL_INITIAL (first_var) = boolean_false_node;
18236 varpool_node::add (first_var);
18238 cond_var = create_tmp_var (boolean_type_node, "tmp_called");
18239 assign = gimple_build_assign (cond_var, first_var);
18240 gimplify_seq_add_stmt (&body, assign);
18242 assign = gimple_build_assign (first_var, boolean_true_node);
18245 else
18247 cond_var = NULL_TREE;
18248 assign = NULL;
18251 build_instrumentation_call (&body, BUILT_IN_PROFILE_FUNC_ENTER,
18252 cond_var, assign);
18254 /* If -finstrument-functions-once is specified, generate:
18256 if (!tmp_called)
18257 [call profiling exit function]
18259 without specific protection for data races. */
18260 build_instrumentation_call (&cleanup, BUILT_IN_PROFILE_FUNC_EXIT,
18261 cond_var, NULL);
18263 gimple *tf = gimple_build_try (seq, cleanup, GIMPLE_TRY_FINALLY);
18264 gimplify_seq_add_stmt (&body, tf);
18265 gbind *new_bind = gimple_build_bind (NULL, body, NULL);
18267 /* Replace the current function body with the body
18268 wrapped in the try/finally TF. */
18269 seq = NULL;
18270 gimple_seq_add_stmt (&seq, new_bind);
18271 gimple_set_body (fndecl, seq);
18272 bind = new_bind;
18275 if (sanitize_flags_p (SANITIZE_THREAD)
18276 && param_tsan_instrument_func_entry_exit)
18278 gcall *call = gimple_build_call_internal (IFN_TSAN_FUNC_EXIT, 0);
18279 gimple *tf = gimple_build_try (seq, call, GIMPLE_TRY_FINALLY);
18280 gbind *new_bind = gimple_build_bind (NULL, tf, NULL);
18281 /* Replace the current function body with the body
18282 wrapped in the try/finally TF. */
18283 seq = NULL;
18284 gimple_seq_add_stmt (&seq, new_bind);
18285 gimple_set_body (fndecl, seq);
18288 DECL_SAVED_TREE (fndecl) = NULL_TREE;
18289 cfun->curr_properties |= PROP_gimple_any;
18291 pop_cfun ();
18293 dump_function (TDI_gimple, fndecl);
18296 /* Return a dummy expression of type TYPE in order to keep going after an
18297 error. */
18299 static tree
18300 dummy_object (tree type)
18302 tree t = build_int_cst (build_pointer_type (type), 0);
18303 return build2 (MEM_REF, type, t, t);
18306 /* Gimplify __builtin_va_arg, aka VA_ARG_EXPR, which is not really a
18307 builtin function, but a very special sort of operator. */
18309 enum gimplify_status
18310 gimplify_va_arg_expr (tree *expr_p, gimple_seq *pre_p,
18311 gimple_seq *post_p ATTRIBUTE_UNUSED)
18313 tree promoted_type, have_va_type;
18314 tree valist = TREE_OPERAND (*expr_p, 0);
18315 tree type = TREE_TYPE (*expr_p);
18316 tree t, tag, aptag;
18317 location_t loc = EXPR_LOCATION (*expr_p);
18319 /* Verify that valist is of the proper type. */
18320 have_va_type = TREE_TYPE (valist);
18321 if (have_va_type == error_mark_node)
18322 return GS_ERROR;
18323 have_va_type = targetm.canonical_va_list_type (have_va_type);
18324 if (have_va_type == NULL_TREE
18325 && POINTER_TYPE_P (TREE_TYPE (valist)))
18326 /* Handle 'Case 1: Not an array type' from c-common.cc/build_va_arg. */
18327 have_va_type
18328 = targetm.canonical_va_list_type (TREE_TYPE (TREE_TYPE (valist)));
18329 gcc_assert (have_va_type != NULL_TREE);
18331 /* Generate a diagnostic for requesting data of a type that cannot
18332 be passed through `...' due to type promotion at the call site. */
18333 if ((promoted_type = lang_hooks.types.type_promotes_to (type))
18334 != type)
18336 static bool gave_help;
18337 bool warned;
18338 /* Use the expansion point to handle cases such as passing bool (defined
18339 in a system header) through `...'. */
18340 location_t xloc
18341 = expansion_point_location_if_in_system_header (loc);
18343 /* Unfortunately, this is merely undefined, rather than a constraint
18344 violation, so we cannot make this an error. If this call is never
18345 executed, the program is still strictly conforming. */
18346 auto_diagnostic_group d;
18347 warned = warning_at (xloc, 0,
18348 "%qT is promoted to %qT when passed through %<...%>",
18349 type, promoted_type);
18350 if (!gave_help && warned)
18352 gave_help = true;
18353 inform (xloc, "(so you should pass %qT not %qT to %<va_arg%>)",
18354 promoted_type, type);
18357 /* We can, however, treat "undefined" any way we please.
18358 Call abort to encourage the user to fix the program. */
18359 if (warned)
18360 inform (xloc, "if this code is reached, the program will abort");
18361 /* Before the abort, allow the evaluation of the va_list
18362 expression to exit or longjmp. */
18363 gimplify_and_add (valist, pre_p);
18364 t = build_call_expr_loc (loc,
18365 builtin_decl_implicit (BUILT_IN_TRAP), 0);
18366 gimplify_and_add (t, pre_p);
18368 /* This is dead code, but go ahead and finish so that the
18369 mode of the result comes out right. */
18370 *expr_p = dummy_object (type);
18371 return GS_ALL_DONE;
18374 tag = build_int_cst (build_pointer_type (type), 0);
18375 aptag = build_int_cst (TREE_TYPE (valist), 0);
18377 *expr_p = build_call_expr_internal_loc (loc, IFN_VA_ARG, type, 3,
18378 valist, tag, aptag);
18380 /* Clear the tentatively set PROP_gimple_lva, to indicate that IFN_VA_ARG
18381 needs to be expanded. */
18382 cfun->curr_properties &= ~PROP_gimple_lva;
18384 return GS_OK;
18387 /* Build a new GIMPLE_ASSIGN tuple and append it to the end of *SEQ_P.
18389 DST/SRC are the destination and source respectively. You can pass
18390 ungimplified trees in DST or SRC, in which case they will be
18391 converted to a gimple operand if necessary.
18393 This function returns the newly created GIMPLE_ASSIGN tuple. */
18395 gimple *
18396 gimplify_assign (tree dst, tree src, gimple_seq *seq_p)
18398 tree t = build2 (MODIFY_EXPR, TREE_TYPE (dst), dst, src);
18399 gimplify_and_add (t, seq_p);
18400 ggc_free (t);
18401 return gimple_seq_last_stmt (*seq_p);
18404 inline hashval_t
18405 gimplify_hasher::hash (const elt_t *p)
18407 tree t = p->val;
18408 return iterative_hash_expr (t, 0);
18411 inline bool
18412 gimplify_hasher::equal (const elt_t *p1, const elt_t *p2)
18414 tree t1 = p1->val;
18415 tree t2 = p2->val;
18416 enum tree_code code = TREE_CODE (t1);
18418 if (TREE_CODE (t2) != code
18419 || TREE_TYPE (t1) != TREE_TYPE (t2))
18420 return false;
18422 if (!operand_equal_p (t1, t2, 0))
18423 return false;
18425 /* Only allow them to compare equal if they also hash equal; otherwise
18426 results are nondeterminate, and we fail bootstrap comparison. */
18427 gcc_checking_assert (hash (p1) == hash (p2));
18429 return true;