tree-optimization/114485 - neg induction with partial vectors
[official-gcc.git] / gcc / gimplify.cc
blobd64bbf3ffbd7712bba84572680c1f1fb8348cba5
1 /* Tree lowering pass. This pass converts the GENERIC functions-as-trees
2 tree representation into the GIMPLE form.
3 Copyright (C) 2002-2024 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 /* If we failed to gimplify VAL then we can end up with the temporary
656 SSA name not having a definition. In this case return a decl. */
657 if (TREE_CODE (t) == SSA_NAME && ! SSA_NAME_DEF_STMT (t))
658 return lookup_tmp_var (val, is_formal, not_gimple_reg);
660 return t;
663 /* Return a formal temporary variable initialized with VAL. PRE_P is as
664 in gimplify_expr. Only use this function if:
666 1) The value of the unfactored expression represented by VAL will not
667 change between the initialization and use of the temporary, and
668 2) The temporary will not be otherwise modified.
670 For instance, #1 means that this is inappropriate for SAVE_EXPR temps,
671 and #2 means it is inappropriate for && temps.
673 For other cases, use get_initialized_tmp_var instead. */
675 tree
676 get_formal_tmp_var (tree val, gimple_seq *pre_p)
678 return internal_get_tmp_var (val, pre_p, NULL, true, true, false);
681 /* Return a temporary variable initialized with VAL. PRE_P and POST_P
682 are as in gimplify_expr. */
684 tree
685 get_initialized_tmp_var (tree val, gimple_seq *pre_p,
686 gimple_seq *post_p /* = NULL */,
687 bool allow_ssa /* = true */)
689 return internal_get_tmp_var (val, pre_p, post_p, false, allow_ssa, false);
692 /* Declare all the variables in VARS in SCOPE. If DEBUG_INFO is true,
693 generate debug info for them; otherwise don't. */
695 void
696 declare_vars (tree vars, gimple *gs, bool debug_info)
698 tree last = vars;
699 if (last)
701 tree temps, block;
703 gbind *scope = as_a <gbind *> (gs);
705 temps = nreverse (last);
707 block = gimple_bind_block (scope);
708 gcc_assert (!block || TREE_CODE (block) == BLOCK);
709 if (!block || !debug_info)
711 DECL_CHAIN (last) = gimple_bind_vars (scope);
712 gimple_bind_set_vars (scope, temps);
714 else
716 /* We need to attach the nodes both to the BIND_EXPR and to its
717 associated BLOCK for debugging purposes. The key point here
718 is that the BLOCK_VARS of the BIND_EXPR_BLOCK of a BIND_EXPR
719 is a subchain of the BIND_EXPR_VARS of the BIND_EXPR. */
720 if (BLOCK_VARS (block))
721 BLOCK_VARS (block) = chainon (BLOCK_VARS (block), temps);
722 else
724 gimple_bind_set_vars (scope,
725 chainon (gimple_bind_vars (scope), temps));
726 BLOCK_VARS (block) = temps;
732 /* For VAR a VAR_DECL of variable size, try to find a constant upper bound
733 for the size and adjust DECL_SIZE/DECL_SIZE_UNIT accordingly. Abort if
734 no such upper bound can be obtained. */
736 static void
737 force_constant_size (tree var)
739 /* The only attempt we make is by querying the maximum size of objects
740 of the variable's type. */
742 HOST_WIDE_INT max_size;
744 gcc_assert (VAR_P (var));
746 max_size = max_int_size_in_bytes (TREE_TYPE (var));
748 gcc_assert (max_size >= 0);
750 DECL_SIZE_UNIT (var)
751 = build_int_cst (TREE_TYPE (DECL_SIZE_UNIT (var)), max_size);
752 DECL_SIZE (var)
753 = build_int_cst (TREE_TYPE (DECL_SIZE (var)), max_size * BITS_PER_UNIT);
756 /* Push the temporary variable TMP into the current binding. */
758 void
759 gimple_add_tmp_var_fn (struct function *fn, tree tmp)
761 gcc_assert (!DECL_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
763 /* Later processing assumes that the object size is constant, which might
764 not be true at this point. Force the use of a constant upper bound in
765 this case. */
766 if (!tree_fits_poly_uint64_p (DECL_SIZE_UNIT (tmp)))
767 force_constant_size (tmp);
769 DECL_CONTEXT (tmp) = fn->decl;
770 DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
772 record_vars_into (tmp, fn->decl);
775 /* Push the temporary variable TMP into the current binding. */
777 void
778 gimple_add_tmp_var (tree tmp)
780 gcc_assert (!DECL_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
782 /* Later processing assumes that the object size is constant, which might
783 not be true at this point. Force the use of a constant upper bound in
784 this case. */
785 if (!tree_fits_poly_uint64_p (DECL_SIZE_UNIT (tmp)))
786 force_constant_size (tmp);
788 DECL_CONTEXT (tmp) = current_function_decl;
789 DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
791 if (gimplify_ctxp)
793 DECL_CHAIN (tmp) = gimplify_ctxp->temps;
794 gimplify_ctxp->temps = tmp;
796 /* Mark temporaries local within the nearest enclosing parallel. */
797 if (gimplify_omp_ctxp)
799 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
800 int flag = GOVD_LOCAL | GOVD_SEEN;
801 while (ctx
802 && (ctx->region_type == ORT_WORKSHARE
803 || ctx->region_type == ORT_TASKGROUP
804 || ctx->region_type == ORT_SIMD
805 || ctx->region_type == ORT_ACC))
807 if (ctx->region_type == ORT_SIMD
808 && TREE_ADDRESSABLE (tmp)
809 && !TREE_STATIC (tmp))
811 if (TREE_CODE (DECL_SIZE_UNIT (tmp)) != INTEGER_CST)
812 ctx->add_safelen1 = true;
813 else if (ctx->in_for_exprs)
814 flag = GOVD_PRIVATE;
815 else
816 flag = GOVD_PRIVATE | GOVD_SEEN;
817 break;
819 ctx = ctx->outer_context;
821 if (ctx)
822 omp_add_variable (ctx, tmp, flag);
825 else if (cfun)
826 record_vars (tmp);
827 else
829 gimple_seq body_seq;
831 /* This case is for nested functions. We need to expose the locals
832 they create. */
833 body_seq = gimple_body (current_function_decl);
834 declare_vars (tmp, gimple_seq_first_stmt (body_seq), false);
840 /* This page contains routines to unshare tree nodes, i.e. to duplicate tree
841 nodes that are referenced more than once in GENERIC functions. This is
842 necessary because gimplification (translation into GIMPLE) is performed
843 by modifying tree nodes in-place, so gimplication of a shared node in a
844 first context could generate an invalid GIMPLE form in a second context.
846 This is achieved with a simple mark/copy/unmark algorithm that walks the
847 GENERIC representation top-down, marks nodes with TREE_VISITED the first
848 time it encounters them, duplicates them if they already have TREE_VISITED
849 set, and finally removes the TREE_VISITED marks it has set.
851 The algorithm works only at the function level, i.e. it generates a GENERIC
852 representation of a function with no nodes shared within the function when
853 passed a GENERIC function (except for nodes that are allowed to be shared).
855 At the global level, it is also necessary to unshare tree nodes that are
856 referenced in more than one function, for the same aforementioned reason.
857 This requires some cooperation from the front-end. There are 2 strategies:
859 1. Manual unsharing. The front-end needs to call unshare_expr on every
860 expression that might end up being shared across functions.
862 2. Deep unsharing. This is an extension of regular unsharing. Instead
863 of calling unshare_expr on expressions that might be shared across
864 functions, the front-end pre-marks them with TREE_VISITED. This will
865 ensure that they are unshared on the first reference within functions
866 when the regular unsharing algorithm runs. The counterpart is that
867 this algorithm must look deeper than for manual unsharing, which is
868 specified by LANG_HOOKS_DEEP_UNSHARING.
870 If there are only few specific cases of node sharing across functions, it is
871 probably easier for a front-end to unshare the expressions manually. On the
872 contrary, if the expressions generated at the global level are as widespread
873 as expressions generated within functions, deep unsharing is very likely the
874 way to go. */
876 /* Similar to copy_tree_r but do not copy SAVE_EXPR or TARGET_EXPR nodes.
877 These nodes model computations that must be done once. If we were to
878 unshare something like SAVE_EXPR(i++), the gimplification process would
879 create wrong code. However, if DATA is non-null, it must hold a pointer
880 set that is used to unshare the subtrees of these nodes. */
882 static tree
883 mostly_copy_tree_r (tree *tp, int *walk_subtrees, void *data)
885 tree t = *tp;
886 enum tree_code code = TREE_CODE (t);
888 /* Do not copy SAVE_EXPR, TARGET_EXPR or BIND_EXPR nodes themselves, but
889 copy their subtrees if we can make sure to do it only once. */
890 if (code == SAVE_EXPR || code == TARGET_EXPR || code == BIND_EXPR)
892 if (data && !((hash_set<tree> *)data)->add (t))
894 else
895 *walk_subtrees = 0;
898 /* Stop at types, decls, constants like copy_tree_r. */
899 else if (TREE_CODE_CLASS (code) == tcc_type
900 || TREE_CODE_CLASS (code) == tcc_declaration
901 || TREE_CODE_CLASS (code) == tcc_constant)
902 *walk_subtrees = 0;
904 /* Cope with the statement expression extension. */
905 else if (code == STATEMENT_LIST)
908 /* Leave the bulk of the work to copy_tree_r itself. */
909 else
910 copy_tree_r (tp, walk_subtrees, NULL);
912 return NULL_TREE;
915 /* Callback for walk_tree to unshare most of the shared trees rooted at *TP.
916 If *TP has been visited already, then *TP is deeply copied by calling
917 mostly_copy_tree_r. DATA is passed to mostly_copy_tree_r unmodified. */
919 static tree
920 copy_if_shared_r (tree *tp, int *walk_subtrees, void *data)
922 tree t = *tp;
923 enum tree_code code = TREE_CODE (t);
925 /* Skip types, decls, and constants. But we do want to look at their
926 types and the bounds of types. Mark them as visited so we properly
927 unmark their subtrees on the unmark pass. If we've already seen them,
928 don't look down further. */
929 if (TREE_CODE_CLASS (code) == tcc_type
930 || TREE_CODE_CLASS (code) == tcc_declaration
931 || TREE_CODE_CLASS (code) == tcc_constant)
933 if (TREE_VISITED (t))
934 *walk_subtrees = 0;
935 else
936 TREE_VISITED (t) = 1;
939 /* If this node has been visited already, unshare it and don't look
940 any deeper. */
941 else if (TREE_VISITED (t))
943 walk_tree (tp, mostly_copy_tree_r, data, NULL);
944 *walk_subtrees = 0;
947 /* Otherwise, mark the node as visited and keep looking. */
948 else
949 TREE_VISITED (t) = 1;
951 return NULL_TREE;
954 /* Unshare most of the shared trees rooted at *TP. DATA is passed to the
955 copy_if_shared_r callback unmodified. */
957 void
958 copy_if_shared (tree *tp, void *data)
960 walk_tree (tp, copy_if_shared_r, data, NULL);
963 /* Unshare all the trees in the body of FNDECL, as well as in the bodies of
964 any nested functions. */
966 static void
967 unshare_body (tree fndecl)
969 struct cgraph_node *cgn = cgraph_node::get (fndecl);
970 /* If the language requires deep unsharing, we need a pointer set to make
971 sure we don't repeatedly unshare subtrees of unshareable nodes. */
972 hash_set<tree> *visited
973 = lang_hooks.deep_unsharing ? new hash_set<tree> : NULL;
975 copy_if_shared (&DECL_SAVED_TREE (fndecl), visited);
976 copy_if_shared (&DECL_SIZE (DECL_RESULT (fndecl)), visited);
977 copy_if_shared (&DECL_SIZE_UNIT (DECL_RESULT (fndecl)), visited);
979 delete visited;
981 if (cgn)
982 for (cgn = first_nested_function (cgn); cgn;
983 cgn = next_nested_function (cgn))
984 unshare_body (cgn->decl);
987 /* Callback for walk_tree to unmark the visited trees rooted at *TP.
988 Subtrees are walked until the first unvisited node is encountered. */
990 static tree
991 unmark_visited_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
993 tree t = *tp;
995 /* If this node has been visited, unmark it and keep looking. */
996 if (TREE_VISITED (t))
997 TREE_VISITED (t) = 0;
999 /* Otherwise, don't look any deeper. */
1000 else
1001 *walk_subtrees = 0;
1003 return NULL_TREE;
1006 /* Unmark the visited trees rooted at *TP. */
1008 static inline void
1009 unmark_visited (tree *tp)
1011 walk_tree (tp, unmark_visited_r, NULL, NULL);
1014 /* Likewise, but mark all trees as not visited. */
1016 static void
1017 unvisit_body (tree fndecl)
1019 struct cgraph_node *cgn = cgraph_node::get (fndecl);
1021 unmark_visited (&DECL_SAVED_TREE (fndecl));
1022 unmark_visited (&DECL_SIZE (DECL_RESULT (fndecl)));
1023 unmark_visited (&DECL_SIZE_UNIT (DECL_RESULT (fndecl)));
1025 if (cgn)
1026 for (cgn = first_nested_function (cgn);
1027 cgn; cgn = next_nested_function (cgn))
1028 unvisit_body (cgn->decl);
1031 /* Unconditionally make an unshared copy of EXPR. This is used when using
1032 stored expressions which span multiple functions, such as BINFO_VTABLE,
1033 as the normal unsharing process can't tell that they're shared. */
1035 tree
1036 unshare_expr (tree expr)
1038 walk_tree (&expr, mostly_copy_tree_r, NULL, NULL);
1039 return expr;
1042 /* Worker for unshare_expr_without_location. */
1044 static tree
1045 prune_expr_location (tree *tp, int *walk_subtrees, void *)
1047 if (EXPR_P (*tp))
1048 SET_EXPR_LOCATION (*tp, UNKNOWN_LOCATION);
1049 else
1050 *walk_subtrees = 0;
1051 return NULL_TREE;
1054 /* Similar to unshare_expr but also prune all expression locations
1055 from EXPR. */
1057 tree
1058 unshare_expr_without_location (tree expr)
1060 walk_tree (&expr, mostly_copy_tree_r, NULL, NULL);
1061 if (EXPR_P (expr))
1062 walk_tree (&expr, prune_expr_location, NULL, NULL);
1063 return expr;
1066 /* Return the EXPR_LOCATION of EXPR, if it (maybe recursively) has
1067 one, OR_ELSE otherwise. The location of a STATEMENT_LISTs
1068 comprising at least one DEBUG_BEGIN_STMT followed by exactly one
1069 EXPR is the location of the EXPR. */
1071 static location_t
1072 rexpr_location (tree expr, location_t or_else = UNKNOWN_LOCATION)
1074 if (!expr)
1075 return or_else;
1077 if (EXPR_HAS_LOCATION (expr))
1078 return EXPR_LOCATION (expr);
1080 if (TREE_CODE (expr) != STATEMENT_LIST)
1081 return or_else;
1083 tree_stmt_iterator i = tsi_start (expr);
1085 bool found = false;
1086 while (!tsi_end_p (i) && TREE_CODE (tsi_stmt (i)) == DEBUG_BEGIN_STMT)
1088 found = true;
1089 tsi_next (&i);
1092 if (!found || !tsi_one_before_end_p (i))
1093 return or_else;
1095 return rexpr_location (tsi_stmt (i), or_else);
1098 /* Return TRUE iff EXPR (maybe recursively) has a location; see
1099 rexpr_location for the potential recursion. */
1101 static inline bool
1102 rexpr_has_location (tree expr)
1104 return rexpr_location (expr) != UNKNOWN_LOCATION;
1108 /* WRAPPER is a code such as BIND_EXPR or CLEANUP_POINT_EXPR which can both
1109 contain statements and have a value. Assign its value to a temporary
1110 and give it void_type_node. Return the temporary, or NULL_TREE if
1111 WRAPPER was already void. */
1113 tree
1114 voidify_wrapper_expr (tree wrapper, tree temp)
1116 tree type = TREE_TYPE (wrapper);
1117 if (type && !VOID_TYPE_P (type))
1119 tree *p;
1121 /* Set p to point to the body of the wrapper. Loop until we find
1122 something that isn't a wrapper. */
1123 for (p = &wrapper; p && *p; )
1125 switch (TREE_CODE (*p))
1127 case BIND_EXPR:
1128 TREE_SIDE_EFFECTS (*p) = 1;
1129 TREE_TYPE (*p) = void_type_node;
1130 /* For a BIND_EXPR, the body is operand 1. */
1131 p = &BIND_EXPR_BODY (*p);
1132 break;
1134 case CLEANUP_POINT_EXPR:
1135 case TRY_FINALLY_EXPR:
1136 case TRY_CATCH_EXPR:
1137 TREE_SIDE_EFFECTS (*p) = 1;
1138 TREE_TYPE (*p) = void_type_node;
1139 p = &TREE_OPERAND (*p, 0);
1140 break;
1142 case STATEMENT_LIST:
1144 tree_stmt_iterator i = tsi_last (*p);
1145 TREE_SIDE_EFFECTS (*p) = 1;
1146 TREE_TYPE (*p) = void_type_node;
1147 p = tsi_end_p (i) ? NULL : tsi_stmt_ptr (i);
1149 break;
1151 case COMPOUND_EXPR:
1152 /* Advance to the last statement. Set all container types to
1153 void. */
1154 for (; TREE_CODE (*p) == COMPOUND_EXPR; p = &TREE_OPERAND (*p, 1))
1156 TREE_SIDE_EFFECTS (*p) = 1;
1157 TREE_TYPE (*p) = void_type_node;
1159 break;
1161 case TRANSACTION_EXPR:
1162 TREE_SIDE_EFFECTS (*p) = 1;
1163 TREE_TYPE (*p) = void_type_node;
1164 p = &TRANSACTION_EXPR_BODY (*p);
1165 break;
1167 default:
1168 /* Assume that any tree upon which voidify_wrapper_expr is
1169 directly called is a wrapper, and that its body is op0. */
1170 if (p == &wrapper)
1172 TREE_SIDE_EFFECTS (*p) = 1;
1173 TREE_TYPE (*p) = void_type_node;
1174 p = &TREE_OPERAND (*p, 0);
1175 break;
1177 goto out;
1181 out:
1182 if (p == NULL || IS_EMPTY_STMT (*p))
1183 temp = NULL_TREE;
1184 else if (temp)
1186 /* The wrapper is on the RHS of an assignment that we're pushing
1187 down. */
1188 gcc_assert (TREE_CODE (temp) == INIT_EXPR
1189 || TREE_CODE (temp) == MODIFY_EXPR);
1190 TREE_OPERAND (temp, 1) = *p;
1191 *p = temp;
1193 else
1195 temp = create_tmp_var (type, "retval");
1196 *p = build2 (INIT_EXPR, type, temp, *p);
1199 return temp;
1202 return NULL_TREE;
1205 /* Prepare calls to builtins to SAVE and RESTORE the stack as well as
1206 a temporary through which they communicate. */
1208 static void
1209 build_stack_save_restore (gcall **save, gcall **restore)
1211 tree tmp_var;
1213 *save = gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_SAVE), 0);
1214 tmp_var = create_tmp_var (ptr_type_node, "saved_stack");
1215 gimple_call_set_lhs (*save, tmp_var);
1217 *restore
1218 = gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_RESTORE),
1219 1, tmp_var);
1222 /* Generate IFN_ASAN_MARK call that poisons shadow of a for DECL variable. */
1224 static tree
1225 build_asan_poison_call_expr (tree decl)
1227 /* Do not poison variables that have size equal to zero. */
1228 tree unit_size = DECL_SIZE_UNIT (decl);
1229 if (zerop (unit_size))
1230 return NULL_TREE;
1232 tree base = build_fold_addr_expr (decl);
1234 return build_call_expr_internal_loc (UNKNOWN_LOCATION, IFN_ASAN_MARK,
1235 void_type_node, 3,
1236 build_int_cst (integer_type_node,
1237 ASAN_MARK_POISON),
1238 base, unit_size);
1241 /* Generate IFN_ASAN_MARK call that would poison or unpoison, depending
1242 on POISON flag, shadow memory of a DECL variable. The call will be
1243 put on location identified by IT iterator, where BEFORE flag drives
1244 position where the stmt will be put. */
1246 static void
1247 asan_poison_variable (tree decl, bool poison, gimple_stmt_iterator *it,
1248 bool before)
1250 tree unit_size = DECL_SIZE_UNIT (decl);
1251 tree base = build_fold_addr_expr (decl);
1253 /* Do not poison variables that have size equal to zero. */
1254 if (zerop (unit_size))
1255 return;
1257 /* It's necessary to have all stack variables aligned to ASAN granularity
1258 bytes. */
1259 gcc_assert (!hwasan_sanitize_p () || hwasan_sanitize_stack_p ());
1260 unsigned shadow_granularity
1261 = hwasan_sanitize_p () ? HWASAN_TAG_GRANULE_SIZE : ASAN_SHADOW_GRANULARITY;
1262 if (DECL_ALIGN_UNIT (decl) <= shadow_granularity)
1263 SET_DECL_ALIGN (decl, BITS_PER_UNIT * shadow_granularity);
1265 HOST_WIDE_INT flags = poison ? ASAN_MARK_POISON : ASAN_MARK_UNPOISON;
1267 gimple *g
1268 = gimple_build_call_internal (IFN_ASAN_MARK, 3,
1269 build_int_cst (integer_type_node, flags),
1270 base, unit_size);
1272 if (before)
1273 gsi_insert_before (it, g, GSI_NEW_STMT);
1274 else
1275 gsi_insert_after (it, g, GSI_NEW_STMT);
1278 /* Generate IFN_ASAN_MARK internal call that depending on POISON flag
1279 either poisons or unpoisons a DECL. Created statement is appended
1280 to SEQ_P gimple sequence. */
1282 static void
1283 asan_poison_variable (tree decl, bool poison, gimple_seq *seq_p)
1285 gimple_stmt_iterator it = gsi_last (*seq_p);
1286 bool before = false;
1288 if (gsi_end_p (it))
1289 before = true;
1291 asan_poison_variable (decl, poison, &it, before);
1294 /* Sort pair of VAR_DECLs A and B by DECL_UID. */
1296 static int
1297 sort_by_decl_uid (const void *a, const void *b)
1299 const tree *t1 = (const tree *)a;
1300 const tree *t2 = (const tree *)b;
1302 int uid1 = DECL_UID (*t1);
1303 int uid2 = DECL_UID (*t2);
1305 if (uid1 < uid2)
1306 return -1;
1307 else if (uid1 > uid2)
1308 return 1;
1309 else
1310 return 0;
1313 /* Generate IFN_ASAN_MARK internal call for all VARIABLES
1314 depending on POISON flag. Created statement is appended
1315 to SEQ_P gimple sequence. */
1317 static void
1318 asan_poison_variables (hash_set<tree> *variables, bool poison, gimple_seq *seq_p)
1320 unsigned c = variables->elements ();
1321 if (c == 0)
1322 return;
1324 auto_vec<tree> sorted_variables (c);
1326 for (hash_set<tree>::iterator it = variables->begin ();
1327 it != variables->end (); ++it)
1328 sorted_variables.safe_push (*it);
1330 sorted_variables.qsort (sort_by_decl_uid);
1332 unsigned i;
1333 tree var;
1334 FOR_EACH_VEC_ELT (sorted_variables, i, var)
1336 asan_poison_variable (var, poison, seq_p);
1338 /* Add use_after_scope_memory attribute for the variable in order
1339 to prevent re-written into SSA. */
1340 if (!lookup_attribute (ASAN_USE_AFTER_SCOPE_ATTRIBUTE,
1341 DECL_ATTRIBUTES (var)))
1342 DECL_ATTRIBUTES (var)
1343 = tree_cons (get_identifier (ASAN_USE_AFTER_SCOPE_ATTRIBUTE),
1344 integer_one_node,
1345 DECL_ATTRIBUTES (var));
1349 /* Gimplify a BIND_EXPR. Just voidify and recurse. */
1351 static enum gimplify_status
1352 gimplify_bind_expr (tree *expr_p, gimple_seq *pre_p)
1354 tree bind_expr = *expr_p;
1355 bool old_keep_stack = gimplify_ctxp->keep_stack;
1356 bool old_save_stack = gimplify_ctxp->save_stack;
1357 tree t;
1358 gbind *bind_stmt;
1359 gimple_seq body, cleanup;
1360 gcall *stack_save;
1361 location_t start_locus = 0, end_locus = 0;
1362 tree ret_clauses = NULL;
1364 tree temp = voidify_wrapper_expr (bind_expr, NULL);
1366 /* Mark variables seen in this bind expr. */
1367 for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
1369 if (VAR_P (t))
1371 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
1372 tree attr;
1374 if (flag_openmp
1375 && !is_global_var (t)
1376 && DECL_CONTEXT (t) == current_function_decl
1377 && TREE_USED (t)
1378 && (attr = lookup_attribute ("omp allocate", DECL_ATTRIBUTES (t)))
1379 != NULL_TREE)
1381 gcc_assert (!DECL_HAS_VALUE_EXPR_P (t));
1382 tree alloc = TREE_PURPOSE (TREE_VALUE (attr));
1383 tree align = TREE_VALUE (TREE_VALUE (attr));
1384 /* Allocate directives that appear in a target region must specify
1385 an allocator clause unless a requires directive with the
1386 dynamic_allocators clause is present in the same compilation
1387 unit. */
1388 bool missing_dyn_alloc = false;
1389 if (alloc == NULL_TREE
1390 && ((omp_requires_mask & OMP_REQUIRES_DYNAMIC_ALLOCATORS)
1391 == 0))
1393 /* This comes too early for omp_discover_declare_target...,
1394 but should at least catch the most common cases. */
1395 missing_dyn_alloc
1396 = cgraph_node::get (current_function_decl)->offloadable;
1397 for (struct gimplify_omp_ctx *ctx2 = ctx;
1398 ctx2 && !missing_dyn_alloc; ctx2 = ctx2->outer_context)
1399 if (ctx2->code == OMP_TARGET)
1400 missing_dyn_alloc = true;
1402 if (missing_dyn_alloc)
1403 error_at (DECL_SOURCE_LOCATION (t),
1404 "%<allocate%> directive for %qD inside a target "
1405 "region must specify an %<allocator%> clause", t);
1406 /* Skip for omp_default_mem_alloc (= 1),
1407 unless align is present. */
1408 else if (!errorcount
1409 && (align != NULL_TREE
1410 || alloc == NULL_TREE
1411 || !integer_onep (alloc)))
1413 /* Fortran might already use a pointer type internally;
1414 use that pointer except for type(C_ptr) and type(C_funptr);
1415 note that normal proc pointers are rejected. */
1416 tree type = TREE_TYPE (t);
1417 tree tmp, v;
1418 if (lang_GNU_Fortran ()
1419 && POINTER_TYPE_P (type)
1420 && TREE_TYPE (type) != void_type_node
1421 && TREE_CODE (TREE_TYPE (type)) != FUNCTION_TYPE)
1423 type = TREE_TYPE (type);
1424 v = t;
1426 else
1428 tmp = build_pointer_type (type);
1429 v = create_tmp_var (tmp, get_name (t));
1430 DECL_IGNORED_P (v) = 0;
1431 DECL_ATTRIBUTES (v)
1432 = tree_cons (get_identifier ("omp allocate var"),
1433 build_tree_list (NULL_TREE, t),
1434 remove_attribute ("omp allocate",
1435 DECL_ATTRIBUTES (t)));
1436 tmp = build_fold_indirect_ref (v);
1437 TREE_THIS_NOTRAP (tmp) = 1;
1438 SET_DECL_VALUE_EXPR (t, tmp);
1439 DECL_HAS_VALUE_EXPR_P (t) = 1;
1441 tree sz = TYPE_SIZE_UNIT (type);
1442 /* The size to use in Fortran might not match TYPE_SIZE_UNIT;
1443 hence, for some decls, a size variable is saved in the
1444 attributes; use it, if available. */
1445 if (TREE_CHAIN (TREE_VALUE (attr))
1446 && TREE_CHAIN (TREE_CHAIN (TREE_VALUE (attr)))
1447 && TREE_PURPOSE (
1448 TREE_CHAIN (TREE_CHAIN (TREE_VALUE (attr)))))
1450 sz = TREE_CHAIN (TREE_CHAIN (TREE_VALUE (attr)));
1451 sz = TREE_PURPOSE (sz);
1453 if (alloc == NULL_TREE)
1454 alloc = build_zero_cst (ptr_type_node);
1455 if (align == NULL_TREE)
1456 align = build_int_cst (size_type_node, DECL_ALIGN_UNIT (t));
1457 else
1458 align = build_int_cst (size_type_node,
1459 MAX (tree_to_uhwi (align),
1460 DECL_ALIGN_UNIT (t)));
1461 location_t loc = DECL_SOURCE_LOCATION (t);
1462 tmp = builtin_decl_explicit (BUILT_IN_GOMP_ALLOC);
1463 tmp = build_call_expr_loc (loc, tmp, 3, align, sz, alloc);
1464 tmp = fold_build2_loc (loc, MODIFY_EXPR, TREE_TYPE (v), v,
1465 fold_convert (TREE_TYPE (v), tmp));
1466 gcc_assert (BIND_EXPR_BODY (bind_expr) != NULL_TREE);
1467 /* Ensure that either TREE_CHAIN (TREE_VALUE (attr) is set
1468 and GOMP_FREE added here or that DECL_HAS_VALUE_EXPR_P (t)
1469 is set, using in a condition much further below. */
1470 gcc_assert (DECL_HAS_VALUE_EXPR_P (t)
1471 || TREE_CHAIN (TREE_VALUE (attr)));
1472 if (TREE_CHAIN (TREE_VALUE (attr)))
1474 /* Fortran is special as it does not have properly nest
1475 declarations in blocks. And as there is no
1476 initializer, there is also no expression to look for.
1477 Hence, the FE makes the statement list of the
1478 try-finally block available. We can put the GOMP_alloc
1479 at the top, unless an allocator or size expression
1480 requires to put it afterward; note that the size is
1481 always later in generated code; for strings, no
1482 size expr but still an expr might be available.
1483 As LTO does not handle a statement list, 'sl' has
1484 to be removed; done so by removing the attribute. */
1485 DECL_ATTRIBUTES (t)
1486 = remove_attribute ("omp allocate",
1487 DECL_ATTRIBUTES (t));
1488 tree sl = TREE_PURPOSE (TREE_CHAIN (TREE_VALUE (attr)));
1489 tree_stmt_iterator e = tsi_start (sl);
1490 tree needle = NULL_TREE;
1491 if (TREE_CHAIN (TREE_CHAIN (TREE_VALUE (attr))))
1493 needle = TREE_CHAIN (TREE_CHAIN (TREE_VALUE (attr)));
1494 needle = (TREE_VALUE (needle) ? TREE_VALUE (needle)
1495 : sz);
1497 else if (TREE_CHAIN (TREE_CHAIN (TREE_VALUE (attr))))
1498 needle = sz;
1499 else if (DECL_P (alloc) && DECL_ARTIFICIAL (alloc))
1500 needle = alloc;
1502 if (needle != NULL_TREE)
1504 while (!tsi_end_p (e))
1506 if (*e == needle
1507 || (TREE_CODE (*e) == MODIFY_EXPR
1508 && TREE_OPERAND (*e, 0) == needle))
1509 break;
1510 ++e;
1512 gcc_assert (!tsi_end_p (e));
1514 tsi_link_after (&e, tmp, TSI_SAME_STMT);
1516 /* As the cleanup is in BIND_EXPR_BODY, GOMP_free is added
1517 here; for C/C++ it will be added in the 'cleanup'
1518 section after gimplification. But Fortran already has
1519 a try-finally block. */
1520 sl = TREE_VALUE (TREE_CHAIN (TREE_VALUE (attr)));
1521 e = tsi_last (sl);
1522 tmp = builtin_decl_explicit (BUILT_IN_GOMP_FREE);
1523 tmp = build_call_expr_loc (EXPR_LOCATION (*e), tmp, 2, v,
1524 build_zero_cst (ptr_type_node));
1525 tsi_link_after (&e, tmp, TSI_SAME_STMT);
1526 tmp = build_clobber (TREE_TYPE (v), CLOBBER_STORAGE_END);
1527 tmp = fold_build2_loc (loc, MODIFY_EXPR, TREE_TYPE (v), v,
1528 fold_convert (TREE_TYPE (v), tmp));
1529 ++e;
1530 tsi_link_after (&e, tmp, TSI_SAME_STMT);
1532 else
1534 gcc_assert (TREE_CODE (BIND_EXPR_BODY (bind_expr))
1535 == STATEMENT_LIST);
1536 tree_stmt_iterator e;
1537 e = tsi_start (BIND_EXPR_BODY (bind_expr));
1538 while (!tsi_end_p (e))
1540 if ((TREE_CODE (*e) == DECL_EXPR
1541 && TREE_OPERAND (*e, 0) == t)
1542 || (TREE_CODE (*e) == CLEANUP_POINT_EXPR
1543 && (TREE_CODE (TREE_OPERAND (*e, 0))
1544 == DECL_EXPR)
1545 && (TREE_OPERAND (TREE_OPERAND (*e, 0), 0)
1546 == t)))
1547 break;
1548 ++e;
1550 gcc_assert (!tsi_end_p (e));
1551 tsi_link_before (&e, tmp, TSI_SAME_STMT);
1556 /* Mark variable as local. */
1557 if (ctx && ctx->region_type != ORT_NONE && !DECL_EXTERNAL (t))
1559 if (! DECL_SEEN_IN_BIND_EXPR_P (t)
1560 || splay_tree_lookup (ctx->variables,
1561 (splay_tree_key) t) == NULL)
1563 int flag = GOVD_LOCAL;
1564 if (ctx->region_type == ORT_SIMD
1565 && TREE_ADDRESSABLE (t)
1566 && !TREE_STATIC (t))
1568 if (TREE_CODE (DECL_SIZE_UNIT (t)) != INTEGER_CST)
1569 ctx->add_safelen1 = true;
1570 else
1571 flag = GOVD_PRIVATE;
1573 omp_add_variable (ctx, t, flag | GOVD_SEEN);
1575 /* Static locals inside of target construct or offloaded
1576 routines need to be "omp declare target". */
1577 if (TREE_STATIC (t))
1578 for (; ctx; ctx = ctx->outer_context)
1579 if ((ctx->region_type & ORT_TARGET) != 0)
1581 if (!lookup_attribute ("omp declare target",
1582 DECL_ATTRIBUTES (t)))
1584 tree id = get_identifier ("omp declare target");
1585 DECL_ATTRIBUTES (t)
1586 = tree_cons (id, NULL_TREE, DECL_ATTRIBUTES (t));
1587 varpool_node *node = varpool_node::get (t);
1588 if (node)
1590 node->offloadable = 1;
1591 if (ENABLE_OFFLOADING && !DECL_EXTERNAL (t))
1593 g->have_offload = true;
1594 if (!in_lto_p)
1595 vec_safe_push (offload_vars, t);
1599 break;
1603 DECL_SEEN_IN_BIND_EXPR_P (t) = 1;
1605 if (DECL_HARD_REGISTER (t) && !is_global_var (t) && cfun)
1606 cfun->has_local_explicit_reg_vars = true;
1610 bind_stmt = gimple_build_bind (BIND_EXPR_VARS (bind_expr), NULL,
1611 BIND_EXPR_BLOCK (bind_expr));
1612 gimple_push_bind_expr (bind_stmt);
1614 gimplify_ctxp->keep_stack = false;
1615 gimplify_ctxp->save_stack = false;
1617 /* Gimplify the body into the GIMPLE_BIND tuple's body. */
1618 body = NULL;
1619 gimplify_stmt (&BIND_EXPR_BODY (bind_expr), &body);
1620 gimple_bind_set_body (bind_stmt, body);
1622 /* Source location wise, the cleanup code (stack_restore and clobbers)
1623 belongs to the end of the block, so propagate what we have. The
1624 stack_save operation belongs to the beginning of block, which we can
1625 infer from the bind_expr directly if the block has no explicit
1626 assignment. */
1627 if (BIND_EXPR_BLOCK (bind_expr))
1629 end_locus = BLOCK_SOURCE_END_LOCATION (BIND_EXPR_BLOCK (bind_expr));
1630 start_locus = BLOCK_SOURCE_LOCATION (BIND_EXPR_BLOCK (bind_expr));
1632 if (start_locus == 0)
1633 start_locus = EXPR_LOCATION (bind_expr);
1635 cleanup = NULL;
1636 stack_save = NULL;
1638 /* Add clobbers for all variables that go out of scope. */
1639 for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
1641 if (VAR_P (t)
1642 && !is_global_var (t)
1643 && DECL_CONTEXT (t) == current_function_decl)
1645 if (flag_openmp
1646 && DECL_HAS_VALUE_EXPR_P (t)
1647 && TREE_USED (t)
1648 && lookup_attribute ("omp allocate", DECL_ATTRIBUTES (t)))
1650 /* For Fortran, TREE_CHAIN (TREE_VALUE (attr)) is set, which
1651 causes that the GOMP_free call is already added above;
1652 and "omp allocate" is removed from DECL_ATTRIBUTES. */
1653 tree v = TREE_OPERAND (DECL_VALUE_EXPR (t), 0);
1654 tree tmp = builtin_decl_explicit (BUILT_IN_GOMP_FREE);
1655 tmp = build_call_expr_loc (end_locus, tmp, 2, v,
1656 build_zero_cst (ptr_type_node));
1657 gimplify_and_add (tmp, &cleanup);
1658 gimple *clobber_stmt;
1659 tmp = build_clobber (TREE_TYPE (v), CLOBBER_STORAGE_END);
1660 clobber_stmt = gimple_build_assign (v, tmp);
1661 gimple_set_location (clobber_stmt, end_locus);
1662 gimplify_seq_add_stmt (&cleanup, clobber_stmt);
1664 if (!DECL_HARD_REGISTER (t)
1665 && !TREE_THIS_VOLATILE (t)
1666 && !DECL_HAS_VALUE_EXPR_P (t)
1667 /* Only care for variables that have to be in memory. Others
1668 will be rewritten into SSA names, hence moved to the
1669 top-level. */
1670 && !is_gimple_reg (t)
1671 && flag_stack_reuse != SR_NONE)
1673 tree clobber = build_clobber (TREE_TYPE (t), CLOBBER_STORAGE_END);
1674 gimple *clobber_stmt;
1675 clobber_stmt = gimple_build_assign (t, clobber);
1676 gimple_set_location (clobber_stmt, end_locus);
1677 gimplify_seq_add_stmt (&cleanup, clobber_stmt);
1680 if (flag_openacc && oacc_declare_returns != NULL)
1682 tree key = t;
1683 if (DECL_HAS_VALUE_EXPR_P (key))
1685 key = DECL_VALUE_EXPR (key);
1686 if (INDIRECT_REF_P (key))
1687 key = TREE_OPERAND (key, 0);
1689 tree *c = oacc_declare_returns->get (key);
1690 if (c != NULL)
1692 if (ret_clauses)
1693 OMP_CLAUSE_CHAIN (*c) = ret_clauses;
1695 ret_clauses = unshare_expr (*c);
1697 oacc_declare_returns->remove (key);
1699 if (oacc_declare_returns->is_empty ())
1701 delete oacc_declare_returns;
1702 oacc_declare_returns = NULL;
1708 if (asan_poisoned_variables != NULL
1709 && asan_poisoned_variables->contains (t))
1711 asan_poisoned_variables->remove (t);
1712 asan_poison_variable (t, true, &cleanup);
1715 if (gimplify_ctxp->live_switch_vars != NULL
1716 && gimplify_ctxp->live_switch_vars->contains (t))
1717 gimplify_ctxp->live_switch_vars->remove (t);
1720 /* If the code both contains VLAs and calls alloca, then we cannot reclaim
1721 the stack space allocated to the VLAs. */
1722 if (gimplify_ctxp->save_stack && !gimplify_ctxp->keep_stack)
1724 gcall *stack_restore;
1726 /* Save stack on entry and restore it on exit. Add a try_finally
1727 block to achieve this. */
1728 build_stack_save_restore (&stack_save, &stack_restore);
1730 gimple_set_location (stack_save, start_locus);
1731 gimple_set_location (stack_restore, end_locus);
1733 gimplify_seq_add_stmt (&cleanup, stack_restore);
1736 if (ret_clauses)
1738 gomp_target *stmt;
1739 gimple_stmt_iterator si = gsi_start (cleanup);
1741 stmt = gimple_build_omp_target (NULL, GF_OMP_TARGET_KIND_OACC_DECLARE,
1742 ret_clauses);
1743 gsi_insert_seq_before_without_update (&si, stmt, GSI_NEW_STMT);
1746 if (cleanup)
1748 gtry *gs;
1749 gimple_seq new_body;
1751 new_body = NULL;
1752 gs = gimple_build_try (gimple_bind_body (bind_stmt), cleanup,
1753 GIMPLE_TRY_FINALLY);
1755 if (stack_save)
1756 gimplify_seq_add_stmt (&new_body, stack_save);
1757 gimplify_seq_add_stmt (&new_body, gs);
1758 gimple_bind_set_body (bind_stmt, new_body);
1761 /* keep_stack propagates all the way up to the outermost BIND_EXPR. */
1762 if (!gimplify_ctxp->keep_stack)
1763 gimplify_ctxp->keep_stack = old_keep_stack;
1764 gimplify_ctxp->save_stack = old_save_stack;
1766 gimple_pop_bind_expr ();
1768 gimplify_seq_add_stmt (pre_p, bind_stmt);
1770 if (temp)
1772 *expr_p = temp;
1773 return GS_OK;
1776 *expr_p = NULL_TREE;
1777 return GS_ALL_DONE;
1780 /* Maybe add early return predict statement to PRE_P sequence. */
1782 static void
1783 maybe_add_early_return_predict_stmt (gimple_seq *pre_p)
1785 /* If we are not in a conditional context, add PREDICT statement. */
1786 if (gimple_conditional_context ())
1788 gimple *predict = gimple_build_predict (PRED_TREE_EARLY_RETURN,
1789 NOT_TAKEN);
1790 gimplify_seq_add_stmt (pre_p, predict);
1794 /* Gimplify a RETURN_EXPR. If the expression to be returned is not a
1795 GIMPLE value, it is assigned to a new temporary and the statement is
1796 re-written to return the temporary.
1798 PRE_P points to the sequence where side effects that must happen before
1799 STMT should be stored. */
1801 static enum gimplify_status
1802 gimplify_return_expr (tree stmt, gimple_seq *pre_p)
1804 greturn *ret;
1805 tree ret_expr = TREE_OPERAND (stmt, 0);
1806 tree result_decl, result;
1808 if (ret_expr == error_mark_node)
1809 return GS_ERROR;
1811 if (!ret_expr
1812 || TREE_CODE (ret_expr) == RESULT_DECL)
1814 maybe_add_early_return_predict_stmt (pre_p);
1815 greturn *ret = gimple_build_return (ret_expr);
1816 copy_warning (ret, stmt);
1817 gimplify_seq_add_stmt (pre_p, ret);
1818 return GS_ALL_DONE;
1821 if (VOID_TYPE_P (TREE_TYPE (TREE_TYPE (current_function_decl))))
1822 result_decl = NULL_TREE;
1823 else if (TREE_CODE (ret_expr) == COMPOUND_EXPR)
1825 /* Used in C++ for handling EH cleanup of the return value if a local
1826 cleanup throws. Assume the front-end knows what it's doing. */
1827 result_decl = DECL_RESULT (current_function_decl);
1828 /* But crash if we end up trying to modify ret_expr below. */
1829 ret_expr = NULL_TREE;
1831 else
1833 result_decl = TREE_OPERAND (ret_expr, 0);
1835 /* See through a return by reference. */
1836 if (INDIRECT_REF_P (result_decl))
1837 result_decl = TREE_OPERAND (result_decl, 0);
1839 gcc_assert ((TREE_CODE (ret_expr) == MODIFY_EXPR
1840 || TREE_CODE (ret_expr) == INIT_EXPR)
1841 && TREE_CODE (result_decl) == RESULT_DECL);
1844 /* If aggregate_value_p is true, then we can return the bare RESULT_DECL.
1845 Recall that aggregate_value_p is FALSE for any aggregate type that is
1846 returned in registers. If we're returning values in registers, then
1847 we don't want to extend the lifetime of the RESULT_DECL, particularly
1848 across another call. In addition, for those aggregates for which
1849 hard_function_value generates a PARALLEL, we'll die during normal
1850 expansion of structure assignments; there's special code in expand_return
1851 to handle this case that does not exist in expand_expr. */
1852 if (!result_decl)
1853 result = NULL_TREE;
1854 else if (aggregate_value_p (result_decl, TREE_TYPE (current_function_decl)))
1856 if (!poly_int_tree_p (DECL_SIZE (result_decl)))
1858 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (result_decl)))
1859 gimplify_type_sizes (TREE_TYPE (result_decl), pre_p);
1860 /* Note that we don't use gimplify_vla_decl because the RESULT_DECL
1861 should be effectively allocated by the caller, i.e. all calls to
1862 this function must be subject to the Return Slot Optimization. */
1863 gimplify_one_sizepos (&DECL_SIZE (result_decl), pre_p);
1864 gimplify_one_sizepos (&DECL_SIZE_UNIT (result_decl), pre_p);
1866 result = result_decl;
1868 else if (gimplify_ctxp->return_temp)
1869 result = gimplify_ctxp->return_temp;
1870 else
1872 result = create_tmp_reg (TREE_TYPE (result_decl));
1874 /* ??? With complex control flow (usually involving abnormal edges),
1875 we can wind up warning about an uninitialized value for this. Due
1876 to how this variable is constructed and initialized, this is never
1877 true. Give up and never warn. */
1878 suppress_warning (result, OPT_Wuninitialized);
1880 gimplify_ctxp->return_temp = result;
1883 /* Smash the lhs of the MODIFY_EXPR to the temporary we plan to use.
1884 Then gimplify the whole thing. */
1885 if (result != result_decl)
1886 TREE_OPERAND (ret_expr, 0) = result;
1888 gimplify_and_add (TREE_OPERAND (stmt, 0), pre_p);
1890 maybe_add_early_return_predict_stmt (pre_p);
1891 ret = gimple_build_return (result);
1892 copy_warning (ret, stmt);
1893 gimplify_seq_add_stmt (pre_p, ret);
1895 return GS_ALL_DONE;
1898 /* Gimplify a variable-length array DECL. */
1900 static void
1901 gimplify_vla_decl (tree decl, gimple_seq *seq_p)
1903 /* This is a variable-sized decl. Simplify its size and mark it
1904 for deferred expansion. */
1905 tree t, addr, ptr_type;
1907 gimplify_one_sizepos (&DECL_SIZE (decl), seq_p);
1908 gimplify_one_sizepos (&DECL_SIZE_UNIT (decl), seq_p);
1910 /* Don't mess with a DECL_VALUE_EXPR set by the front-end. */
1911 if (DECL_HAS_VALUE_EXPR_P (decl))
1912 return;
1914 /* All occurrences of this decl in final gimplified code will be
1915 replaced by indirection. Setting DECL_VALUE_EXPR does two
1916 things: First, it lets the rest of the gimplifier know what
1917 replacement to use. Second, it lets the debug info know
1918 where to find the value. */
1919 ptr_type = build_pointer_type (TREE_TYPE (decl));
1920 addr = create_tmp_var (ptr_type, get_name (decl));
1921 DECL_IGNORED_P (addr) = 0;
1922 t = build_fold_indirect_ref (addr);
1923 TREE_THIS_NOTRAP (t) = 1;
1924 SET_DECL_VALUE_EXPR (decl, t);
1925 DECL_HAS_VALUE_EXPR_P (decl) = 1;
1927 t = build_alloca_call_expr (DECL_SIZE_UNIT (decl), DECL_ALIGN (decl),
1928 max_int_size_in_bytes (TREE_TYPE (decl)));
1929 /* The call has been built for a variable-sized object. */
1930 CALL_ALLOCA_FOR_VAR_P (t) = 1;
1931 t = fold_convert (ptr_type, t);
1932 t = build2 (MODIFY_EXPR, TREE_TYPE (addr), addr, t);
1934 gimplify_and_add (t, seq_p);
1936 /* Record the dynamic allocation associated with DECL if requested. */
1937 if (flag_callgraph_info & CALLGRAPH_INFO_DYNAMIC_ALLOC)
1938 record_dynamic_alloc (decl);
1941 /* A helper function to be called via walk_tree. Mark all labels under *TP
1942 as being forced. To be called for DECL_INITIAL of static variables. */
1944 static tree
1945 force_labels_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
1947 if (TYPE_P (*tp))
1948 *walk_subtrees = 0;
1949 if (TREE_CODE (*tp) == LABEL_DECL)
1951 FORCED_LABEL (*tp) = 1;
1952 cfun->has_forced_label_in_static = 1;
1955 return NULL_TREE;
1958 /* Generate an initialization to automatic variable DECL based on INIT_TYPE.
1959 Build a call to internal const function DEFERRED_INIT:
1960 1st argument: SIZE of the DECL;
1961 2nd argument: INIT_TYPE;
1962 3rd argument: NAME of the DECL;
1964 as LHS = DEFERRED_INIT (SIZE of the DECL, INIT_TYPE, NAME of the DECL). */
1966 static void
1967 gimple_add_init_for_auto_var (tree decl,
1968 enum auto_init_type init_type,
1969 gimple_seq *seq_p)
1971 gcc_assert (auto_var_p (decl));
1972 gcc_assert (init_type > AUTO_INIT_UNINITIALIZED);
1973 location_t loc = EXPR_LOCATION (decl);
1974 tree decl_size = TYPE_SIZE_UNIT (TREE_TYPE (decl));
1976 tree init_type_node
1977 = build_int_cst (integer_type_node, (int) init_type);
1979 tree decl_name = NULL_TREE;
1980 if (DECL_NAME (decl))
1982 decl_name = build_string_literal (DECL_NAME (decl));
1984 else
1986 char decl_name_anonymous[3 + (HOST_BITS_PER_INT + 2) / 3];
1987 sprintf (decl_name_anonymous, "D.%u", DECL_UID (decl));
1988 decl_name = build_string_literal (decl_name_anonymous);
1991 tree call = build_call_expr_internal_loc (loc, IFN_DEFERRED_INIT,
1992 TREE_TYPE (decl), 3,
1993 decl_size, init_type_node,
1994 decl_name);
1996 gimplify_assign (decl, call, seq_p);
1999 /* Generate padding initialization for automatic vairable DECL.
2000 C guarantees that brace-init with fewer initializers than members
2001 aggregate will initialize the rest of the aggregate as-if it were
2002 static initialization. In turn static initialization guarantees
2003 that padding is initialized to zero. So, we always initialize paddings
2004 to zeroes regardless INIT_TYPE.
2005 To do the padding initialization, we insert a call to
2006 __builtin_clear_padding (&decl, 0, for_auto_init = true).
2007 Note, we add an additional dummy argument for __builtin_clear_padding,
2008 'for_auto_init' to distinguish whether this call is for automatic
2009 variable initialization or not.
2011 static void
2012 gimple_add_padding_init_for_auto_var (tree decl, bool is_vla,
2013 gimple_seq *seq_p)
2015 tree addr_of_decl = NULL_TREE;
2016 tree fn = builtin_decl_explicit (BUILT_IN_CLEAR_PADDING);
2018 if (is_vla)
2020 /* The temporary address variable for this vla should be
2021 created in gimplify_vla_decl. */
2022 gcc_assert (DECL_HAS_VALUE_EXPR_P (decl));
2023 gcc_assert (INDIRECT_REF_P (DECL_VALUE_EXPR (decl)));
2024 addr_of_decl = TREE_OPERAND (DECL_VALUE_EXPR (decl), 0);
2026 else
2028 mark_addressable (decl);
2029 addr_of_decl = build_fold_addr_expr (decl);
2032 gimple *call = gimple_build_call (fn, 2, addr_of_decl,
2033 build_one_cst (TREE_TYPE (addr_of_decl)));
2034 gimplify_seq_add_stmt (seq_p, call);
2037 /* Return true if the DECL need to be automaticly initialized by the
2038 compiler. */
2039 static bool
2040 is_var_need_auto_init (tree decl)
2042 if (auto_var_p (decl)
2043 && (TREE_CODE (decl) != VAR_DECL
2044 || !DECL_HARD_REGISTER (decl))
2045 && (flag_auto_var_init > AUTO_INIT_UNINITIALIZED)
2046 && (!lookup_attribute ("uninitialized", DECL_ATTRIBUTES (decl)))
2047 && !OPAQUE_TYPE_P (TREE_TYPE (decl))
2048 && !is_empty_type (TREE_TYPE (decl)))
2049 return true;
2050 return false;
2053 /* Gimplify a DECL_EXPR node *STMT_P by making any necessary allocation
2054 and initialization explicit. */
2056 static enum gimplify_status
2057 gimplify_decl_expr (tree *stmt_p, gimple_seq *seq_p)
2059 tree stmt = *stmt_p;
2060 tree decl = DECL_EXPR_DECL (stmt);
2062 *stmt_p = NULL_TREE;
2064 if (TREE_TYPE (decl) == error_mark_node)
2065 return GS_ERROR;
2067 if ((TREE_CODE (decl) == TYPE_DECL
2068 || VAR_P (decl))
2069 && !TYPE_SIZES_GIMPLIFIED (TREE_TYPE (decl)))
2071 gimplify_type_sizes (TREE_TYPE (decl), seq_p);
2072 if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE)
2073 gimplify_type_sizes (TREE_TYPE (TREE_TYPE (decl)), seq_p);
2076 /* ??? DECL_ORIGINAL_TYPE is streamed for LTO so it needs to be gimplified
2077 in case its size expressions contain problematic nodes like CALL_EXPR. */
2078 if (TREE_CODE (decl) == TYPE_DECL
2079 && DECL_ORIGINAL_TYPE (decl)
2080 && !TYPE_SIZES_GIMPLIFIED (DECL_ORIGINAL_TYPE (decl)))
2082 gimplify_type_sizes (DECL_ORIGINAL_TYPE (decl), seq_p);
2083 if (TREE_CODE (DECL_ORIGINAL_TYPE (decl)) == REFERENCE_TYPE)
2084 gimplify_type_sizes (TREE_TYPE (DECL_ORIGINAL_TYPE (decl)), seq_p);
2087 if (VAR_P (decl) && !DECL_EXTERNAL (decl))
2089 tree init = DECL_INITIAL (decl);
2090 bool is_vla = false;
2091 /* Check whether a decl has FE created VALUE_EXPR here BEFORE
2092 gimplify_vla_decl creates VALUE_EXPR for a vla decl.
2093 If the decl has VALUE_EXPR that was created by FE (usually
2094 C++FE), it's a proxy varaible, and FE already initialized
2095 the VALUE_EXPR of it, we should not initialize it anymore. */
2096 bool decl_had_value_expr_p = DECL_HAS_VALUE_EXPR_P (decl);
2098 poly_uint64 size;
2099 if (!poly_int_tree_p (DECL_SIZE_UNIT (decl), &size)
2100 || (!TREE_STATIC (decl)
2101 && flag_stack_check == GENERIC_STACK_CHECK
2102 && maybe_gt (size,
2103 (unsigned HOST_WIDE_INT) STACK_CHECK_MAX_VAR_SIZE)))
2105 gimplify_vla_decl (decl, seq_p);
2106 is_vla = true;
2109 if (asan_poisoned_variables
2110 && !is_vla
2111 && TREE_ADDRESSABLE (decl)
2112 && !TREE_STATIC (decl)
2113 && !DECL_HAS_VALUE_EXPR_P (decl)
2114 && DECL_ALIGN (decl) <= MAX_SUPPORTED_STACK_ALIGNMENT
2115 && dbg_cnt (asan_use_after_scope)
2116 && !gimplify_omp_ctxp
2117 /* GNAT introduces temporaries to hold return values of calls in
2118 initializers of variables defined in other units, so the
2119 declaration of the variable is discarded completely. We do not
2120 want to issue poison calls for such dropped variables. */
2121 && (DECL_SEEN_IN_BIND_EXPR_P (decl)
2122 || (DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)))
2124 asan_poisoned_variables->add (decl);
2125 asan_poison_variable (decl, false, seq_p);
2126 if (!DECL_ARTIFICIAL (decl) && gimplify_ctxp->live_switch_vars)
2127 gimplify_ctxp->live_switch_vars->add (decl);
2130 /* Some front ends do not explicitly declare all anonymous
2131 artificial variables. We compensate here by declaring the
2132 variables, though it would be better if the front ends would
2133 explicitly declare them. */
2134 if (!DECL_SEEN_IN_BIND_EXPR_P (decl)
2135 && DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)
2136 gimple_add_tmp_var (decl);
2138 if (init && init != error_mark_node)
2140 if (!TREE_STATIC (decl))
2142 DECL_INITIAL (decl) = NULL_TREE;
2143 init = build2 (INIT_EXPR, void_type_node, decl, init);
2144 gimplify_and_add (init, seq_p);
2145 ggc_free (init);
2146 /* Clear TREE_READONLY if we really have an initialization. */
2147 if (!DECL_INITIAL (decl)
2148 && !omp_privatize_by_reference (decl))
2149 TREE_READONLY (decl) = 0;
2151 else
2152 /* We must still examine initializers for static variables
2153 as they may contain a label address. */
2154 walk_tree (&init, force_labels_r, NULL, NULL);
2156 /* When there is no explicit initializer, if the user requested,
2157 We should insert an artifical initializer for this automatic
2158 variable. */
2159 else if (is_var_need_auto_init (decl)
2160 && !decl_had_value_expr_p)
2162 gimple_add_init_for_auto_var (decl,
2163 flag_auto_var_init,
2164 seq_p);
2165 /* The expanding of a call to the above .DEFERRED_INIT will apply
2166 block initialization to the whole space covered by this variable.
2167 As a result, all the paddings will be initialized to zeroes
2168 for zero initialization and 0xFE byte-repeatable patterns for
2169 pattern initialization.
2170 In order to make the paddings as zeroes for pattern init, We
2171 should add a call to __builtin_clear_padding to clear the
2172 paddings to zero in compatiple with CLANG.
2173 We cannot insert this call if the variable is a gimple register
2174 since __builtin_clear_padding will take the address of the
2175 variable. As a result, if a long double/_Complex long double
2176 variable will spilled into stack later, its padding is 0XFE. */
2177 if (flag_auto_var_init == AUTO_INIT_PATTERN
2178 && !is_gimple_reg (decl)
2179 && clear_padding_type_may_have_padding_p (TREE_TYPE (decl)))
2180 gimple_add_padding_init_for_auto_var (decl, is_vla, seq_p);
2184 return GS_ALL_DONE;
2187 /* Gimplify a LOOP_EXPR. Normally this just involves gimplifying the body
2188 and replacing the LOOP_EXPR with goto, but if the loop contains an
2189 EXIT_EXPR, we need to append a label for it to jump to. */
2191 static enum gimplify_status
2192 gimplify_loop_expr (tree *expr_p, gimple_seq *pre_p)
2194 tree saved_label = gimplify_ctxp->exit_label;
2195 tree start_label = create_artificial_label (UNKNOWN_LOCATION);
2197 gimplify_seq_add_stmt (pre_p, gimple_build_label (start_label));
2199 gimplify_ctxp->exit_label = NULL_TREE;
2201 gimplify_and_add (LOOP_EXPR_BODY (*expr_p), pre_p);
2203 gimplify_seq_add_stmt (pre_p, gimple_build_goto (start_label));
2205 if (gimplify_ctxp->exit_label)
2206 gimplify_seq_add_stmt (pre_p,
2207 gimple_build_label (gimplify_ctxp->exit_label));
2209 gimplify_ctxp->exit_label = saved_label;
2211 *expr_p = NULL;
2212 return GS_ALL_DONE;
2215 /* Gimplify a statement list onto a sequence. These may be created either
2216 by an enlightened front-end, or by shortcut_cond_expr. */
2218 static enum gimplify_status
2219 gimplify_statement_list (tree *expr_p, gimple_seq *pre_p)
2221 tree temp = voidify_wrapper_expr (*expr_p, NULL);
2223 tree_stmt_iterator i = tsi_start (*expr_p);
2225 while (!tsi_end_p (i))
2227 gimplify_stmt (tsi_stmt_ptr (i), pre_p);
2228 tsi_delink (&i);
2231 if (temp)
2233 *expr_p = temp;
2234 return GS_OK;
2237 return GS_ALL_DONE;
2241 /* Emit warning for the unreachable statment STMT if needed.
2242 Return the gimple itself when the warning is emitted, otherwise
2243 return NULL. */
2244 static gimple *
2245 emit_warn_switch_unreachable (gimple *stmt)
2247 if (gimple_code (stmt) == GIMPLE_GOTO
2248 && TREE_CODE (gimple_goto_dest (stmt)) == LABEL_DECL
2249 && DECL_ARTIFICIAL (gimple_goto_dest (stmt)))
2250 /* Don't warn for compiler-generated gotos. These occur
2251 in Duff's devices, for example. */
2252 return NULL;
2253 else if ((flag_auto_var_init > AUTO_INIT_UNINITIALIZED)
2254 && ((gimple_call_internal_p (stmt, IFN_DEFERRED_INIT))
2255 || (gimple_call_builtin_p (stmt, BUILT_IN_CLEAR_PADDING)
2256 && (bool) TREE_INT_CST_LOW (gimple_call_arg (stmt, 1)))
2257 || (is_gimple_assign (stmt)
2258 && gimple_assign_single_p (stmt)
2259 && (TREE_CODE (gimple_assign_rhs1 (stmt)) == SSA_NAME)
2260 && gimple_call_internal_p (
2261 SSA_NAME_DEF_STMT (gimple_assign_rhs1 (stmt)),
2262 IFN_DEFERRED_INIT))))
2263 /* Don't warn for compiler-generated initializations for
2264 -ftrivial-auto-var-init.
2265 There are 3 cases:
2266 case 1: a call to .DEFERRED_INIT;
2267 case 2: a call to __builtin_clear_padding with the 2nd argument is
2268 present and non-zero;
2269 case 3: a gimple assign store right after the call to .DEFERRED_INIT
2270 that has the LHS of .DEFERRED_INIT as the RHS as following:
2271 _1 = .DEFERRED_INIT (4, 2, &"i1"[0]);
2272 i1 = _1. */
2273 return NULL;
2274 else
2275 warning_at (gimple_location (stmt), OPT_Wswitch_unreachable,
2276 "statement will never be executed");
2277 return stmt;
2280 /* Callback for walk_gimple_seq. */
2282 static tree
2283 warn_switch_unreachable_and_auto_init_r (gimple_stmt_iterator *gsi_p,
2284 bool *handled_ops_p,
2285 struct walk_stmt_info *wi)
2287 gimple *stmt = gsi_stmt (*gsi_p);
2288 bool unreachable_issued = wi->info != NULL;
2290 *handled_ops_p = true;
2291 switch (gimple_code (stmt))
2293 case GIMPLE_TRY:
2294 /* A compiler-generated cleanup or a user-written try block.
2295 If it's empty, don't dive into it--that would result in
2296 worse location info. */
2297 if (gimple_try_eval (stmt) == NULL)
2299 if (warn_switch_unreachable && !unreachable_issued)
2300 wi->info = emit_warn_switch_unreachable (stmt);
2302 /* Stop when auto var init warning is not on. */
2303 if (!warn_trivial_auto_var_init)
2304 return integer_zero_node;
2306 /* Fall through. */
2307 case GIMPLE_BIND:
2308 case GIMPLE_CATCH:
2309 case GIMPLE_EH_FILTER:
2310 case GIMPLE_TRANSACTION:
2311 /* Walk the sub-statements. */
2312 *handled_ops_p = false;
2313 break;
2315 case GIMPLE_DEBUG:
2316 /* Ignore these. We may generate them before declarations that
2317 are never executed. If there's something to warn about,
2318 there will be non-debug stmts too, and we'll catch those. */
2319 break;
2321 case GIMPLE_LABEL:
2322 /* Stop till the first Label. */
2323 return integer_zero_node;
2324 case GIMPLE_CALL:
2325 if (gimple_call_internal_p (stmt, IFN_ASAN_MARK))
2327 *handled_ops_p = false;
2328 break;
2330 if (warn_trivial_auto_var_init
2331 && flag_auto_var_init > AUTO_INIT_UNINITIALIZED
2332 && gimple_call_internal_p (stmt, IFN_DEFERRED_INIT))
2334 /* Get the variable name from the 3rd argument of call. */
2335 tree var_name = gimple_call_arg (stmt, 2);
2336 var_name = TREE_OPERAND (TREE_OPERAND (var_name, 0), 0);
2337 const char *var_name_str = TREE_STRING_POINTER (var_name);
2339 warning_at (gimple_location (stmt), OPT_Wtrivial_auto_var_init,
2340 "%qs cannot be initialized with"
2341 "%<-ftrivial-auto-var_init%>",
2342 var_name_str);
2343 break;
2346 /* Fall through. */
2347 default:
2348 /* check the first "real" statement (not a decl/lexical scope/...), issue
2349 warning if needed. */
2350 if (warn_switch_unreachable && !unreachable_issued)
2351 wi->info = emit_warn_switch_unreachable (stmt);
2352 /* Stop when auto var init warning is not on. */
2353 if (!warn_trivial_auto_var_init)
2354 return integer_zero_node;
2355 break;
2357 return NULL_TREE;
2361 /* Possibly warn about unreachable statements between switch's controlling
2362 expression and the first case. Also warn about -ftrivial-auto-var-init
2363 cannot initialize the auto variable under such situation.
2364 SEQ is the body of a switch expression. */
2366 static void
2367 maybe_warn_switch_unreachable_and_auto_init (gimple_seq seq)
2369 if ((!warn_switch_unreachable && !warn_trivial_auto_var_init)
2370 /* This warning doesn't play well with Fortran when optimizations
2371 are on. */
2372 || lang_GNU_Fortran ()
2373 || seq == NULL)
2374 return;
2376 struct walk_stmt_info wi;
2378 memset (&wi, 0, sizeof (wi));
2379 walk_gimple_seq (seq, warn_switch_unreachable_and_auto_init_r, NULL, &wi);
2383 /* A label entry that pairs label and a location. */
2384 struct label_entry
2386 tree label;
2387 location_t loc;
2390 /* Find LABEL in vector of label entries VEC. */
2392 static struct label_entry *
2393 find_label_entry (const auto_vec<struct label_entry> *vec, tree label)
2395 unsigned int i;
2396 struct label_entry *l;
2398 FOR_EACH_VEC_ELT (*vec, i, l)
2399 if (l->label == label)
2400 return l;
2401 return NULL;
2404 /* Return true if LABEL, a LABEL_DECL, represents a case label
2405 in a vector of labels CASES. */
2407 static bool
2408 case_label_p (const vec<tree> *cases, tree label)
2410 unsigned int i;
2411 tree l;
2413 FOR_EACH_VEC_ELT (*cases, i, l)
2414 if (CASE_LABEL (l) == label)
2415 return true;
2416 return false;
2419 /* Find the last nondebug statement in a scope STMT. */
2421 static gimple *
2422 last_stmt_in_scope (gimple *stmt)
2424 if (!stmt)
2425 return NULL;
2427 switch (gimple_code (stmt))
2429 case GIMPLE_BIND:
2431 gbind *bind = as_a <gbind *> (stmt);
2432 stmt = gimple_seq_last_nondebug_stmt (gimple_bind_body (bind));
2433 return last_stmt_in_scope (stmt);
2436 case GIMPLE_TRY:
2438 gtry *try_stmt = as_a <gtry *> (stmt);
2439 stmt = gimple_seq_last_nondebug_stmt (gimple_try_eval (try_stmt));
2440 gimple *last_eval = last_stmt_in_scope (stmt);
2441 if (gimple_stmt_may_fallthru (last_eval)
2442 && (last_eval == NULL
2443 || !gimple_call_internal_p (last_eval, IFN_FALLTHROUGH))
2444 && gimple_try_kind (try_stmt) == GIMPLE_TRY_FINALLY)
2446 stmt = gimple_seq_last_nondebug_stmt (gimple_try_cleanup (try_stmt));
2447 return last_stmt_in_scope (stmt);
2449 else
2450 return last_eval;
2453 case GIMPLE_DEBUG:
2454 gcc_unreachable ();
2456 default:
2457 return stmt;
2461 /* Collect labels that may fall through into LABELS and return the statement
2462 preceding another case label, or a user-defined label. Store a location
2463 useful to give warnings at *PREVLOC (usually the location of the returned
2464 statement or of its surrounding scope). */
2466 static gimple *
2467 collect_fallthrough_labels (gimple_stmt_iterator *gsi_p,
2468 auto_vec <struct label_entry> *labels,
2469 location_t *prevloc)
2471 gimple *prev = NULL;
2473 *prevloc = UNKNOWN_LOCATION;
2476 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_BIND)
2478 /* Recognize the special GIMPLE_BIND added by gimplify_switch_expr,
2479 which starts on a GIMPLE_SWITCH and ends with a break label.
2480 Handle that as a single statement that can fall through. */
2481 gbind *bind = as_a <gbind *> (gsi_stmt (*gsi_p));
2482 gimple *first = gimple_seq_first_stmt (gimple_bind_body (bind));
2483 gimple *last = gimple_seq_last_stmt (gimple_bind_body (bind));
2484 if (last
2485 && gimple_code (first) == GIMPLE_SWITCH
2486 && gimple_code (last) == GIMPLE_LABEL)
2488 tree label = gimple_label_label (as_a <glabel *> (last));
2489 if (SWITCH_BREAK_LABEL_P (label))
2491 prev = bind;
2492 gsi_next (gsi_p);
2493 continue;
2497 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_BIND
2498 || gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_TRY)
2500 /* Nested scope. Only look at the last statement of
2501 the innermost scope. */
2502 location_t bind_loc = gimple_location (gsi_stmt (*gsi_p));
2503 gimple *last = last_stmt_in_scope (gsi_stmt (*gsi_p));
2504 if (last)
2506 prev = last;
2507 /* It might be a label without a location. Use the
2508 location of the scope then. */
2509 if (!gimple_has_location (prev))
2510 *prevloc = bind_loc;
2512 gsi_next (gsi_p);
2513 continue;
2516 /* Ifs are tricky. */
2517 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_COND)
2519 gcond *cond_stmt = as_a <gcond *> (gsi_stmt (*gsi_p));
2520 tree false_lab = gimple_cond_false_label (cond_stmt);
2521 location_t if_loc = gimple_location (cond_stmt);
2523 /* If we have e.g.
2524 if (i > 1) goto <D.2259>; else goto D;
2525 we can't do much with the else-branch. */
2526 if (!DECL_ARTIFICIAL (false_lab))
2527 break;
2529 /* Go on until the false label, then one step back. */
2530 for (; !gsi_end_p (*gsi_p); gsi_next (gsi_p))
2532 gimple *stmt = gsi_stmt (*gsi_p);
2533 if (gimple_code (stmt) == GIMPLE_LABEL
2534 && gimple_label_label (as_a <glabel *> (stmt)) == false_lab)
2535 break;
2538 /* Not found? Oops. */
2539 if (gsi_end_p (*gsi_p))
2540 break;
2542 /* A dead label can't fall through. */
2543 if (!UNUSED_LABEL_P (false_lab))
2545 struct label_entry l = { false_lab, if_loc };
2546 labels->safe_push (l);
2549 /* Go to the last statement of the then branch. */
2550 gsi_prev (gsi_p);
2552 /* if (i != 0) goto <D.1759>; else goto <D.1760>;
2553 <D.1759>:
2554 <stmt>;
2555 goto <D.1761>;
2556 <D.1760>:
2558 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_GOTO
2559 && !gimple_has_location (gsi_stmt (*gsi_p)))
2561 /* Look at the statement before, it might be
2562 attribute fallthrough, in which case don't warn. */
2563 gsi_prev (gsi_p);
2564 bool fallthru_before_dest
2565 = gimple_call_internal_p (gsi_stmt (*gsi_p), IFN_FALLTHROUGH);
2566 gsi_next (gsi_p);
2567 tree goto_dest = gimple_goto_dest (gsi_stmt (*gsi_p));
2568 if (!fallthru_before_dest)
2570 struct label_entry l = { goto_dest, if_loc };
2571 labels->safe_push (l);
2574 /* This case is about
2575 if (1 != 0) goto <D.2022>; else goto <D.2023>;
2576 <D.2022>:
2577 n = n + 1; // #1
2578 <D.2023>: // #2
2579 <D.1988>: // #3
2580 where #2 is UNUSED_LABEL_P and we want to warn about #1 falling
2581 through to #3. So set PREV to #1. */
2582 else if (UNUSED_LABEL_P (false_lab))
2583 prev = gsi_stmt (*gsi_p);
2585 /* And move back. */
2586 gsi_next (gsi_p);
2589 /* Remember the last statement. Skip labels that are of no interest
2590 to us. */
2591 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_LABEL)
2593 tree label = gimple_label_label (as_a <glabel *> (gsi_stmt (*gsi_p)));
2594 if (find_label_entry (labels, label))
2595 prev = gsi_stmt (*gsi_p);
2597 else if (gimple_call_internal_p (gsi_stmt (*gsi_p), IFN_ASAN_MARK))
2599 else if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_PREDICT)
2601 else if (!is_gimple_debug (gsi_stmt (*gsi_p)))
2602 prev = gsi_stmt (*gsi_p);
2603 gsi_next (gsi_p);
2605 while (!gsi_end_p (*gsi_p)
2606 /* Stop if we find a case or a user-defined label. */
2607 && (gimple_code (gsi_stmt (*gsi_p)) != GIMPLE_LABEL
2608 || !gimple_has_location (gsi_stmt (*gsi_p))));
2610 if (prev && gimple_has_location (prev))
2611 *prevloc = gimple_location (prev);
2612 return prev;
2615 /* Return true if the switch fallthough warning should occur. LABEL is
2616 the label statement that we're falling through to. */
2618 static bool
2619 should_warn_for_implicit_fallthrough (gimple_stmt_iterator *gsi_p, tree label)
2621 gimple_stmt_iterator gsi = *gsi_p;
2623 /* Don't warn if the label is marked with a "falls through" comment. */
2624 if (FALLTHROUGH_LABEL_P (label))
2625 return false;
2627 /* Don't warn for non-case labels followed by a statement:
2628 case 0:
2629 foo ();
2630 label:
2631 bar ();
2632 as these are likely intentional. */
2633 if (!case_label_p (&gimplify_ctxp->case_labels, label))
2635 tree l;
2636 while (!gsi_end_p (gsi)
2637 && gimple_code (gsi_stmt (gsi)) == GIMPLE_LABEL
2638 && (l = gimple_label_label (as_a <glabel *> (gsi_stmt (gsi))))
2639 && !case_label_p (&gimplify_ctxp->case_labels, l))
2640 gsi_next_nondebug (&gsi);
2641 if (gsi_end_p (gsi) || gimple_code (gsi_stmt (gsi)) != GIMPLE_LABEL)
2642 return false;
2645 /* Don't warn for terminated branches, i.e. when the subsequent case labels
2646 immediately breaks. */
2647 gsi = *gsi_p;
2649 /* Skip all immediately following labels. */
2650 while (!gsi_end_p (gsi)
2651 && (gimple_code (gsi_stmt (gsi)) == GIMPLE_LABEL
2652 || gimple_code (gsi_stmt (gsi)) == GIMPLE_PREDICT))
2653 gsi_next_nondebug (&gsi);
2655 /* { ... something; default:; } */
2656 if (gsi_end_p (gsi)
2657 /* { ... something; default: break; } or
2658 { ... something; default: goto L; } */
2659 || gimple_code (gsi_stmt (gsi)) == GIMPLE_GOTO
2660 /* { ... something; default: return; } */
2661 || gimple_code (gsi_stmt (gsi)) == GIMPLE_RETURN)
2662 return false;
2664 return true;
2667 /* Callback for walk_gimple_seq. */
2669 static tree
2670 warn_implicit_fallthrough_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
2671 struct walk_stmt_info *)
2673 gimple *stmt = gsi_stmt (*gsi_p);
2675 *handled_ops_p = true;
2676 switch (gimple_code (stmt))
2678 case GIMPLE_TRY:
2679 case GIMPLE_BIND:
2680 case GIMPLE_CATCH:
2681 case GIMPLE_EH_FILTER:
2682 case GIMPLE_TRANSACTION:
2683 /* Walk the sub-statements. */
2684 *handled_ops_p = false;
2685 break;
2687 /* Find a sequence of form:
2689 GIMPLE_LABEL
2690 [...]
2691 <may fallthru stmt>
2692 GIMPLE_LABEL
2694 and possibly warn. */
2695 case GIMPLE_LABEL:
2697 /* Found a label. Skip all immediately following labels. */
2698 while (!gsi_end_p (*gsi_p)
2699 && gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_LABEL)
2700 gsi_next_nondebug (gsi_p);
2702 /* There might be no more statements. */
2703 if (gsi_end_p (*gsi_p))
2704 return integer_zero_node;
2706 /* Vector of labels that fall through. */
2707 auto_vec <struct label_entry> labels;
2708 location_t prevloc;
2709 gimple *prev = collect_fallthrough_labels (gsi_p, &labels, &prevloc);
2711 /* There might be no more statements. */
2712 if (gsi_end_p (*gsi_p))
2713 return integer_zero_node;
2715 gimple *next = gsi_stmt (*gsi_p);
2716 tree label;
2717 /* If what follows is a label, then we may have a fallthrough. */
2718 if (gimple_code (next) == GIMPLE_LABEL
2719 && gimple_has_location (next)
2720 && (label = gimple_label_label (as_a <glabel *> (next)))
2721 && prev != NULL)
2723 struct label_entry *l;
2724 bool warned_p = false;
2725 auto_diagnostic_group d;
2726 if (!should_warn_for_implicit_fallthrough (gsi_p, label))
2727 /* Quiet. */;
2728 else if (gimple_code (prev) == GIMPLE_LABEL
2729 && (label = gimple_label_label (as_a <glabel *> (prev)))
2730 && (l = find_label_entry (&labels, label)))
2731 warned_p = warning_at (l->loc, OPT_Wimplicit_fallthrough_,
2732 "this statement may fall through");
2733 else if (!gimple_call_internal_p (prev, IFN_FALLTHROUGH)
2734 /* Try to be clever and don't warn when the statement
2735 can't actually fall through. */
2736 && gimple_stmt_may_fallthru (prev)
2737 && prevloc != UNKNOWN_LOCATION)
2738 warned_p = warning_at (prevloc,
2739 OPT_Wimplicit_fallthrough_,
2740 "this statement may fall through");
2741 if (warned_p)
2742 inform (gimple_location (next), "here");
2744 /* Mark this label as processed so as to prevent multiple
2745 warnings in nested switches. */
2746 FALLTHROUGH_LABEL_P (label) = true;
2748 /* So that next warn_implicit_fallthrough_r will start looking for
2749 a new sequence starting with this label. */
2750 gsi_prev (gsi_p);
2753 break;
2754 default:
2755 break;
2757 return NULL_TREE;
2760 /* Warn when a switch case falls through. */
2762 static void
2763 maybe_warn_implicit_fallthrough (gimple_seq seq)
2765 if (!warn_implicit_fallthrough)
2766 return;
2768 /* This warning is meant for C/C++/ObjC/ObjC++ only. */
2769 if (!(lang_GNU_C ()
2770 || lang_GNU_CXX ()
2771 || lang_GNU_OBJC ()))
2772 return;
2774 struct walk_stmt_info wi;
2775 memset (&wi, 0, sizeof (wi));
2776 walk_gimple_seq (seq, warn_implicit_fallthrough_r, NULL, &wi);
2779 /* Callback for walk_gimple_seq. */
2781 static tree
2782 expand_FALLTHROUGH_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
2783 struct walk_stmt_info *wi)
2785 gimple *stmt = gsi_stmt (*gsi_p);
2787 *handled_ops_p = true;
2788 switch (gimple_code (stmt))
2790 case GIMPLE_TRY:
2791 case GIMPLE_BIND:
2792 case GIMPLE_CATCH:
2793 case GIMPLE_EH_FILTER:
2794 case GIMPLE_TRANSACTION:
2795 /* Walk the sub-statements. */
2796 *handled_ops_p = false;
2797 break;
2798 case GIMPLE_CALL:
2799 static_cast<location_t *>(wi->info)[0] = UNKNOWN_LOCATION;
2800 if (gimple_call_internal_p (stmt, IFN_FALLTHROUGH))
2802 location_t loc = gimple_location (stmt);
2803 gsi_remove (gsi_p, true);
2804 wi->removed_stmt = true;
2806 /* nothrow flag is added by genericize_c_loop to mark fallthrough
2807 statement at the end of some loop's body. Those should be
2808 always diagnosed, either because they indeed don't precede
2809 a case label or default label, or because the next statement
2810 is not within the same iteration statement. */
2811 if ((stmt->subcode & GF_CALL_NOTHROW) != 0)
2813 pedwarn (loc, 0, "attribute %<fallthrough%> not preceding "
2814 "a case label or default label");
2815 break;
2818 if (gsi_end_p (*gsi_p))
2820 static_cast<location_t *>(wi->info)[0] = BUILTINS_LOCATION;
2821 static_cast<location_t *>(wi->info)[1] = loc;
2822 break;
2825 bool found = false;
2827 gimple_stmt_iterator gsi2 = *gsi_p;
2828 stmt = gsi_stmt (gsi2);
2829 if (gimple_code (stmt) == GIMPLE_GOTO && !gimple_has_location (stmt))
2831 /* Go on until the artificial label. */
2832 tree goto_dest = gimple_goto_dest (stmt);
2833 for (; !gsi_end_p (gsi2); gsi_next (&gsi2))
2835 if (gimple_code (gsi_stmt (gsi2)) == GIMPLE_LABEL
2836 && gimple_label_label (as_a <glabel *> (gsi_stmt (gsi2)))
2837 == goto_dest)
2838 break;
2841 /* Not found? Stop. */
2842 if (gsi_end_p (gsi2))
2843 break;
2845 /* Look one past it. */
2846 gsi_next (&gsi2);
2849 /* We're looking for a case label or default label here. */
2850 while (!gsi_end_p (gsi2))
2852 stmt = gsi_stmt (gsi2);
2853 if (gimple_code (stmt) == GIMPLE_LABEL)
2855 tree label = gimple_label_label (as_a <glabel *> (stmt));
2856 if (gimple_has_location (stmt) && DECL_ARTIFICIAL (label))
2858 found = true;
2859 break;
2862 else if (gimple_call_internal_p (stmt, IFN_ASAN_MARK))
2864 else if (!is_gimple_debug (stmt))
2865 /* Anything else is not expected. */
2866 break;
2867 gsi_next (&gsi2);
2869 if (!found)
2870 pedwarn (loc, 0, "attribute %<fallthrough%> not preceding "
2871 "a case label or default label");
2873 break;
2874 default:
2875 static_cast<location_t *>(wi->info)[0] = UNKNOWN_LOCATION;
2876 break;
2878 return NULL_TREE;
2881 /* Expand all FALLTHROUGH () calls in SEQ. */
2883 static void
2884 expand_FALLTHROUGH (gimple_seq *seq_p)
2886 struct walk_stmt_info wi;
2887 location_t loc[2];
2888 memset (&wi, 0, sizeof (wi));
2889 loc[0] = UNKNOWN_LOCATION;
2890 loc[1] = UNKNOWN_LOCATION;
2891 wi.info = (void *) &loc[0];
2892 walk_gimple_seq_mod (seq_p, expand_FALLTHROUGH_r, NULL, &wi);
2893 if (loc[0] != UNKNOWN_LOCATION)
2894 /* We've found [[fallthrough]]; at the end of a switch, which the C++
2895 standard says is ill-formed; see [dcl.attr.fallthrough]. */
2896 pedwarn (loc[1], 0, "attribute %<fallthrough%> not preceding "
2897 "a case label or default label");
2901 /* Gimplify a SWITCH_EXPR, and collect the vector of labels it can
2902 branch to. */
2904 static enum gimplify_status
2905 gimplify_switch_expr (tree *expr_p, gimple_seq *pre_p)
2907 tree switch_expr = *expr_p;
2908 gimple_seq switch_body_seq = NULL;
2909 enum gimplify_status ret;
2910 tree index_type = TREE_TYPE (switch_expr);
2911 if (index_type == NULL_TREE)
2912 index_type = TREE_TYPE (SWITCH_COND (switch_expr));
2914 ret = gimplify_expr (&SWITCH_COND (switch_expr), pre_p, NULL, is_gimple_val,
2915 fb_rvalue);
2916 if (ret == GS_ERROR || ret == GS_UNHANDLED)
2917 return ret;
2919 if (SWITCH_BODY (switch_expr))
2921 vec<tree> labels;
2922 vec<tree> saved_labels;
2923 hash_set<tree> *saved_live_switch_vars = NULL;
2924 tree default_case = NULL_TREE;
2925 gswitch *switch_stmt;
2927 /* Save old labels, get new ones from body, then restore the old
2928 labels. Save all the things from the switch body to append after. */
2929 saved_labels = gimplify_ctxp->case_labels;
2930 gimplify_ctxp->case_labels.create (8);
2932 /* Do not create live_switch_vars if SWITCH_BODY is not a BIND_EXPR. */
2933 saved_live_switch_vars = gimplify_ctxp->live_switch_vars;
2934 tree_code body_type = TREE_CODE (SWITCH_BODY (switch_expr));
2935 if (body_type == BIND_EXPR || body_type == STATEMENT_LIST)
2936 gimplify_ctxp->live_switch_vars = new hash_set<tree> (4);
2937 else
2938 gimplify_ctxp->live_switch_vars = NULL;
2940 bool old_in_switch_expr = gimplify_ctxp->in_switch_expr;
2941 gimplify_ctxp->in_switch_expr = true;
2943 gimplify_stmt (&SWITCH_BODY (switch_expr), &switch_body_seq);
2945 gimplify_ctxp->in_switch_expr = old_in_switch_expr;
2946 maybe_warn_switch_unreachable_and_auto_init (switch_body_seq);
2947 maybe_warn_implicit_fallthrough (switch_body_seq);
2948 /* Only do this for the outermost GIMPLE_SWITCH. */
2949 if (!gimplify_ctxp->in_switch_expr)
2950 expand_FALLTHROUGH (&switch_body_seq);
2952 labels = gimplify_ctxp->case_labels;
2953 gimplify_ctxp->case_labels = saved_labels;
2955 if (gimplify_ctxp->live_switch_vars)
2957 gcc_assert (gimplify_ctxp->live_switch_vars->is_empty ());
2958 delete gimplify_ctxp->live_switch_vars;
2960 gimplify_ctxp->live_switch_vars = saved_live_switch_vars;
2962 preprocess_case_label_vec_for_gimple (labels, index_type,
2963 &default_case);
2965 bool add_bind = false;
2966 if (!default_case)
2968 glabel *new_default;
2970 default_case
2971 = build_case_label (NULL_TREE, NULL_TREE,
2972 create_artificial_label (UNKNOWN_LOCATION));
2973 if (old_in_switch_expr)
2975 SWITCH_BREAK_LABEL_P (CASE_LABEL (default_case)) = 1;
2976 add_bind = true;
2978 new_default = gimple_build_label (CASE_LABEL (default_case));
2979 gimplify_seq_add_stmt (&switch_body_seq, new_default);
2981 else if (old_in_switch_expr)
2983 gimple *last = gimple_seq_last_stmt (switch_body_seq);
2984 if (last && gimple_code (last) == GIMPLE_LABEL)
2986 tree label = gimple_label_label (as_a <glabel *> (last));
2987 if (SWITCH_BREAK_LABEL_P (label))
2988 add_bind = true;
2992 switch_stmt = gimple_build_switch (SWITCH_COND (switch_expr),
2993 default_case, labels);
2994 /* For the benefit of -Wimplicit-fallthrough, if switch_body_seq
2995 ends with a GIMPLE_LABEL holding SWITCH_BREAK_LABEL_P LABEL_DECL,
2996 wrap the GIMPLE_SWITCH up to that GIMPLE_LABEL into a GIMPLE_BIND,
2997 so that we can easily find the start and end of the switch
2998 statement. */
2999 if (add_bind)
3001 gimple_seq bind_body = NULL;
3002 gimplify_seq_add_stmt (&bind_body, switch_stmt);
3003 gimple_seq_add_seq (&bind_body, switch_body_seq);
3004 gbind *bind = gimple_build_bind (NULL_TREE, bind_body, NULL_TREE);
3005 gimple_set_location (bind, EXPR_LOCATION (switch_expr));
3006 gimplify_seq_add_stmt (pre_p, bind);
3008 else
3010 gimplify_seq_add_stmt (pre_p, switch_stmt);
3011 gimplify_seq_add_seq (pre_p, switch_body_seq);
3013 labels.release ();
3015 else
3016 gcc_unreachable ();
3018 return GS_ALL_DONE;
3021 /* Gimplify the LABEL_EXPR pointed to by EXPR_P. */
3023 static enum gimplify_status
3024 gimplify_label_expr (tree *expr_p, gimple_seq *pre_p)
3026 gcc_assert (decl_function_context (LABEL_EXPR_LABEL (*expr_p))
3027 == current_function_decl);
3029 tree label = LABEL_EXPR_LABEL (*expr_p);
3030 glabel *label_stmt = gimple_build_label (label);
3031 gimple_set_location (label_stmt, EXPR_LOCATION (*expr_p));
3032 gimplify_seq_add_stmt (pre_p, label_stmt);
3034 if (lookup_attribute ("cold", DECL_ATTRIBUTES (label)))
3035 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_COLD_LABEL,
3036 NOT_TAKEN));
3037 else if (lookup_attribute ("hot", DECL_ATTRIBUTES (label)))
3038 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_HOT_LABEL,
3039 TAKEN));
3041 return GS_ALL_DONE;
3044 /* Gimplify the CASE_LABEL_EXPR pointed to by EXPR_P. */
3046 static enum gimplify_status
3047 gimplify_case_label_expr (tree *expr_p, gimple_seq *pre_p)
3049 struct gimplify_ctx *ctxp;
3050 glabel *label_stmt;
3052 /* Invalid programs can play Duff's Device type games with, for example,
3053 #pragma omp parallel. At least in the C front end, we don't
3054 detect such invalid branches until after gimplification, in the
3055 diagnose_omp_blocks pass. */
3056 for (ctxp = gimplify_ctxp; ; ctxp = ctxp->prev_context)
3057 if (ctxp->case_labels.exists ())
3058 break;
3060 tree label = CASE_LABEL (*expr_p);
3061 label_stmt = gimple_build_label (label);
3062 gimple_set_location (label_stmt, EXPR_LOCATION (*expr_p));
3063 ctxp->case_labels.safe_push (*expr_p);
3064 gimplify_seq_add_stmt (pre_p, label_stmt);
3066 if (lookup_attribute ("cold", DECL_ATTRIBUTES (label)))
3067 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_COLD_LABEL,
3068 NOT_TAKEN));
3069 else if (lookup_attribute ("hot", DECL_ATTRIBUTES (label)))
3070 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_HOT_LABEL,
3071 TAKEN));
3073 return GS_ALL_DONE;
3076 /* Build a GOTO to the LABEL_DECL pointed to by LABEL_P, building it first
3077 if necessary. */
3079 tree
3080 build_and_jump (tree *label_p)
3082 if (label_p == NULL)
3083 /* If there's nowhere to jump, just fall through. */
3084 return NULL_TREE;
3086 if (*label_p == NULL_TREE)
3088 tree label = create_artificial_label (UNKNOWN_LOCATION);
3089 *label_p = label;
3092 return build1 (GOTO_EXPR, void_type_node, *label_p);
3095 /* Gimplify an EXIT_EXPR by converting to a GOTO_EXPR inside a COND_EXPR.
3096 This also involves building a label to jump to and communicating it to
3097 gimplify_loop_expr through gimplify_ctxp->exit_label. */
3099 static enum gimplify_status
3100 gimplify_exit_expr (tree *expr_p)
3102 tree cond = TREE_OPERAND (*expr_p, 0);
3103 tree expr;
3105 expr = build_and_jump (&gimplify_ctxp->exit_label);
3106 expr = build3 (COND_EXPR, void_type_node, cond, expr, NULL_TREE);
3107 *expr_p = expr;
3109 return GS_OK;
3112 /* *EXPR_P is a COMPONENT_REF being used as an rvalue. If its type is
3113 different from its canonical type, wrap the whole thing inside a
3114 NOP_EXPR and force the type of the COMPONENT_REF to be the canonical
3115 type.
3117 The canonical type of a COMPONENT_REF is the type of the field being
3118 referenced--unless the field is a bit-field which can be read directly
3119 in a smaller mode, in which case the canonical type is the
3120 sign-appropriate type corresponding to that mode. */
3122 static void
3123 canonicalize_component_ref (tree *expr_p)
3125 tree expr = *expr_p;
3126 tree type;
3128 gcc_assert (TREE_CODE (expr) == COMPONENT_REF);
3130 if (INTEGRAL_TYPE_P (TREE_TYPE (expr)))
3131 type = TREE_TYPE (get_unwidened (expr, NULL_TREE));
3132 else
3133 type = TREE_TYPE (TREE_OPERAND (expr, 1));
3135 /* One could argue that all the stuff below is not necessary for
3136 the non-bitfield case and declare it a FE error if type
3137 adjustment would be needed. */
3138 if (TREE_TYPE (expr) != type)
3140 #ifdef ENABLE_TYPES_CHECKING
3141 tree old_type = TREE_TYPE (expr);
3142 #endif
3143 int type_quals;
3145 /* We need to preserve qualifiers and propagate them from
3146 operand 0. */
3147 type_quals = TYPE_QUALS (type)
3148 | TYPE_QUALS (TREE_TYPE (TREE_OPERAND (expr, 0)));
3149 if (TYPE_QUALS (type) != type_quals)
3150 type = build_qualified_type (TYPE_MAIN_VARIANT (type), type_quals);
3152 /* Set the type of the COMPONENT_REF to the underlying type. */
3153 TREE_TYPE (expr) = type;
3155 #ifdef ENABLE_TYPES_CHECKING
3156 /* It is now a FE error, if the conversion from the canonical
3157 type to the original expression type is not useless. */
3158 gcc_assert (useless_type_conversion_p (old_type, type));
3159 #endif
3163 /* If a NOP conversion is changing a pointer to array of foo to a pointer
3164 to foo, embed that change in the ADDR_EXPR by converting
3165 T array[U];
3166 (T *)&array
3168 &array[L]
3169 where L is the lower bound. For simplicity, only do this for constant
3170 lower bound.
3171 The constraint is that the type of &array[L] is trivially convertible
3172 to T *. */
3174 static void
3175 canonicalize_addr_expr (tree *expr_p)
3177 tree expr = *expr_p;
3178 tree addr_expr = TREE_OPERAND (expr, 0);
3179 tree datype, ddatype, pddatype;
3181 /* We simplify only conversions from an ADDR_EXPR to a pointer type. */
3182 if (!POINTER_TYPE_P (TREE_TYPE (expr))
3183 || TREE_CODE (addr_expr) != ADDR_EXPR)
3184 return;
3186 /* The addr_expr type should be a pointer to an array. */
3187 datype = TREE_TYPE (TREE_TYPE (addr_expr));
3188 if (TREE_CODE (datype) != ARRAY_TYPE)
3189 return;
3191 /* The pointer to element type shall be trivially convertible to
3192 the expression pointer type. */
3193 ddatype = TREE_TYPE (datype);
3194 pddatype = build_pointer_type (ddatype);
3195 if (!useless_type_conversion_p (TYPE_MAIN_VARIANT (TREE_TYPE (expr)),
3196 pddatype))
3197 return;
3199 /* The lower bound and element sizes must be constant. */
3200 if (!TYPE_SIZE_UNIT (ddatype)
3201 || TREE_CODE (TYPE_SIZE_UNIT (ddatype)) != INTEGER_CST
3202 || !TYPE_DOMAIN (datype) || !TYPE_MIN_VALUE (TYPE_DOMAIN (datype))
3203 || TREE_CODE (TYPE_MIN_VALUE (TYPE_DOMAIN (datype))) != INTEGER_CST)
3204 return;
3206 /* All checks succeeded. Build a new node to merge the cast. */
3207 *expr_p = build4 (ARRAY_REF, ddatype, TREE_OPERAND (addr_expr, 0),
3208 TYPE_MIN_VALUE (TYPE_DOMAIN (datype)),
3209 NULL_TREE, NULL_TREE);
3210 *expr_p = build1 (ADDR_EXPR, pddatype, *expr_p);
3212 /* We can have stripped a required restrict qualifier above. */
3213 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
3214 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
3217 /* *EXPR_P is a NOP_EXPR or CONVERT_EXPR. Remove it and/or other conversions
3218 underneath as appropriate. */
3220 static enum gimplify_status
3221 gimplify_conversion (tree *expr_p)
3223 location_t loc = EXPR_LOCATION (*expr_p);
3224 gcc_assert (CONVERT_EXPR_P (*expr_p));
3226 /* Then strip away all but the outermost conversion. */
3227 STRIP_SIGN_NOPS (TREE_OPERAND (*expr_p, 0));
3229 /* And remove the outermost conversion if it's useless. */
3230 if (tree_ssa_useless_type_conversion (*expr_p))
3231 *expr_p = TREE_OPERAND (*expr_p, 0);
3233 /* If we still have a conversion at the toplevel,
3234 then canonicalize some constructs. */
3235 if (CONVERT_EXPR_P (*expr_p))
3237 tree sub = TREE_OPERAND (*expr_p, 0);
3239 /* If a NOP conversion is changing the type of a COMPONENT_REF
3240 expression, then canonicalize its type now in order to expose more
3241 redundant conversions. */
3242 if (TREE_CODE (sub) == COMPONENT_REF)
3243 canonicalize_component_ref (&TREE_OPERAND (*expr_p, 0));
3245 /* If a NOP conversion is changing a pointer to array of foo
3246 to a pointer to foo, embed that change in the ADDR_EXPR. */
3247 else if (TREE_CODE (sub) == ADDR_EXPR)
3248 canonicalize_addr_expr (expr_p);
3251 /* If we have a conversion to a non-register type force the
3252 use of a VIEW_CONVERT_EXPR instead. */
3253 if (CONVERT_EXPR_P (*expr_p) && !is_gimple_reg_type (TREE_TYPE (*expr_p)))
3254 *expr_p = fold_build1_loc (loc, VIEW_CONVERT_EXPR, TREE_TYPE (*expr_p),
3255 TREE_OPERAND (*expr_p, 0));
3257 /* Canonicalize CONVERT_EXPR to NOP_EXPR. */
3258 if (TREE_CODE (*expr_p) == CONVERT_EXPR)
3259 TREE_SET_CODE (*expr_p, NOP_EXPR);
3261 return GS_OK;
3264 /* Gimplify a VAR_DECL or PARM_DECL. Return GS_OK if we expanded a
3265 DECL_VALUE_EXPR, and it's worth re-examining things. */
3267 static enum gimplify_status
3268 gimplify_var_or_parm_decl (tree *expr_p)
3270 tree decl = *expr_p;
3272 /* ??? If this is a local variable, and it has not been seen in any
3273 outer BIND_EXPR, then it's probably the result of a duplicate
3274 declaration, for which we've already issued an error. It would
3275 be really nice if the front end wouldn't leak these at all.
3276 Currently the only known culprit is C++ destructors, as seen
3277 in g++.old-deja/g++.jason/binding.C.
3278 Another possible culpit are size expressions for variably modified
3279 types which are lost in the FE or not gimplified correctly. */
3280 if (VAR_P (decl)
3281 && !DECL_SEEN_IN_BIND_EXPR_P (decl)
3282 && !TREE_STATIC (decl) && !DECL_EXTERNAL (decl)
3283 && decl_function_context (decl) == current_function_decl)
3285 gcc_assert (seen_error ());
3286 return GS_ERROR;
3289 /* When within an OMP context, notice uses of variables. */
3290 if (gimplify_omp_ctxp && omp_notice_variable (gimplify_omp_ctxp, decl, true))
3291 return GS_ALL_DONE;
3293 /* If the decl is an alias for another expression, substitute it now. */
3294 if (DECL_HAS_VALUE_EXPR_P (decl))
3296 *expr_p = unshare_expr (DECL_VALUE_EXPR (decl));
3297 return GS_OK;
3300 return GS_ALL_DONE;
3303 /* Recalculate the value of the TREE_SIDE_EFFECTS flag for T. */
3305 static void
3306 recalculate_side_effects (tree t)
3308 enum tree_code code = TREE_CODE (t);
3309 int len = TREE_OPERAND_LENGTH (t);
3310 int i;
3312 switch (TREE_CODE_CLASS (code))
3314 case tcc_expression:
3315 switch (code)
3317 case INIT_EXPR:
3318 case MODIFY_EXPR:
3319 case VA_ARG_EXPR:
3320 case PREDECREMENT_EXPR:
3321 case PREINCREMENT_EXPR:
3322 case POSTDECREMENT_EXPR:
3323 case POSTINCREMENT_EXPR:
3324 /* All of these have side-effects, no matter what their
3325 operands are. */
3326 return;
3328 default:
3329 break;
3331 /* Fall through. */
3333 case tcc_comparison: /* a comparison expression */
3334 case tcc_unary: /* a unary arithmetic expression */
3335 case tcc_binary: /* a binary arithmetic expression */
3336 case tcc_reference: /* a reference */
3337 case tcc_vl_exp: /* a function call */
3338 TREE_SIDE_EFFECTS (t) = TREE_THIS_VOLATILE (t);
3339 for (i = 0; i < len; ++i)
3341 tree op = TREE_OPERAND (t, i);
3342 if (op && TREE_SIDE_EFFECTS (op))
3343 TREE_SIDE_EFFECTS (t) = 1;
3345 break;
3347 case tcc_constant:
3348 /* No side-effects. */
3349 return;
3351 default:
3352 if (code == SSA_NAME)
3353 /* No side-effects. */
3354 return;
3355 gcc_unreachable ();
3359 /* Gimplify the COMPONENT_REF, ARRAY_REF, REALPART_EXPR or IMAGPART_EXPR
3360 node *EXPR_P.
3362 compound_lval
3363 : min_lval '[' val ']'
3364 | min_lval '.' ID
3365 | compound_lval '[' val ']'
3366 | compound_lval '.' ID
3368 This is not part of the original SIMPLE definition, which separates
3369 array and member references, but it seems reasonable to handle them
3370 together. Also, this way we don't run into problems with union
3371 aliasing; gcc requires that for accesses through a union to alias, the
3372 union reference must be explicit, which was not always the case when we
3373 were splitting up array and member refs.
3375 PRE_P points to the sequence where side effects that must happen before
3376 *EXPR_P should be stored.
3378 POST_P points to the sequence where side effects that must happen after
3379 *EXPR_P should be stored. */
3381 static enum gimplify_status
3382 gimplify_compound_lval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
3383 fallback_t fallback)
3385 tree *p;
3386 enum gimplify_status ret = GS_ALL_DONE, tret;
3387 int i;
3388 location_t loc = EXPR_LOCATION (*expr_p);
3389 tree expr = *expr_p;
3391 /* Create a stack of the subexpressions so later we can walk them in
3392 order from inner to outer. */
3393 auto_vec<tree, 10> expr_stack;
3395 /* We can handle anything that get_inner_reference can deal with. */
3396 for (p = expr_p; ; p = &TREE_OPERAND (*p, 0))
3398 restart:
3399 /* Fold INDIRECT_REFs now to turn them into ARRAY_REFs. */
3400 if (TREE_CODE (*p) == INDIRECT_REF)
3401 *p = fold_indirect_ref_loc (loc, *p);
3403 if (handled_component_p (*p))
3405 /* Expand DECL_VALUE_EXPR now. In some cases that may expose
3406 additional COMPONENT_REFs. */
3407 else if ((VAR_P (*p) || TREE_CODE (*p) == PARM_DECL)
3408 && gimplify_var_or_parm_decl (p) == GS_OK)
3409 goto restart;
3410 else
3411 break;
3413 expr_stack.safe_push (*p);
3416 gcc_assert (expr_stack.length ());
3418 /* Now EXPR_STACK is a stack of pointers to all the refs we've
3419 walked through and P points to the innermost expression.
3421 Java requires that we elaborated nodes in source order. That
3422 means we must gimplify the inner expression followed by each of
3423 the indices, in order. But we can't gimplify the inner
3424 expression until we deal with any variable bounds, sizes, or
3425 positions in order to deal with PLACEHOLDER_EXPRs.
3427 The base expression may contain a statement expression that
3428 has declarations used in size expressions, so has to be
3429 gimplified before gimplifying the size expressions.
3431 So we do this in three steps. First we deal with variable
3432 bounds, sizes, and positions, then we gimplify the base and
3433 ensure it is memory if needed, then we deal with the annotations
3434 for any variables in the components and any indices, from left
3435 to right. */
3437 bool need_non_reg = false;
3438 for (i = expr_stack.length () - 1; i >= 0; i--)
3440 tree t = expr_stack[i];
3442 if (error_operand_p (TREE_OPERAND (t, 0)))
3443 return GS_ERROR;
3445 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
3447 /* Deal with the low bound and element type size and put them into
3448 the ARRAY_REF. If these values are set, they have already been
3449 gimplified. */
3450 if (TREE_OPERAND (t, 2) == NULL_TREE)
3452 tree low = unshare_expr (array_ref_low_bound (t));
3453 if (!is_gimple_min_invariant (low))
3455 TREE_OPERAND (t, 2) = low;
3459 if (TREE_OPERAND (t, 3) == NULL_TREE)
3461 tree elmt_size = array_ref_element_size (t);
3462 if (!is_gimple_min_invariant (elmt_size))
3464 elmt_size = unshare_expr (elmt_size);
3465 tree elmt_type = TREE_TYPE (TREE_TYPE (TREE_OPERAND (t, 0)));
3466 tree factor = size_int (TYPE_ALIGN_UNIT (elmt_type));
3468 /* Divide the element size by the alignment of the element
3469 type (above). */
3470 elmt_size = size_binop_loc (loc, EXACT_DIV_EXPR,
3471 elmt_size, factor);
3473 TREE_OPERAND (t, 3) = elmt_size;
3476 need_non_reg = true;
3478 else if (TREE_CODE (t) == COMPONENT_REF)
3480 /* Set the field offset into T and gimplify it. */
3481 if (TREE_OPERAND (t, 2) == NULL_TREE)
3483 tree offset = component_ref_field_offset (t);
3484 if (!is_gimple_min_invariant (offset))
3486 offset = unshare_expr (offset);
3487 tree field = TREE_OPERAND (t, 1);
3488 tree factor
3489 = size_int (DECL_OFFSET_ALIGN (field) / BITS_PER_UNIT);
3491 /* Divide the offset by its alignment. */
3492 offset = size_binop_loc (loc, EXACT_DIV_EXPR,
3493 offset, factor);
3495 TREE_OPERAND (t, 2) = offset;
3498 need_non_reg = true;
3500 else if (!is_gimple_reg_type (TREE_TYPE (t)))
3501 /* When the result of an operation, in particular a VIEW_CONVERT_EXPR
3502 is a non-register type then require the base object to be a
3503 non-register as well. */
3504 need_non_reg = true;
3507 /* Step 2 is to gimplify the base expression. Make sure lvalue is set
3508 so as to match the min_lval predicate. Failure to do so may result
3509 in the creation of large aggregate temporaries. */
3510 tret = gimplify_expr (p, pre_p, post_p, is_gimple_min_lval,
3511 fallback | fb_lvalue);
3512 ret = MIN (ret, tret);
3513 if (ret == GS_ERROR)
3514 return GS_ERROR;
3516 /* Step 2a: if we have component references we do not support on
3517 registers then make sure the base isn't a register. Of course
3518 we can only do so if an rvalue is OK. */
3519 if (need_non_reg && (fallback & fb_rvalue))
3520 prepare_gimple_addressable (p, pre_p);
3523 /* Step 3: gimplify size expressions and the indices and operands of
3524 ARRAY_REF. During this loop we also remove any useless conversions.
3525 If we operate on a register also make sure to properly gimplify
3526 to individual operations. */
3528 bool reg_operations = is_gimple_reg (*p);
3529 for (; expr_stack.length () > 0; )
3531 tree t = expr_stack.pop ();
3533 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
3535 gcc_assert (!reg_operations);
3537 /* Gimplify the low bound and element type size. */
3538 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
3539 is_gimple_reg, fb_rvalue);
3540 ret = MIN (ret, tret);
3542 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p, post_p,
3543 is_gimple_reg, fb_rvalue);
3544 ret = MIN (ret, tret);
3546 /* Gimplify the dimension. */
3547 tret = gimplify_expr (&TREE_OPERAND (t, 1), pre_p, post_p,
3548 is_gimple_val, fb_rvalue);
3549 ret = MIN (ret, tret);
3551 else if (TREE_CODE (t) == COMPONENT_REF)
3553 gcc_assert (!reg_operations);
3555 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
3556 is_gimple_reg, fb_rvalue);
3557 ret = MIN (ret, tret);
3559 else if (reg_operations)
3561 tret = gimplify_expr (&TREE_OPERAND (t, 0), pre_p, post_p,
3562 is_gimple_val, fb_rvalue);
3563 ret = MIN (ret, tret);
3566 STRIP_USELESS_TYPE_CONVERSION (TREE_OPERAND (t, 0));
3568 /* The innermost expression P may have originally had
3569 TREE_SIDE_EFFECTS set which would have caused all the outer
3570 expressions in *EXPR_P leading to P to also have had
3571 TREE_SIDE_EFFECTS set. */
3572 recalculate_side_effects (t);
3575 /* If the outermost expression is a COMPONENT_REF, canonicalize its type. */
3576 if ((fallback & fb_rvalue) && TREE_CODE (*expr_p) == COMPONENT_REF)
3578 canonicalize_component_ref (expr_p);
3581 expr_stack.release ();
3583 gcc_assert (*expr_p == expr || ret != GS_ALL_DONE);
3585 return ret;
3588 /* Gimplify the self modifying expression pointed to by EXPR_P
3589 (++, --, +=, -=).
3591 PRE_P points to the list where side effects that must happen before
3592 *EXPR_P should be stored.
3594 POST_P points to the list where side effects that must happen after
3595 *EXPR_P should be stored.
3597 WANT_VALUE is nonzero iff we want to use the value of this expression
3598 in another expression.
3600 ARITH_TYPE is the type the computation should be performed in. */
3602 enum gimplify_status
3603 gimplify_self_mod_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
3604 bool want_value, tree arith_type)
3606 enum tree_code code;
3607 tree lhs, lvalue, rhs, t1;
3608 gimple_seq post = NULL, *orig_post_p = post_p;
3609 bool postfix;
3610 enum tree_code arith_code;
3611 enum gimplify_status ret;
3612 location_t loc = EXPR_LOCATION (*expr_p);
3614 code = TREE_CODE (*expr_p);
3616 gcc_assert (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR
3617 || code == PREINCREMENT_EXPR || code == PREDECREMENT_EXPR);
3619 /* Prefix or postfix? */
3620 if (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR)
3621 /* Faster to treat as prefix if result is not used. */
3622 postfix = want_value;
3623 else
3624 postfix = false;
3626 /* For postfix, make sure the inner expression's post side effects
3627 are executed after side effects from this expression. */
3628 if (postfix)
3629 post_p = &post;
3631 /* Add or subtract? */
3632 if (code == PREINCREMENT_EXPR || code == POSTINCREMENT_EXPR)
3633 arith_code = PLUS_EXPR;
3634 else
3635 arith_code = MINUS_EXPR;
3637 /* Gimplify the LHS into a GIMPLE lvalue. */
3638 lvalue = TREE_OPERAND (*expr_p, 0);
3639 ret = gimplify_expr (&lvalue, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
3640 if (ret == GS_ERROR)
3641 return ret;
3643 /* Extract the operands to the arithmetic operation. */
3644 lhs = lvalue;
3645 rhs = TREE_OPERAND (*expr_p, 1);
3647 /* For postfix operator, we evaluate the LHS to an rvalue and then use
3648 that as the result value and in the postqueue operation. */
3649 if (postfix)
3651 ret = gimplify_expr (&lhs, pre_p, post_p, is_gimple_val, fb_rvalue);
3652 if (ret == GS_ERROR)
3653 return ret;
3655 lhs = get_initialized_tmp_var (lhs, pre_p);
3658 /* For POINTERs increment, use POINTER_PLUS_EXPR. */
3659 if (POINTER_TYPE_P (TREE_TYPE (lhs)))
3661 rhs = convert_to_ptrofftype_loc (loc, rhs);
3662 if (arith_code == MINUS_EXPR)
3663 rhs = fold_build1_loc (loc, NEGATE_EXPR, TREE_TYPE (rhs), rhs);
3664 t1 = fold_build2 (POINTER_PLUS_EXPR, TREE_TYPE (*expr_p), lhs, rhs);
3666 else
3667 t1 = fold_convert (TREE_TYPE (*expr_p),
3668 fold_build2 (arith_code, arith_type,
3669 fold_convert (arith_type, lhs),
3670 fold_convert (arith_type, rhs)));
3672 if (postfix)
3674 gimplify_assign (lvalue, t1, pre_p);
3675 gimplify_seq_add_seq (orig_post_p, post);
3676 *expr_p = lhs;
3677 return GS_ALL_DONE;
3679 else
3681 *expr_p = build2 (MODIFY_EXPR, TREE_TYPE (lvalue), lvalue, t1);
3682 return GS_OK;
3686 /* If *EXPR_P has a variable sized type, wrap it in a WITH_SIZE_EXPR. */
3688 static void
3689 maybe_with_size_expr (tree *expr_p)
3691 tree expr = *expr_p;
3692 tree type = TREE_TYPE (expr);
3693 tree size;
3695 /* If we've already wrapped this or the type is error_mark_node, we can't do
3696 anything. */
3697 if (TREE_CODE (expr) == WITH_SIZE_EXPR
3698 || type == error_mark_node)
3699 return;
3701 /* If the size isn't known or is a constant, we have nothing to do. */
3702 size = TYPE_SIZE_UNIT (type);
3703 if (!size || poly_int_tree_p (size))
3704 return;
3706 /* Otherwise, make a WITH_SIZE_EXPR. */
3707 size = unshare_expr (size);
3708 size = SUBSTITUTE_PLACEHOLDER_IN_EXPR (size, expr);
3709 *expr_p = build2 (WITH_SIZE_EXPR, type, expr, size);
3712 /* Helper for gimplify_call_expr. Gimplify a single argument *ARG_P
3713 Store any side-effects in PRE_P. CALL_LOCATION is the location of
3714 the CALL_EXPR. If ALLOW_SSA is set the actual parameter may be
3715 gimplified to an SSA name. */
3717 enum gimplify_status
3718 gimplify_arg (tree *arg_p, gimple_seq *pre_p, location_t call_location,
3719 bool allow_ssa)
3721 bool (*test) (tree);
3722 fallback_t fb;
3724 /* In general, we allow lvalues for function arguments to avoid
3725 extra overhead of copying large aggregates out of even larger
3726 aggregates into temporaries only to copy the temporaries to
3727 the argument list. Make optimizers happy by pulling out to
3728 temporaries those types that fit in registers. */
3729 if (is_gimple_reg_type (TREE_TYPE (*arg_p)))
3730 test = is_gimple_val, fb = fb_rvalue;
3731 else
3733 test = is_gimple_lvalue, fb = fb_either;
3734 /* Also strip a TARGET_EXPR that would force an extra copy. */
3735 if (TREE_CODE (*arg_p) == TARGET_EXPR)
3737 tree init = TARGET_EXPR_INITIAL (*arg_p);
3738 if (init
3739 && !VOID_TYPE_P (TREE_TYPE (init)))
3740 *arg_p = init;
3744 /* If this is a variable sized type, we must remember the size. */
3745 maybe_with_size_expr (arg_p);
3747 /* FIXME diagnostics: This will mess up gcc.dg/Warray-bounds.c. */
3748 /* Make sure arguments have the same location as the function call
3749 itself. */
3750 protected_set_expr_location (*arg_p, call_location);
3752 /* There is a sequence point before a function call. Side effects in
3753 the argument list must occur before the actual call. So, when
3754 gimplifying arguments, force gimplify_expr to use an internal
3755 post queue which is then appended to the end of PRE_P. */
3756 return gimplify_expr (arg_p, pre_p, NULL, test, fb, allow_ssa);
3759 /* Don't fold inside offloading or taskreg regions: it can break code by
3760 adding decl references that weren't in the source. We'll do it during
3761 omplower pass instead. */
3763 static bool
3764 maybe_fold_stmt (gimple_stmt_iterator *gsi)
3766 struct gimplify_omp_ctx *ctx;
3767 for (ctx = gimplify_omp_ctxp; ctx; ctx = ctx->outer_context)
3768 if ((ctx->region_type & (ORT_TARGET | ORT_PARALLEL | ORT_TASK)) != 0)
3769 return false;
3770 else if ((ctx->region_type & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
3771 return false;
3772 /* Delay folding of builtins until the IL is in consistent state
3773 so the diagnostic machinery can do a better job. */
3774 if (gimple_call_builtin_p (gsi_stmt (*gsi)))
3775 return false;
3776 return fold_stmt (gsi);
3779 /* Gimplify the CALL_EXPR node *EXPR_P into the GIMPLE sequence PRE_P.
3780 WANT_VALUE is true if the result of the call is desired. */
3782 static enum gimplify_status
3783 gimplify_call_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
3785 tree fndecl, parms, p, fnptrtype;
3786 enum gimplify_status ret;
3787 int i, nargs;
3788 gcall *call;
3789 bool builtin_va_start_p = false;
3790 location_t loc = EXPR_LOCATION (*expr_p);
3792 gcc_assert (TREE_CODE (*expr_p) == CALL_EXPR);
3794 /* For reliable diagnostics during inlining, it is necessary that
3795 every call_expr be annotated with file and line. */
3796 if (! EXPR_HAS_LOCATION (*expr_p))
3797 SET_EXPR_LOCATION (*expr_p, input_location);
3799 /* Gimplify internal functions created in the FEs. */
3800 if (CALL_EXPR_FN (*expr_p) == NULL_TREE)
3802 if (want_value)
3803 return GS_ALL_DONE;
3805 nargs = call_expr_nargs (*expr_p);
3806 enum internal_fn ifn = CALL_EXPR_IFN (*expr_p);
3807 auto_vec<tree> vargs (nargs);
3809 if (ifn == IFN_ASSUME)
3811 if (simple_condition_p (CALL_EXPR_ARG (*expr_p, 0)))
3813 /* If the [[assume (cond)]]; condition is simple
3814 enough and can be evaluated unconditionally
3815 without side-effects, expand it as
3816 if (!cond) __builtin_unreachable (); */
3817 tree fndecl = builtin_decl_explicit (BUILT_IN_UNREACHABLE);
3818 *expr_p = build3 (COND_EXPR, void_type_node,
3819 CALL_EXPR_ARG (*expr_p, 0), void_node,
3820 build_call_expr_loc (EXPR_LOCATION (*expr_p),
3821 fndecl, 0));
3822 return GS_OK;
3824 /* If not optimizing, ignore the assumptions. */
3825 if (!optimize || seen_error ())
3827 *expr_p = NULL_TREE;
3828 return GS_ALL_DONE;
3830 /* Temporarily, until gimple lowering, transform
3831 .ASSUME (cond);
3832 into:
3833 [[assume (guard)]]
3835 guard = cond;
3837 such that gimple lowering can outline the condition into
3838 a separate function easily. */
3839 tree guard = create_tmp_var (boolean_type_node);
3840 *expr_p = build2 (MODIFY_EXPR, void_type_node, guard,
3841 gimple_boolify (CALL_EXPR_ARG (*expr_p, 0)));
3842 *expr_p = build3 (BIND_EXPR, void_type_node, NULL, *expr_p, NULL);
3843 push_gimplify_context ();
3844 gimple_seq body = NULL;
3845 gimple *g = gimplify_and_return_first (*expr_p, &body);
3846 pop_gimplify_context (g);
3847 g = gimple_build_assume (guard, body);
3848 gimple_set_location (g, loc);
3849 gimplify_seq_add_stmt (pre_p, g);
3850 *expr_p = NULL_TREE;
3851 return GS_ALL_DONE;
3854 for (i = 0; i < nargs; i++)
3856 gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
3857 EXPR_LOCATION (*expr_p));
3858 vargs.quick_push (CALL_EXPR_ARG (*expr_p, i));
3861 gcall *call = gimple_build_call_internal_vec (ifn, vargs);
3862 gimple_call_set_nothrow (call, TREE_NOTHROW (*expr_p));
3863 gimplify_seq_add_stmt (pre_p, call);
3864 return GS_ALL_DONE;
3867 /* This may be a call to a builtin function.
3869 Builtin function calls may be transformed into different
3870 (and more efficient) builtin function calls under certain
3871 circumstances. Unfortunately, gimplification can muck things
3872 up enough that the builtin expanders are not aware that certain
3873 transformations are still valid.
3875 So we attempt transformation/gimplification of the call before
3876 we gimplify the CALL_EXPR. At this time we do not manage to
3877 transform all calls in the same manner as the expanders do, but
3878 we do transform most of them. */
3879 fndecl = get_callee_fndecl (*expr_p);
3880 if (fndecl && fndecl_built_in_p (fndecl, BUILT_IN_NORMAL))
3881 switch (DECL_FUNCTION_CODE (fndecl))
3883 CASE_BUILT_IN_ALLOCA:
3884 /* If the call has been built for a variable-sized object, then we
3885 want to restore the stack level when the enclosing BIND_EXPR is
3886 exited to reclaim the allocated space; otherwise, we precisely
3887 need to do the opposite and preserve the latest stack level. */
3888 if (CALL_ALLOCA_FOR_VAR_P (*expr_p))
3889 gimplify_ctxp->save_stack = true;
3890 else
3891 gimplify_ctxp->keep_stack = true;
3892 break;
3894 case BUILT_IN_VA_START:
3896 builtin_va_start_p = true;
3897 if (call_expr_nargs (*expr_p) < 2)
3899 error ("too few arguments to function %<va_start%>");
3900 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
3901 return GS_OK;
3904 if (fold_builtin_next_arg (*expr_p, true))
3906 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
3907 return GS_OK;
3909 break;
3912 case BUILT_IN_EH_RETURN:
3913 cfun->calls_eh_return = true;
3914 break;
3916 case BUILT_IN_CLEAR_PADDING:
3917 if (call_expr_nargs (*expr_p) == 1)
3919 /* Remember the original type of the argument in an internal
3920 dummy second argument, as in GIMPLE pointer conversions are
3921 useless. Also mark this call as not for automatic
3922 initialization in the internal dummy third argument. */
3923 p = CALL_EXPR_ARG (*expr_p, 0);
3924 *expr_p
3925 = build_call_expr_loc (EXPR_LOCATION (*expr_p), fndecl, 2, p,
3926 build_zero_cst (TREE_TYPE (p)));
3927 return GS_OK;
3929 break;
3931 default:
3934 if (fndecl && fndecl_built_in_p (fndecl))
3936 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
3937 if (new_tree && new_tree != *expr_p)
3939 /* There was a transformation of this call which computes the
3940 same value, but in a more efficient way. Return and try
3941 again. */
3942 *expr_p = new_tree;
3943 return GS_OK;
3947 /* Remember the original function pointer type. */
3948 fnptrtype = TREE_TYPE (CALL_EXPR_FN (*expr_p));
3950 if (flag_openmp
3951 && fndecl
3952 && cfun
3953 && (cfun->curr_properties & PROP_gimple_any) == 0)
3955 tree variant = omp_resolve_declare_variant (fndecl);
3956 if (variant != fndecl)
3957 CALL_EXPR_FN (*expr_p) = build1 (ADDR_EXPR, fnptrtype, variant);
3960 /* There is a sequence point before the call, so any side effects in
3961 the calling expression must occur before the actual call. Force
3962 gimplify_expr to use an internal post queue. */
3963 ret = gimplify_expr (&CALL_EXPR_FN (*expr_p), pre_p, NULL,
3964 is_gimple_call_addr, fb_rvalue);
3966 if (ret == GS_ERROR)
3967 return GS_ERROR;
3969 nargs = call_expr_nargs (*expr_p);
3971 /* Get argument types for verification. */
3972 fndecl = get_callee_fndecl (*expr_p);
3973 parms = NULL_TREE;
3974 if (fndecl)
3975 parms = TYPE_ARG_TYPES (TREE_TYPE (fndecl));
3976 else
3977 parms = TYPE_ARG_TYPES (TREE_TYPE (fnptrtype));
3979 if (fndecl && DECL_ARGUMENTS (fndecl))
3980 p = DECL_ARGUMENTS (fndecl);
3981 else if (parms)
3982 p = parms;
3983 else
3984 p = NULL_TREE;
3985 for (i = 0; i < nargs && p; i++, p = TREE_CHAIN (p))
3988 /* If the last argument is __builtin_va_arg_pack () and it is not
3989 passed as a named argument, decrease the number of CALL_EXPR
3990 arguments and set instead the CALL_EXPR_VA_ARG_PACK flag. */
3991 if (!p
3992 && i < nargs
3993 && TREE_CODE (CALL_EXPR_ARG (*expr_p, nargs - 1)) == CALL_EXPR)
3995 tree last_arg = CALL_EXPR_ARG (*expr_p, nargs - 1);
3996 tree last_arg_fndecl = get_callee_fndecl (last_arg);
3998 if (last_arg_fndecl
3999 && fndecl_built_in_p (last_arg_fndecl, BUILT_IN_VA_ARG_PACK))
4001 tree call = *expr_p;
4003 --nargs;
4004 *expr_p = build_call_array_loc (loc, TREE_TYPE (call),
4005 CALL_EXPR_FN (call),
4006 nargs, CALL_EXPR_ARGP (call));
4008 /* Copy all CALL_EXPR flags, location and block, except
4009 CALL_EXPR_VA_ARG_PACK flag. */
4010 CALL_EXPR_STATIC_CHAIN (*expr_p) = CALL_EXPR_STATIC_CHAIN (call);
4011 CALL_EXPR_TAILCALL (*expr_p) = CALL_EXPR_TAILCALL (call);
4012 CALL_EXPR_RETURN_SLOT_OPT (*expr_p)
4013 = CALL_EXPR_RETURN_SLOT_OPT (call);
4014 CALL_FROM_THUNK_P (*expr_p) = CALL_FROM_THUNK_P (call);
4015 SET_EXPR_LOCATION (*expr_p, EXPR_LOCATION (call));
4017 /* Set CALL_EXPR_VA_ARG_PACK. */
4018 CALL_EXPR_VA_ARG_PACK (*expr_p) = 1;
4022 /* If the call returns twice then after building the CFG the call
4023 argument computations will no longer dominate the call because
4024 we add an abnormal incoming edge to the call. So do not use SSA
4025 vars there. */
4026 bool returns_twice = call_expr_flags (*expr_p) & ECF_RETURNS_TWICE;
4028 /* Gimplify the function arguments. */
4029 if (nargs > 0)
4031 for (i = (PUSH_ARGS_REVERSED ? nargs - 1 : 0);
4032 PUSH_ARGS_REVERSED ? i >= 0 : i < nargs;
4033 PUSH_ARGS_REVERSED ? i-- : i++)
4035 enum gimplify_status t;
4037 /* Avoid gimplifying the second argument to va_start, which needs to
4038 be the plain PARM_DECL. */
4039 if ((i != 1) || !builtin_va_start_p)
4041 t = gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
4042 EXPR_LOCATION (*expr_p), ! returns_twice);
4044 if (t == GS_ERROR)
4045 ret = GS_ERROR;
4050 /* Gimplify the static chain. */
4051 if (CALL_EXPR_STATIC_CHAIN (*expr_p))
4053 if (fndecl && !DECL_STATIC_CHAIN (fndecl))
4054 CALL_EXPR_STATIC_CHAIN (*expr_p) = NULL;
4055 else
4057 enum gimplify_status t;
4058 t = gimplify_arg (&CALL_EXPR_STATIC_CHAIN (*expr_p), pre_p,
4059 EXPR_LOCATION (*expr_p), ! returns_twice);
4060 if (t == GS_ERROR)
4061 ret = GS_ERROR;
4065 /* Verify the function result. */
4066 if (want_value && fndecl
4067 && VOID_TYPE_P (TREE_TYPE (TREE_TYPE (fnptrtype))))
4069 error_at (loc, "using result of function returning %<void%>");
4070 ret = GS_ERROR;
4073 /* Try this again in case gimplification exposed something. */
4074 if (ret != GS_ERROR)
4076 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
4078 if (new_tree && new_tree != *expr_p)
4080 /* There was a transformation of this call which computes the
4081 same value, but in a more efficient way. Return and try
4082 again. */
4083 *expr_p = new_tree;
4084 return GS_OK;
4087 else
4089 *expr_p = error_mark_node;
4090 return GS_ERROR;
4093 /* If the function is "const" or "pure", then clear TREE_SIDE_EFFECTS on its
4094 decl. This allows us to eliminate redundant or useless
4095 calls to "const" functions. */
4096 if (TREE_CODE (*expr_p) == CALL_EXPR)
4098 int flags = call_expr_flags (*expr_p);
4099 if (flags & (ECF_CONST | ECF_PURE)
4100 /* An infinite loop is considered a side effect. */
4101 && !(flags & (ECF_LOOPING_CONST_OR_PURE)))
4102 TREE_SIDE_EFFECTS (*expr_p) = 0;
4105 /* If the value is not needed by the caller, emit a new GIMPLE_CALL
4106 and clear *EXPR_P. Otherwise, leave *EXPR_P in its gimplified
4107 form and delegate the creation of a GIMPLE_CALL to
4108 gimplify_modify_expr. This is always possible because when
4109 WANT_VALUE is true, the caller wants the result of this call into
4110 a temporary, which means that we will emit an INIT_EXPR in
4111 internal_get_tmp_var which will then be handled by
4112 gimplify_modify_expr. */
4113 if (!want_value)
4115 /* The CALL_EXPR in *EXPR_P is already in GIMPLE form, so all we
4116 have to do is replicate it as a GIMPLE_CALL tuple. */
4117 gimple_stmt_iterator gsi;
4118 call = gimple_build_call_from_tree (*expr_p, fnptrtype);
4119 notice_special_calls (call);
4120 gimplify_seq_add_stmt (pre_p, call);
4121 gsi = gsi_last (*pre_p);
4122 maybe_fold_stmt (&gsi);
4123 *expr_p = NULL_TREE;
4125 else
4126 /* Remember the original function type. */
4127 CALL_EXPR_FN (*expr_p) = build1 (NOP_EXPR, fnptrtype,
4128 CALL_EXPR_FN (*expr_p));
4130 return ret;
4133 /* Handle shortcut semantics in the predicate operand of a COND_EXPR by
4134 rewriting it into multiple COND_EXPRs, and possibly GOTO_EXPRs.
4136 TRUE_LABEL_P and FALSE_LABEL_P point to the labels to jump to if the
4137 condition is true or false, respectively. If null, we should generate
4138 our own to skip over the evaluation of this specific expression.
4140 LOCUS is the source location of the COND_EXPR.
4142 This function is the tree equivalent of do_jump.
4144 shortcut_cond_r should only be called by shortcut_cond_expr. */
4146 static tree
4147 shortcut_cond_r (tree pred, tree *true_label_p, tree *false_label_p,
4148 location_t locus)
4150 tree local_label = NULL_TREE;
4151 tree t, expr = NULL;
4153 /* OK, it's not a simple case; we need to pull apart the COND_EXPR to
4154 retain the shortcut semantics. Just insert the gotos here;
4155 shortcut_cond_expr will append the real blocks later. */
4156 if (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
4158 location_t new_locus;
4160 /* Turn if (a && b) into
4162 if (a); else goto no;
4163 if (b) goto yes; else goto no;
4164 (no:) */
4166 if (false_label_p == NULL)
4167 false_label_p = &local_label;
4169 /* Keep the original source location on the first 'if'. */
4170 t = shortcut_cond_r (TREE_OPERAND (pred, 0), NULL, false_label_p, locus);
4171 append_to_statement_list (t, &expr);
4173 /* Set the source location of the && on the second 'if'. */
4174 new_locus = rexpr_location (pred, locus);
4175 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
4176 new_locus);
4177 append_to_statement_list (t, &expr);
4179 else if (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
4181 location_t new_locus;
4183 /* Turn if (a || b) into
4185 if (a) goto yes;
4186 if (b) goto yes; else goto no;
4187 (yes:) */
4189 if (true_label_p == NULL)
4190 true_label_p = &local_label;
4192 /* Keep the original source location on the first 'if'. */
4193 t = shortcut_cond_r (TREE_OPERAND (pred, 0), true_label_p, NULL, locus);
4194 append_to_statement_list (t, &expr);
4196 /* Set the source location of the || on the second 'if'. */
4197 new_locus = rexpr_location (pred, locus);
4198 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
4199 new_locus);
4200 append_to_statement_list (t, &expr);
4202 else if (TREE_CODE (pred) == COND_EXPR
4203 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 1)))
4204 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 2))))
4206 location_t new_locus;
4208 /* As long as we're messing with gotos, turn if (a ? b : c) into
4209 if (a)
4210 if (b) goto yes; else goto no;
4211 else
4212 if (c) goto yes; else goto no;
4214 Don't do this if one of the arms has void type, which can happen
4215 in C++ when the arm is throw. */
4217 /* Keep the original source location on the first 'if'. Set the source
4218 location of the ? on the second 'if'. */
4219 new_locus = rexpr_location (pred, locus);
4220 expr = build3 (COND_EXPR, void_type_node, TREE_OPERAND (pred, 0),
4221 shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p,
4222 false_label_p, locus),
4223 shortcut_cond_r (TREE_OPERAND (pred, 2), true_label_p,
4224 false_label_p, new_locus));
4226 else
4228 expr = build3 (COND_EXPR, void_type_node, pred,
4229 build_and_jump (true_label_p),
4230 build_and_jump (false_label_p));
4231 SET_EXPR_LOCATION (expr, locus);
4234 if (local_label)
4236 t = build1 (LABEL_EXPR, void_type_node, local_label);
4237 append_to_statement_list (t, &expr);
4240 return expr;
4243 /* If EXPR is a GOTO_EXPR, return it. If it is a STATEMENT_LIST, skip
4244 any of its leading DEBUG_BEGIN_STMTS and recurse on the subsequent
4245 statement, if it is the last one. Otherwise, return NULL. */
4247 static tree
4248 find_goto (tree expr)
4250 if (!expr)
4251 return NULL_TREE;
4253 if (TREE_CODE (expr) == GOTO_EXPR)
4254 return expr;
4256 if (TREE_CODE (expr) != STATEMENT_LIST)
4257 return NULL_TREE;
4259 tree_stmt_iterator i = tsi_start (expr);
4261 while (!tsi_end_p (i) && TREE_CODE (tsi_stmt (i)) == DEBUG_BEGIN_STMT)
4262 tsi_next (&i);
4264 if (!tsi_one_before_end_p (i))
4265 return NULL_TREE;
4267 return find_goto (tsi_stmt (i));
4270 /* Same as find_goto, except that it returns NULL if the destination
4271 is not a LABEL_DECL. */
4273 static inline tree
4274 find_goto_label (tree expr)
4276 tree dest = find_goto (expr);
4277 if (dest && TREE_CODE (GOTO_DESTINATION (dest)) == LABEL_DECL)
4278 return dest;
4279 return NULL_TREE;
4282 /* Given a conditional expression EXPR with short-circuit boolean
4283 predicates using TRUTH_ANDIF_EXPR or TRUTH_ORIF_EXPR, break the
4284 predicate apart into the equivalent sequence of conditionals. */
4286 static tree
4287 shortcut_cond_expr (tree expr)
4289 tree pred = TREE_OPERAND (expr, 0);
4290 tree then_ = TREE_OPERAND (expr, 1);
4291 tree else_ = TREE_OPERAND (expr, 2);
4292 tree true_label, false_label, end_label, t;
4293 tree *true_label_p;
4294 tree *false_label_p;
4295 bool emit_end, emit_false, jump_over_else;
4296 bool then_se = then_ && TREE_SIDE_EFFECTS (then_);
4297 bool else_se = else_ && TREE_SIDE_EFFECTS (else_);
4299 /* First do simple transformations. */
4300 if (!else_se)
4302 /* If there is no 'else', turn
4303 if (a && b) then c
4304 into
4305 if (a) if (b) then c. */
4306 while (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
4308 /* Keep the original source location on the first 'if'. */
4309 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
4310 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
4311 /* Set the source location of the && on the second 'if'. */
4312 if (rexpr_has_location (pred))
4313 SET_EXPR_LOCATION (expr, rexpr_location (pred));
4314 then_ = shortcut_cond_expr (expr);
4315 then_se = then_ && TREE_SIDE_EFFECTS (then_);
4316 pred = TREE_OPERAND (pred, 0);
4317 expr = build3 (COND_EXPR, void_type_node, pred, then_, NULL_TREE);
4318 SET_EXPR_LOCATION (expr, locus);
4322 if (!then_se)
4324 /* If there is no 'then', turn
4325 if (a || b); else d
4326 into
4327 if (a); else if (b); else d. */
4328 while (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
4330 /* Keep the original source location on the first 'if'. */
4331 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
4332 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
4333 /* Set the source location of the || on the second 'if'. */
4334 if (rexpr_has_location (pred))
4335 SET_EXPR_LOCATION (expr, rexpr_location (pred));
4336 else_ = shortcut_cond_expr (expr);
4337 else_se = else_ && TREE_SIDE_EFFECTS (else_);
4338 pred = TREE_OPERAND (pred, 0);
4339 expr = build3 (COND_EXPR, void_type_node, pred, NULL_TREE, else_);
4340 SET_EXPR_LOCATION (expr, locus);
4344 /* If we're done, great. */
4345 if (TREE_CODE (pred) != TRUTH_ANDIF_EXPR
4346 && TREE_CODE (pred) != TRUTH_ORIF_EXPR)
4347 return expr;
4349 /* Otherwise we need to mess with gotos. Change
4350 if (a) c; else d;
4352 if (a); else goto no;
4353 c; goto end;
4354 no: d; end:
4355 and recursively gimplify the condition. */
4357 true_label = false_label = end_label = NULL_TREE;
4359 /* If our arms just jump somewhere, hijack those labels so we don't
4360 generate jumps to jumps. */
4362 if (tree then_goto = find_goto_label (then_))
4364 true_label = GOTO_DESTINATION (then_goto);
4365 then_ = NULL;
4366 then_se = false;
4369 if (tree else_goto = find_goto_label (else_))
4371 false_label = GOTO_DESTINATION (else_goto);
4372 else_ = NULL;
4373 else_se = false;
4376 /* If we aren't hijacking a label for the 'then' branch, it falls through. */
4377 if (true_label)
4378 true_label_p = &true_label;
4379 else
4380 true_label_p = NULL;
4382 /* The 'else' branch also needs a label if it contains interesting code. */
4383 if (false_label || else_se)
4384 false_label_p = &false_label;
4385 else
4386 false_label_p = NULL;
4388 /* If there was nothing else in our arms, just forward the label(s). */
4389 if (!then_se && !else_se)
4390 return shortcut_cond_r (pred, true_label_p, false_label_p,
4391 EXPR_LOC_OR_LOC (expr, input_location));
4393 /* If our last subexpression already has a terminal label, reuse it. */
4394 if (else_se)
4395 t = expr_last (else_);
4396 else if (then_se)
4397 t = expr_last (then_);
4398 else
4399 t = NULL;
4400 if (t && TREE_CODE (t) == LABEL_EXPR)
4401 end_label = LABEL_EXPR_LABEL (t);
4403 /* If we don't care about jumping to the 'else' branch, jump to the end
4404 if the condition is false. */
4405 if (!false_label_p)
4406 false_label_p = &end_label;
4408 /* We only want to emit these labels if we aren't hijacking them. */
4409 emit_end = (end_label == NULL_TREE);
4410 emit_false = (false_label == NULL_TREE);
4412 /* We only emit the jump over the else clause if we have to--if the
4413 then clause may fall through. Otherwise we can wind up with a
4414 useless jump and a useless label at the end of gimplified code,
4415 which will cause us to think that this conditional as a whole
4416 falls through even if it doesn't. If we then inline a function
4417 which ends with such a condition, that can cause us to issue an
4418 inappropriate warning about control reaching the end of a
4419 non-void function. */
4420 jump_over_else = block_may_fallthru (then_);
4422 pred = shortcut_cond_r (pred, true_label_p, false_label_p,
4423 EXPR_LOC_OR_LOC (expr, input_location));
4425 expr = NULL;
4426 append_to_statement_list (pred, &expr);
4428 append_to_statement_list (then_, &expr);
4429 if (else_se)
4431 if (jump_over_else)
4433 tree last = expr_last (expr);
4434 t = build_and_jump (&end_label);
4435 if (rexpr_has_location (last))
4436 SET_EXPR_LOCATION (t, rexpr_location (last));
4437 append_to_statement_list (t, &expr);
4439 if (emit_false)
4441 t = build1 (LABEL_EXPR, void_type_node, false_label);
4442 append_to_statement_list (t, &expr);
4444 append_to_statement_list (else_, &expr);
4446 if (emit_end && end_label)
4448 t = build1 (LABEL_EXPR, void_type_node, end_label);
4449 append_to_statement_list (t, &expr);
4452 return expr;
4455 /* EXPR is used in a boolean context; make sure it has BOOLEAN_TYPE. */
4457 tree
4458 gimple_boolify (tree expr)
4460 tree type = TREE_TYPE (expr);
4461 location_t loc = EXPR_LOCATION (expr);
4463 if (TREE_CODE (expr) == NE_EXPR
4464 && TREE_CODE (TREE_OPERAND (expr, 0)) == CALL_EXPR
4465 && integer_zerop (TREE_OPERAND (expr, 1)))
4467 tree call = TREE_OPERAND (expr, 0);
4468 tree fn = get_callee_fndecl (call);
4470 /* For __builtin_expect ((long) (x), y) recurse into x as well
4471 if x is truth_value_p. */
4472 if (fn
4473 && fndecl_built_in_p (fn, BUILT_IN_EXPECT)
4474 && call_expr_nargs (call) == 2)
4476 tree arg = CALL_EXPR_ARG (call, 0);
4477 if (arg)
4479 if (TREE_CODE (arg) == NOP_EXPR
4480 && TREE_TYPE (arg) == TREE_TYPE (call))
4481 arg = TREE_OPERAND (arg, 0);
4482 if (truth_value_p (TREE_CODE (arg)))
4484 arg = gimple_boolify (arg);
4485 CALL_EXPR_ARG (call, 0)
4486 = fold_convert_loc (loc, TREE_TYPE (call), arg);
4492 switch (TREE_CODE (expr))
4494 case TRUTH_AND_EXPR:
4495 case TRUTH_OR_EXPR:
4496 case TRUTH_XOR_EXPR:
4497 case TRUTH_ANDIF_EXPR:
4498 case TRUTH_ORIF_EXPR:
4499 /* Also boolify the arguments of truth exprs. */
4500 TREE_OPERAND (expr, 1) = gimple_boolify (TREE_OPERAND (expr, 1));
4501 /* FALLTHRU */
4503 case TRUTH_NOT_EXPR:
4504 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
4506 /* These expressions always produce boolean results. */
4507 if (TREE_CODE (type) != BOOLEAN_TYPE)
4508 TREE_TYPE (expr) = boolean_type_node;
4509 return expr;
4511 case ANNOTATE_EXPR:
4512 switch ((enum annot_expr_kind) TREE_INT_CST_LOW (TREE_OPERAND (expr, 1)))
4514 case annot_expr_ivdep_kind:
4515 case annot_expr_unroll_kind:
4516 case annot_expr_no_vector_kind:
4517 case annot_expr_vector_kind:
4518 case annot_expr_parallel_kind:
4519 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
4520 if (TREE_CODE (type) != BOOLEAN_TYPE)
4521 TREE_TYPE (expr) = boolean_type_node;
4522 return expr;
4523 default:
4524 gcc_unreachable ();
4527 default:
4528 if (COMPARISON_CLASS_P (expr))
4530 /* These expressions always produce boolean results. */
4531 if (TREE_CODE (type) != BOOLEAN_TYPE)
4532 TREE_TYPE (expr) = boolean_type_node;
4533 return expr;
4535 /* Other expressions that get here must have boolean values, but
4536 might need to be converted to the appropriate mode. */
4537 if (TREE_CODE (type) == BOOLEAN_TYPE)
4538 return expr;
4539 return fold_convert_loc (loc, boolean_type_node, expr);
4543 /* Given a conditional expression *EXPR_P without side effects, gimplify
4544 its operands. New statements are inserted to PRE_P. */
4546 static enum gimplify_status
4547 gimplify_pure_cond_expr (tree *expr_p, gimple_seq *pre_p)
4549 tree expr = *expr_p, cond;
4550 enum gimplify_status ret, tret;
4551 enum tree_code code;
4553 cond = gimple_boolify (COND_EXPR_COND (expr));
4555 /* We need to handle && and || specially, as their gimplification
4556 creates pure cond_expr, thus leading to an infinite cycle otherwise. */
4557 code = TREE_CODE (cond);
4558 if (code == TRUTH_ANDIF_EXPR)
4559 TREE_SET_CODE (cond, TRUTH_AND_EXPR);
4560 else if (code == TRUTH_ORIF_EXPR)
4561 TREE_SET_CODE (cond, TRUTH_OR_EXPR);
4562 ret = gimplify_expr (&cond, pre_p, NULL, is_gimple_val, fb_rvalue);
4563 COND_EXPR_COND (*expr_p) = cond;
4565 tret = gimplify_expr (&COND_EXPR_THEN (expr), pre_p, NULL,
4566 is_gimple_val, fb_rvalue);
4567 ret = MIN (ret, tret);
4568 tret = gimplify_expr (&COND_EXPR_ELSE (expr), pre_p, NULL,
4569 is_gimple_val, fb_rvalue);
4571 return MIN (ret, tret);
4574 /* Return true if evaluating EXPR could trap.
4575 EXPR is GENERIC, while tree_could_trap_p can be called
4576 only on GIMPLE. */
4578 bool
4579 generic_expr_could_trap_p (tree expr)
4581 unsigned i, n;
4583 if (!expr || is_gimple_val (expr))
4584 return false;
4586 if (!EXPR_P (expr) || tree_could_trap_p (expr))
4587 return true;
4589 n = TREE_OPERAND_LENGTH (expr);
4590 for (i = 0; i < n; i++)
4591 if (generic_expr_could_trap_p (TREE_OPERAND (expr, i)))
4592 return true;
4594 return false;
4597 /* Convert the conditional expression pointed to by EXPR_P '(p) ? a : b;'
4598 into
4600 if (p) if (p)
4601 t1 = a; a;
4602 else or else
4603 t1 = b; b;
4606 The second form is used when *EXPR_P is of type void.
4608 PRE_P points to the list where side effects that must happen before
4609 *EXPR_P should be stored. */
4611 static enum gimplify_status
4612 gimplify_cond_expr (tree *expr_p, gimple_seq *pre_p, fallback_t fallback)
4614 tree expr = *expr_p;
4615 tree type = TREE_TYPE (expr);
4616 location_t loc = EXPR_LOCATION (expr);
4617 tree tmp, arm1, arm2;
4618 enum gimplify_status ret;
4619 tree label_true, label_false, label_cont;
4620 bool have_then_clause_p, have_else_clause_p;
4621 gcond *cond_stmt;
4622 enum tree_code pred_code;
4623 gimple_seq seq = NULL;
4625 /* If this COND_EXPR has a value, copy the values into a temporary within
4626 the arms. */
4627 if (!VOID_TYPE_P (type))
4629 tree then_ = TREE_OPERAND (expr, 1), else_ = TREE_OPERAND (expr, 2);
4630 tree result;
4632 /* If either an rvalue is ok or we do not require an lvalue, create the
4633 temporary. But we cannot do that if the type is addressable. */
4634 if (((fallback & fb_rvalue) || !(fallback & fb_lvalue))
4635 && !TREE_ADDRESSABLE (type))
4637 if (gimplify_ctxp->allow_rhs_cond_expr
4638 /* If either branch has side effects or could trap, it can't be
4639 evaluated unconditionally. */
4640 && !TREE_SIDE_EFFECTS (then_)
4641 && !generic_expr_could_trap_p (then_)
4642 && !TREE_SIDE_EFFECTS (else_)
4643 && !generic_expr_could_trap_p (else_))
4644 return gimplify_pure_cond_expr (expr_p, pre_p);
4646 tmp = create_tmp_var (type, "iftmp");
4647 result = tmp;
4650 /* Otherwise, only create and copy references to the values. */
4651 else
4653 type = build_pointer_type (type);
4655 if (!VOID_TYPE_P (TREE_TYPE (then_)))
4656 then_ = build_fold_addr_expr_loc (loc, then_);
4658 if (!VOID_TYPE_P (TREE_TYPE (else_)))
4659 else_ = build_fold_addr_expr_loc (loc, else_);
4661 expr
4662 = build3 (COND_EXPR, type, TREE_OPERAND (expr, 0), then_, else_);
4664 tmp = create_tmp_var (type, "iftmp");
4665 result = build_simple_mem_ref_loc (loc, tmp);
4668 /* Build the new then clause, `tmp = then_;'. But don't build the
4669 assignment if the value is void; in C++ it can be if it's a throw. */
4670 if (!VOID_TYPE_P (TREE_TYPE (then_)))
4671 TREE_OPERAND (expr, 1) = build2 (INIT_EXPR, type, tmp, then_);
4673 /* Similarly, build the new else clause, `tmp = else_;'. */
4674 if (!VOID_TYPE_P (TREE_TYPE (else_)))
4675 TREE_OPERAND (expr, 2) = build2 (INIT_EXPR, type, tmp, else_);
4677 TREE_TYPE (expr) = void_type_node;
4678 recalculate_side_effects (expr);
4680 /* Move the COND_EXPR to the prequeue. */
4681 gimplify_stmt (&expr, pre_p);
4683 *expr_p = result;
4684 return GS_ALL_DONE;
4687 /* Remove any COMPOUND_EXPR so the following cases will be caught. */
4688 STRIP_TYPE_NOPS (TREE_OPERAND (expr, 0));
4689 if (TREE_CODE (TREE_OPERAND (expr, 0)) == COMPOUND_EXPR)
4690 gimplify_compound_expr (&TREE_OPERAND (expr, 0), pre_p, true);
4692 /* Make sure the condition has BOOLEAN_TYPE. */
4693 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
4695 /* Break apart && and || conditions. */
4696 if (TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ANDIF_EXPR
4697 || TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ORIF_EXPR)
4699 expr = shortcut_cond_expr (expr);
4701 if (expr != *expr_p)
4703 *expr_p = expr;
4705 /* We can't rely on gimplify_expr to re-gimplify the expanded
4706 form properly, as cleanups might cause the target labels to be
4707 wrapped in a TRY_FINALLY_EXPR. To prevent that, we need to
4708 set up a conditional context. */
4709 gimple_push_condition ();
4710 gimplify_stmt (expr_p, &seq);
4711 gimple_pop_condition (pre_p);
4712 gimple_seq_add_seq (pre_p, seq);
4714 return GS_ALL_DONE;
4718 /* Now do the normal gimplification. */
4720 /* Gimplify condition. */
4721 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, NULL,
4722 is_gimple_condexpr_for_cond, fb_rvalue);
4723 if (ret == GS_ERROR)
4724 return GS_ERROR;
4725 gcc_assert (TREE_OPERAND (expr, 0) != NULL_TREE);
4727 gimple_push_condition ();
4729 have_then_clause_p = have_else_clause_p = false;
4730 label_true = find_goto_label (TREE_OPERAND (expr, 1));
4731 if (label_true
4732 && DECL_CONTEXT (GOTO_DESTINATION (label_true)) == current_function_decl
4733 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
4734 have different locations, otherwise we end up with incorrect
4735 location information on the branches. */
4736 && (optimize
4737 || !EXPR_HAS_LOCATION (expr)
4738 || !rexpr_has_location (label_true)
4739 || EXPR_LOCATION (expr) == rexpr_location (label_true)))
4741 have_then_clause_p = true;
4742 label_true = GOTO_DESTINATION (label_true);
4744 else
4745 label_true = create_artificial_label (UNKNOWN_LOCATION);
4746 label_false = find_goto_label (TREE_OPERAND (expr, 2));
4747 if (label_false
4748 && DECL_CONTEXT (GOTO_DESTINATION (label_false)) == current_function_decl
4749 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
4750 have different locations, otherwise we end up with incorrect
4751 location information on the branches. */
4752 && (optimize
4753 || !EXPR_HAS_LOCATION (expr)
4754 || !rexpr_has_location (label_false)
4755 || EXPR_LOCATION (expr) == rexpr_location (label_false)))
4757 have_else_clause_p = true;
4758 label_false = GOTO_DESTINATION (label_false);
4760 else
4761 label_false = create_artificial_label (UNKNOWN_LOCATION);
4763 gimple_cond_get_ops_from_tree (COND_EXPR_COND (expr), &pred_code, &arm1,
4764 &arm2);
4765 cond_stmt = gimple_build_cond (pred_code, arm1, arm2, label_true,
4766 label_false);
4767 gimple_set_location (cond_stmt, EXPR_LOCATION (expr));
4768 copy_warning (cond_stmt, COND_EXPR_COND (expr));
4769 gimplify_seq_add_stmt (&seq, cond_stmt);
4770 gimple_stmt_iterator gsi = gsi_last (seq);
4771 maybe_fold_stmt (&gsi);
4773 label_cont = NULL_TREE;
4774 if (!have_then_clause_p)
4776 /* For if (...) {} else { code; } put label_true after
4777 the else block. */
4778 if (TREE_OPERAND (expr, 1) == NULL_TREE
4779 && !have_else_clause_p
4780 && TREE_OPERAND (expr, 2) != NULL_TREE)
4782 /* For if (0) {} else { code; } tell -Wimplicit-fallthrough
4783 handling that label_cont == label_true can be only reached
4784 through fallthrough from { code; }. */
4785 if (integer_zerop (COND_EXPR_COND (expr)))
4786 UNUSED_LABEL_P (label_true) = 1;
4787 label_cont = label_true;
4789 else
4791 bool then_side_effects
4792 = (TREE_OPERAND (expr, 1)
4793 && TREE_SIDE_EFFECTS (TREE_OPERAND (expr, 1)));
4794 gimplify_seq_add_stmt (&seq, gimple_build_label (label_true));
4795 have_then_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 1), &seq);
4796 /* For if (...) { code; } else {} or
4797 if (...) { code; } else goto label; or
4798 if (...) { code; return; } else { ... }
4799 label_cont isn't needed. */
4800 if (!have_else_clause_p
4801 && TREE_OPERAND (expr, 2) != NULL_TREE
4802 && gimple_seq_may_fallthru (seq))
4804 gimple *g;
4805 label_cont = create_artificial_label (UNKNOWN_LOCATION);
4807 /* For if (0) { non-side-effect-code } else { code }
4808 tell -Wimplicit-fallthrough handling that label_cont can
4809 be only reached through fallthrough from { code }. */
4810 if (integer_zerop (COND_EXPR_COND (expr)))
4812 UNUSED_LABEL_P (label_true) = 1;
4813 if (!then_side_effects)
4814 UNUSED_LABEL_P (label_cont) = 1;
4817 g = gimple_build_goto (label_cont);
4819 /* GIMPLE_COND's are very low level; they have embedded
4820 gotos. This particular embedded goto should not be marked
4821 with the location of the original COND_EXPR, as it would
4822 correspond to the COND_EXPR's condition, not the ELSE or the
4823 THEN arms. To avoid marking it with the wrong location, flag
4824 it as "no location". */
4825 gimple_set_do_not_emit_location (g);
4827 gimplify_seq_add_stmt (&seq, g);
4831 if (!have_else_clause_p)
4833 /* For if (1) { code } or if (1) { code } else { non-side-effect-code }
4834 tell -Wimplicit-fallthrough handling that label_false can be only
4835 reached through fallthrough from { code }. */
4836 if (integer_nonzerop (COND_EXPR_COND (expr))
4837 && (TREE_OPERAND (expr, 2) == NULL_TREE
4838 || !TREE_SIDE_EFFECTS (TREE_OPERAND (expr, 2))))
4839 UNUSED_LABEL_P (label_false) = 1;
4840 gimplify_seq_add_stmt (&seq, gimple_build_label (label_false));
4841 have_else_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 2), &seq);
4843 if (label_cont)
4844 gimplify_seq_add_stmt (&seq, gimple_build_label (label_cont));
4846 gimple_pop_condition (pre_p);
4847 gimple_seq_add_seq (pre_p, seq);
4849 if (ret == GS_ERROR)
4850 ; /* Do nothing. */
4851 else if (have_then_clause_p || have_else_clause_p)
4852 ret = GS_ALL_DONE;
4853 else
4855 /* Both arms are empty; replace the COND_EXPR with its predicate. */
4856 expr = TREE_OPERAND (expr, 0);
4857 gimplify_stmt (&expr, pre_p);
4860 *expr_p = NULL;
4861 return ret;
4864 /* Prepare the node pointed to by EXPR_P, an is_gimple_addressable expression,
4865 to be marked addressable.
4867 We cannot rely on such an expression being directly markable if a temporary
4868 has been created by the gimplification. In this case, we create another
4869 temporary and initialize it with a copy, which will become a store after we
4870 mark it addressable. This can happen if the front-end passed us something
4871 that it could not mark addressable yet, like a Fortran pass-by-reference
4872 parameter (int) floatvar. */
4874 static void
4875 prepare_gimple_addressable (tree *expr_p, gimple_seq *seq_p)
4877 while (handled_component_p (*expr_p))
4878 expr_p = &TREE_OPERAND (*expr_p, 0);
4880 /* Do not allow an SSA name as the temporary. */
4881 if (is_gimple_reg (*expr_p))
4882 *expr_p = internal_get_tmp_var (*expr_p, seq_p, NULL, false, false, true);
4885 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
4886 a call to __builtin_memcpy. */
4888 static enum gimplify_status
4889 gimplify_modify_expr_to_memcpy (tree *expr_p, tree size, bool want_value,
4890 gimple_seq *seq_p)
4892 tree t, to, to_ptr, from, from_ptr;
4893 gcall *gs;
4894 location_t loc = EXPR_LOCATION (*expr_p);
4896 to = TREE_OPERAND (*expr_p, 0);
4897 from = TREE_OPERAND (*expr_p, 1);
4898 gcc_assert (ADDR_SPACE_GENERIC_P (TYPE_ADDR_SPACE (TREE_TYPE (to)))
4899 && ADDR_SPACE_GENERIC_P (TYPE_ADDR_SPACE (TREE_TYPE (from))));
4901 /* Mark the RHS addressable. Beware that it may not be possible to do so
4902 directly if a temporary has been created by the gimplification. */
4903 prepare_gimple_addressable (&from, seq_p);
4905 mark_addressable (from);
4906 from_ptr = build_fold_addr_expr_loc (loc, from);
4907 gimplify_arg (&from_ptr, seq_p, loc);
4909 mark_addressable (to);
4910 to_ptr = build_fold_addr_expr_loc (loc, to);
4911 gimplify_arg (&to_ptr, seq_p, loc);
4913 t = builtin_decl_implicit (BUILT_IN_MEMCPY);
4915 gs = gimple_build_call (t, 3, to_ptr, from_ptr, size);
4916 gimple_call_set_alloca_for_var (gs, true);
4918 if (want_value)
4920 /* tmp = memcpy() */
4921 t = create_tmp_var (TREE_TYPE (to_ptr));
4922 gimple_call_set_lhs (gs, t);
4923 gimplify_seq_add_stmt (seq_p, gs);
4925 *expr_p = build_simple_mem_ref (t);
4926 return GS_ALL_DONE;
4929 gimplify_seq_add_stmt (seq_p, gs);
4930 *expr_p = NULL;
4931 return GS_ALL_DONE;
4934 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
4935 a call to __builtin_memset. In this case we know that the RHS is
4936 a CONSTRUCTOR with an empty element list. */
4938 static enum gimplify_status
4939 gimplify_modify_expr_to_memset (tree *expr_p, tree size, bool want_value,
4940 gimple_seq *seq_p)
4942 tree t, from, to, to_ptr;
4943 gcall *gs;
4944 location_t loc = EXPR_LOCATION (*expr_p);
4946 /* Assert our assumptions, to abort instead of producing wrong code
4947 silently if they are not met. Beware that the RHS CONSTRUCTOR might
4948 not be immediately exposed. */
4949 from = TREE_OPERAND (*expr_p, 1);
4950 if (TREE_CODE (from) == WITH_SIZE_EXPR)
4951 from = TREE_OPERAND (from, 0);
4953 gcc_assert (TREE_CODE (from) == CONSTRUCTOR
4954 && vec_safe_is_empty (CONSTRUCTOR_ELTS (from)));
4956 /* Now proceed. */
4957 to = TREE_OPERAND (*expr_p, 0);
4958 gcc_assert (ADDR_SPACE_GENERIC_P (TYPE_ADDR_SPACE (TREE_TYPE (to))));
4960 to_ptr = build_fold_addr_expr_loc (loc, to);
4961 gimplify_arg (&to_ptr, seq_p, loc);
4962 t = builtin_decl_implicit (BUILT_IN_MEMSET);
4964 gs = gimple_build_call (t, 3, to_ptr, integer_zero_node, size);
4966 if (want_value)
4968 /* tmp = memset() */
4969 t = create_tmp_var (TREE_TYPE (to_ptr));
4970 gimple_call_set_lhs (gs, t);
4971 gimplify_seq_add_stmt (seq_p, gs);
4973 *expr_p = build1 (INDIRECT_REF, TREE_TYPE (to), t);
4974 return GS_ALL_DONE;
4977 gimplify_seq_add_stmt (seq_p, gs);
4978 *expr_p = NULL;
4979 return GS_ALL_DONE;
4982 /* A subroutine of gimplify_init_ctor_preeval. Called via walk_tree,
4983 determine, cautiously, if a CONSTRUCTOR overlaps the lhs of an
4984 assignment. Return non-null if we detect a potential overlap. */
4986 struct gimplify_init_ctor_preeval_data
4988 /* The base decl of the lhs object. May be NULL, in which case we
4989 have to assume the lhs is indirect. */
4990 tree lhs_base_decl;
4992 /* The alias set of the lhs object. */
4993 alias_set_type lhs_alias_set;
4996 static tree
4997 gimplify_init_ctor_preeval_1 (tree *tp, int *walk_subtrees, void *xdata)
4999 struct gimplify_init_ctor_preeval_data *data
5000 = (struct gimplify_init_ctor_preeval_data *) xdata;
5001 tree t = *tp;
5003 /* If we find the base object, obviously we have overlap. */
5004 if (data->lhs_base_decl == t)
5005 return t;
5007 /* If the constructor component is indirect, determine if we have a
5008 potential overlap with the lhs. The only bits of information we
5009 have to go on at this point are addressability and alias sets. */
5010 if ((INDIRECT_REF_P (t)
5011 || TREE_CODE (t) == MEM_REF)
5012 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
5013 && alias_sets_conflict_p (data->lhs_alias_set, get_alias_set (t)))
5014 return t;
5016 /* If the constructor component is a call, determine if it can hide a
5017 potential overlap with the lhs through an INDIRECT_REF like above.
5018 ??? Ugh - this is completely broken. In fact this whole analysis
5019 doesn't look conservative. */
5020 if (TREE_CODE (t) == CALL_EXPR)
5022 tree type, fntype = TREE_TYPE (TREE_TYPE (CALL_EXPR_FN (t)));
5024 for (type = TYPE_ARG_TYPES (fntype); type; type = TREE_CHAIN (type))
5025 if (POINTER_TYPE_P (TREE_VALUE (type))
5026 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
5027 && alias_sets_conflict_p (data->lhs_alias_set,
5028 get_alias_set
5029 (TREE_TYPE (TREE_VALUE (type)))))
5030 return t;
5033 if (IS_TYPE_OR_DECL_P (t))
5034 *walk_subtrees = 0;
5035 return NULL;
5038 /* A subroutine of gimplify_init_constructor. Pre-evaluate EXPR,
5039 force values that overlap with the lhs (as described by *DATA)
5040 into temporaries. */
5042 static void
5043 gimplify_init_ctor_preeval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
5044 struct gimplify_init_ctor_preeval_data *data)
5046 enum gimplify_status one;
5048 /* If the value is constant, then there's nothing to pre-evaluate. */
5049 if (TREE_CONSTANT (*expr_p))
5051 /* Ensure it does not have side effects, it might contain a reference to
5052 the object we're initializing. */
5053 gcc_assert (!TREE_SIDE_EFFECTS (*expr_p));
5054 return;
5057 /* If the type has non-trivial constructors, we can't pre-evaluate. */
5058 if (TREE_ADDRESSABLE (TREE_TYPE (*expr_p)))
5059 return;
5061 /* Recurse for nested constructors. */
5062 if (TREE_CODE (*expr_p) == CONSTRUCTOR)
5064 unsigned HOST_WIDE_INT ix;
5065 constructor_elt *ce;
5066 vec<constructor_elt, va_gc> *v = CONSTRUCTOR_ELTS (*expr_p);
5068 FOR_EACH_VEC_SAFE_ELT (v, ix, ce)
5069 gimplify_init_ctor_preeval (&ce->value, pre_p, post_p, data);
5071 return;
5074 /* If this is a variable sized type, we must remember the size. */
5075 maybe_with_size_expr (expr_p);
5077 /* Gimplify the constructor element to something appropriate for the rhs
5078 of a MODIFY_EXPR. Given that we know the LHS is an aggregate, we know
5079 the gimplifier will consider this a store to memory. Doing this
5080 gimplification now means that we won't have to deal with complicated
5081 language-specific trees, nor trees like SAVE_EXPR that can induce
5082 exponential search behavior. */
5083 one = gimplify_expr (expr_p, pre_p, post_p, is_gimple_mem_rhs, fb_rvalue);
5084 if (one == GS_ERROR)
5086 *expr_p = NULL;
5087 return;
5090 /* If we gimplified to a bare decl, we can be sure that it doesn't overlap
5091 with the lhs, since "a = { .x=a }" doesn't make sense. This will
5092 always be true for all scalars, since is_gimple_mem_rhs insists on a
5093 temporary variable for them. */
5094 if (DECL_P (*expr_p))
5095 return;
5097 /* If this is of variable size, we have no choice but to assume it doesn't
5098 overlap since we can't make a temporary for it. */
5099 if (TREE_CODE (TYPE_SIZE (TREE_TYPE (*expr_p))) != INTEGER_CST)
5100 return;
5102 /* Otherwise, we must search for overlap ... */
5103 if (!walk_tree (expr_p, gimplify_init_ctor_preeval_1, data, NULL))
5104 return;
5106 /* ... and if found, force the value into a temporary. */
5107 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
5110 /* A subroutine of gimplify_init_ctor_eval. Create a loop for
5111 a RANGE_EXPR in a CONSTRUCTOR for an array.
5113 var = lower;
5114 loop_entry:
5115 object[var] = value;
5116 if (var == upper)
5117 goto loop_exit;
5118 var = var + 1;
5119 goto loop_entry;
5120 loop_exit:
5122 We increment var _after_ the loop exit check because we might otherwise
5123 fail if upper == TYPE_MAX_VALUE (type for upper).
5125 Note that we never have to deal with SAVE_EXPRs here, because this has
5126 already been taken care of for us, in gimplify_init_ctor_preeval(). */
5128 static void gimplify_init_ctor_eval (tree, vec<constructor_elt, va_gc> *,
5129 gimple_seq *, bool);
5131 static void
5132 gimplify_init_ctor_eval_range (tree object, tree lower, tree upper,
5133 tree value, tree array_elt_type,
5134 gimple_seq *pre_p, bool cleared)
5136 tree loop_entry_label, loop_exit_label, fall_thru_label;
5137 tree var, var_type, cref, tmp;
5139 loop_entry_label = create_artificial_label (UNKNOWN_LOCATION);
5140 loop_exit_label = create_artificial_label (UNKNOWN_LOCATION);
5141 fall_thru_label = create_artificial_label (UNKNOWN_LOCATION);
5143 /* Create and initialize the index variable. */
5144 var_type = TREE_TYPE (upper);
5145 var = create_tmp_var (var_type);
5146 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, lower));
5148 /* Add the loop entry label. */
5149 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_entry_label));
5151 /* Build the reference. */
5152 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
5153 var, NULL_TREE, NULL_TREE);
5155 /* If we are a constructor, just call gimplify_init_ctor_eval to do
5156 the store. Otherwise just assign value to the reference. */
5158 if (TREE_CODE (value) == CONSTRUCTOR)
5159 /* NB we might have to call ourself recursively through
5160 gimplify_init_ctor_eval if the value is a constructor. */
5161 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
5162 pre_p, cleared);
5163 else
5165 if (gimplify_expr (&value, pre_p, NULL, is_gimple_val, fb_rvalue)
5166 != GS_ERROR)
5167 gimplify_seq_add_stmt (pre_p, gimple_build_assign (cref, value));
5170 /* We exit the loop when the index var is equal to the upper bound. */
5171 gimplify_seq_add_stmt (pre_p,
5172 gimple_build_cond (EQ_EXPR, var, upper,
5173 loop_exit_label, fall_thru_label));
5175 gimplify_seq_add_stmt (pre_p, gimple_build_label (fall_thru_label));
5177 /* Otherwise, increment the index var... */
5178 tmp = build2 (PLUS_EXPR, var_type, var,
5179 fold_convert (var_type, integer_one_node));
5180 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, tmp));
5182 /* ...and jump back to the loop entry. */
5183 gimplify_seq_add_stmt (pre_p, gimple_build_goto (loop_entry_label));
5185 /* Add the loop exit label. */
5186 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_exit_label));
5189 /* A subroutine of gimplify_init_constructor. Generate individual
5190 MODIFY_EXPRs for a CONSTRUCTOR. OBJECT is the LHS against which the
5191 assignments should happen. ELTS is the CONSTRUCTOR_ELTS of the
5192 CONSTRUCTOR. CLEARED is true if the entire LHS object has been
5193 zeroed first. */
5195 static void
5196 gimplify_init_ctor_eval (tree object, vec<constructor_elt, va_gc> *elts,
5197 gimple_seq *pre_p, bool cleared)
5199 tree array_elt_type = NULL;
5200 unsigned HOST_WIDE_INT ix;
5201 tree purpose, value;
5203 if (TREE_CODE (TREE_TYPE (object)) == ARRAY_TYPE)
5204 array_elt_type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (object)));
5206 FOR_EACH_CONSTRUCTOR_ELT (elts, ix, purpose, value)
5208 tree cref;
5210 /* NULL values are created above for gimplification errors. */
5211 if (value == NULL)
5212 continue;
5214 if (cleared && initializer_zerop (value))
5215 continue;
5217 /* ??? Here's to hoping the front end fills in all of the indices,
5218 so we don't have to figure out what's missing ourselves. */
5219 gcc_assert (purpose);
5221 /* Skip zero-sized fields, unless value has side-effects. This can
5222 happen with calls to functions returning a empty type, which
5223 we shouldn't discard. As a number of downstream passes don't
5224 expect sets of empty type fields, we rely on the gimplification of
5225 the MODIFY_EXPR we make below to drop the assignment statement. */
5226 if (!TREE_SIDE_EFFECTS (value)
5227 && TREE_CODE (purpose) == FIELD_DECL
5228 && is_empty_type (TREE_TYPE (purpose)))
5229 continue;
5231 /* If we have a RANGE_EXPR, we have to build a loop to assign the
5232 whole range. */
5233 if (TREE_CODE (purpose) == RANGE_EXPR)
5235 tree lower = TREE_OPERAND (purpose, 0);
5236 tree upper = TREE_OPERAND (purpose, 1);
5238 /* If the lower bound is equal to upper, just treat it as if
5239 upper was the index. */
5240 if (simple_cst_equal (lower, upper))
5241 purpose = upper;
5242 else
5244 gimplify_init_ctor_eval_range (object, lower, upper, value,
5245 array_elt_type, pre_p, cleared);
5246 continue;
5250 if (array_elt_type)
5252 /* Do not use bitsizetype for ARRAY_REF indices. */
5253 if (TYPE_DOMAIN (TREE_TYPE (object)))
5254 purpose
5255 = fold_convert (TREE_TYPE (TYPE_DOMAIN (TREE_TYPE (object))),
5256 purpose);
5257 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
5258 purpose, NULL_TREE, NULL_TREE);
5260 else
5262 gcc_assert (TREE_CODE (purpose) == FIELD_DECL);
5263 cref = build3 (COMPONENT_REF, TREE_TYPE (purpose),
5264 unshare_expr (object), purpose, NULL_TREE);
5267 if (TREE_CODE (value) == CONSTRUCTOR
5268 && TREE_CODE (TREE_TYPE (value)) != VECTOR_TYPE)
5269 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
5270 pre_p, cleared);
5271 else
5273 tree init = build2 (INIT_EXPR, TREE_TYPE (cref), cref, value);
5274 gimplify_and_add (init, pre_p);
5275 ggc_free (init);
5280 /* Return the appropriate RHS predicate for this LHS. */
5282 gimple_predicate
5283 rhs_predicate_for (tree lhs)
5285 if (is_gimple_reg (lhs))
5286 return is_gimple_reg_rhs_or_call;
5287 else
5288 return is_gimple_mem_rhs_or_call;
5291 /* Return the initial guess for an appropriate RHS predicate for this LHS,
5292 before the LHS has been gimplified. */
5294 static gimple_predicate
5295 initial_rhs_predicate_for (tree lhs)
5297 if (is_gimple_reg_type (TREE_TYPE (lhs)))
5298 return is_gimple_reg_rhs_or_call;
5299 else
5300 return is_gimple_mem_rhs_or_call;
5303 /* Gimplify a C99 compound literal expression. This just means adding
5304 the DECL_EXPR before the current statement and using its anonymous
5305 decl instead. */
5307 static enum gimplify_status
5308 gimplify_compound_literal_expr (tree *expr_p, gimple_seq *pre_p,
5309 bool (*gimple_test_f) (tree),
5310 fallback_t fallback)
5312 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (*expr_p);
5313 tree decl = DECL_EXPR_DECL (decl_s);
5314 tree init = DECL_INITIAL (decl);
5315 /* Mark the decl as addressable if the compound literal
5316 expression is addressable now, otherwise it is marked too late
5317 after we gimplify the initialization expression. */
5318 if (TREE_ADDRESSABLE (*expr_p))
5319 TREE_ADDRESSABLE (decl) = 1;
5320 /* Otherwise, if we don't need an lvalue and have a literal directly
5321 substitute it. Check if it matches the gimple predicate, as
5322 otherwise we'd generate a new temporary, and we can as well just
5323 use the decl we already have. */
5324 else if (!TREE_ADDRESSABLE (decl)
5325 && !TREE_THIS_VOLATILE (decl)
5326 && init
5327 && (fallback & fb_lvalue) == 0
5328 && gimple_test_f (init))
5330 *expr_p = init;
5331 return GS_OK;
5334 /* If the decl is not addressable, then it is being used in some
5335 expression or on the right hand side of a statement, and it can
5336 be put into a readonly data section. */
5337 if (!TREE_ADDRESSABLE (decl) && (fallback & fb_lvalue) == 0)
5338 TREE_READONLY (decl) = 1;
5340 /* This decl isn't mentioned in the enclosing block, so add it to the
5341 list of temps. FIXME it seems a bit of a kludge to say that
5342 anonymous artificial vars aren't pushed, but everything else is. */
5343 if (DECL_NAME (decl) == NULL_TREE && !DECL_SEEN_IN_BIND_EXPR_P (decl))
5344 gimple_add_tmp_var (decl);
5346 gimplify_and_add (decl_s, pre_p);
5347 *expr_p = decl;
5348 return GS_OK;
5351 /* Optimize embedded COMPOUND_LITERAL_EXPRs within a CONSTRUCTOR,
5352 return a new CONSTRUCTOR if something changed. */
5354 static tree
5355 optimize_compound_literals_in_ctor (tree orig_ctor)
5357 tree ctor = orig_ctor;
5358 vec<constructor_elt, va_gc> *elts = CONSTRUCTOR_ELTS (ctor);
5359 unsigned int idx, num = vec_safe_length (elts);
5361 for (idx = 0; idx < num; idx++)
5363 tree value = (*elts)[idx].value;
5364 tree newval = value;
5365 if (TREE_CODE (value) == CONSTRUCTOR)
5366 newval = optimize_compound_literals_in_ctor (value);
5367 else if (TREE_CODE (value) == COMPOUND_LITERAL_EXPR)
5369 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (value);
5370 tree decl = DECL_EXPR_DECL (decl_s);
5371 tree init = DECL_INITIAL (decl);
5373 if (!TREE_ADDRESSABLE (value)
5374 && !TREE_ADDRESSABLE (decl)
5375 && init
5376 && TREE_CODE (init) == CONSTRUCTOR)
5377 newval = optimize_compound_literals_in_ctor (init);
5379 if (newval == value)
5380 continue;
5382 if (ctor == orig_ctor)
5384 ctor = copy_node (orig_ctor);
5385 CONSTRUCTOR_ELTS (ctor) = vec_safe_copy (elts);
5386 elts = CONSTRUCTOR_ELTS (ctor);
5388 (*elts)[idx].value = newval;
5390 return ctor;
5393 /* A subroutine of gimplify_modify_expr. Break out elements of a
5394 CONSTRUCTOR used as an initializer into separate MODIFY_EXPRs.
5396 Note that we still need to clear any elements that don't have explicit
5397 initializers, so if not all elements are initialized we keep the
5398 original MODIFY_EXPR, we just remove all of the constructor elements.
5400 If NOTIFY_TEMP_CREATION is true, do not gimplify, just return
5401 GS_ERROR if we would have to create a temporary when gimplifying
5402 this constructor. Otherwise, return GS_OK.
5404 If NOTIFY_TEMP_CREATION is false, just do the gimplification. */
5406 static enum gimplify_status
5407 gimplify_init_constructor (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
5408 bool want_value, bool notify_temp_creation)
5410 tree object, ctor, type;
5411 enum gimplify_status ret;
5412 vec<constructor_elt, va_gc> *elts;
5413 bool cleared = false;
5414 bool is_empty_ctor = false;
5415 bool is_init_expr = (TREE_CODE (*expr_p) == INIT_EXPR);
5417 gcc_assert (TREE_CODE (TREE_OPERAND (*expr_p, 1)) == CONSTRUCTOR);
5419 if (!notify_temp_creation)
5421 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
5422 is_gimple_lvalue, fb_lvalue);
5423 if (ret == GS_ERROR)
5424 return ret;
5427 object = TREE_OPERAND (*expr_p, 0);
5428 ctor = TREE_OPERAND (*expr_p, 1)
5429 = optimize_compound_literals_in_ctor (TREE_OPERAND (*expr_p, 1));
5430 type = TREE_TYPE (ctor);
5431 elts = CONSTRUCTOR_ELTS (ctor);
5432 ret = GS_ALL_DONE;
5434 switch (TREE_CODE (type))
5436 case RECORD_TYPE:
5437 case UNION_TYPE:
5438 case QUAL_UNION_TYPE:
5439 case ARRAY_TYPE:
5441 /* Use readonly data for initializers of this or smaller size
5442 regardless of the num_nonzero_elements / num_unique_nonzero_elements
5443 ratio. */
5444 const HOST_WIDE_INT min_unique_size = 64;
5445 /* If num_nonzero_elements / num_unique_nonzero_elements ratio
5446 is smaller than this, use readonly data. */
5447 const int unique_nonzero_ratio = 8;
5448 /* True if a single access of the object must be ensured. This is the
5449 case if the target is volatile, the type is non-addressable and more
5450 than one field need to be assigned. */
5451 const bool ensure_single_access
5452 = TREE_THIS_VOLATILE (object)
5453 && !TREE_ADDRESSABLE (type)
5454 && vec_safe_length (elts) > 1;
5455 struct gimplify_init_ctor_preeval_data preeval_data;
5456 HOST_WIDE_INT num_ctor_elements, num_nonzero_elements;
5457 HOST_WIDE_INT num_unique_nonzero_elements;
5458 bool complete_p, valid_const_initializer;
5460 /* Aggregate types must lower constructors to initialization of
5461 individual elements. The exception is that a CONSTRUCTOR node
5462 with no elements indicates zero-initialization of the whole. */
5463 if (vec_safe_is_empty (elts))
5465 if (notify_temp_creation)
5466 return GS_OK;
5468 /* The var will be initialized and so appear on lhs of
5469 assignment, it can't be TREE_READONLY anymore. */
5470 if (VAR_P (object))
5471 TREE_READONLY (object) = 0;
5473 is_empty_ctor = true;
5474 break;
5477 /* Fetch information about the constructor to direct later processing.
5478 We might want to make static versions of it in various cases, and
5479 can only do so if it known to be a valid constant initializer. */
5480 valid_const_initializer
5481 = categorize_ctor_elements (ctor, &num_nonzero_elements,
5482 &num_unique_nonzero_elements,
5483 &num_ctor_elements, &complete_p);
5485 /* If a const aggregate variable is being initialized, then it
5486 should never be a lose to promote the variable to be static. */
5487 if (valid_const_initializer
5488 && num_nonzero_elements > 1
5489 && TREE_READONLY (object)
5490 && VAR_P (object)
5491 && !DECL_REGISTER (object)
5492 && (flag_merge_constants >= 2 || !TREE_ADDRESSABLE (object)
5493 || DECL_MERGEABLE (object))
5494 /* For ctors that have many repeated nonzero elements
5495 represented through RANGE_EXPRs, prefer initializing
5496 those through runtime loops over copies of large amounts
5497 of data from readonly data section. */
5498 && (num_unique_nonzero_elements
5499 > num_nonzero_elements / unique_nonzero_ratio
5500 || ((unsigned HOST_WIDE_INT) int_size_in_bytes (type)
5501 <= (unsigned HOST_WIDE_INT) min_unique_size)))
5503 if (notify_temp_creation)
5504 return GS_ERROR;
5506 DECL_INITIAL (object) = ctor;
5507 TREE_STATIC (object) = 1;
5508 if (!DECL_NAME (object))
5509 DECL_NAME (object) = create_tmp_var_name ("C");
5510 walk_tree (&DECL_INITIAL (object), force_labels_r, NULL, NULL);
5512 /* ??? C++ doesn't automatically append a .<number> to the
5513 assembler name, and even when it does, it looks at FE private
5514 data structures to figure out what that number should be,
5515 which are not set for this variable. I suppose this is
5516 important for local statics for inline functions, which aren't
5517 "local" in the object file sense. So in order to get a unique
5518 TU-local symbol, we must invoke the lhd version now. */
5519 lhd_set_decl_assembler_name (object);
5521 *expr_p = NULL_TREE;
5522 break;
5525 /* The var will be initialized and so appear on lhs of
5526 assignment, it can't be TREE_READONLY anymore. */
5527 if (VAR_P (object) && !notify_temp_creation)
5528 TREE_READONLY (object) = 0;
5530 /* If there are "lots" of initialized elements, even discounting
5531 those that are not address constants (and thus *must* be
5532 computed at runtime), then partition the constructor into
5533 constant and non-constant parts. Block copy the constant
5534 parts in, then generate code for the non-constant parts. */
5535 /* TODO. There's code in cp/typeck.cc to do this. */
5537 if (int_size_in_bytes (TREE_TYPE (ctor)) < 0)
5538 /* store_constructor will ignore the clearing of variable-sized
5539 objects. Initializers for such objects must explicitly set
5540 every field that needs to be set. */
5541 cleared = false;
5542 else if (!complete_p)
5543 /* If the constructor isn't complete, clear the whole object
5544 beforehand, unless CONSTRUCTOR_NO_CLEARING is set on it.
5546 ??? This ought not to be needed. For any element not present
5547 in the initializer, we should simply set them to zero. Except
5548 we'd need to *find* the elements that are not present, and that
5549 requires trickery to avoid quadratic compile-time behavior in
5550 large cases or excessive memory use in small cases. */
5551 cleared = !CONSTRUCTOR_NO_CLEARING (ctor);
5552 else if (num_ctor_elements - num_nonzero_elements
5553 > CLEAR_RATIO (optimize_function_for_speed_p (cfun))
5554 && num_nonzero_elements < num_ctor_elements / 4)
5555 /* If there are "lots" of zeros, it's more efficient to clear
5556 the memory and then set the nonzero elements. */
5557 cleared = true;
5558 else if (ensure_single_access && num_nonzero_elements == 0)
5559 /* If a single access to the target must be ensured and all elements
5560 are zero, then it's optimal to clear whatever their number. */
5561 cleared = true;
5562 else
5563 cleared = false;
5565 /* If there are "lots" of initialized elements, and all of them
5566 are valid address constants, then the entire initializer can
5567 be dropped to memory, and then memcpy'd out. Don't do this
5568 for sparse arrays, though, as it's more efficient to follow
5569 the standard CONSTRUCTOR behavior of memset followed by
5570 individual element initialization. Also don't do this for small
5571 all-zero initializers (which aren't big enough to merit
5572 clearing), and don't try to make bitwise copies of
5573 TREE_ADDRESSABLE types. */
5574 if (valid_const_initializer
5575 && complete_p
5576 && !(cleared || num_nonzero_elements == 0)
5577 && !TREE_ADDRESSABLE (type))
5579 HOST_WIDE_INT size = int_size_in_bytes (type);
5580 unsigned int align;
5582 /* ??? We can still get unbounded array types, at least
5583 from the C++ front end. This seems wrong, but attempt
5584 to work around it for now. */
5585 if (size < 0)
5587 size = int_size_in_bytes (TREE_TYPE (object));
5588 if (size >= 0)
5589 TREE_TYPE (ctor) = type = TREE_TYPE (object);
5592 /* Find the maximum alignment we can assume for the object. */
5593 /* ??? Make use of DECL_OFFSET_ALIGN. */
5594 if (DECL_P (object))
5595 align = DECL_ALIGN (object);
5596 else
5597 align = TYPE_ALIGN (type);
5599 /* Do a block move either if the size is so small as to make
5600 each individual move a sub-unit move on average, or if it
5601 is so large as to make individual moves inefficient. */
5602 if (size > 0
5603 && num_nonzero_elements > 1
5604 /* For ctors that have many repeated nonzero elements
5605 represented through RANGE_EXPRs, prefer initializing
5606 those through runtime loops over copies of large amounts
5607 of data from readonly data section. */
5608 && (num_unique_nonzero_elements
5609 > num_nonzero_elements / unique_nonzero_ratio
5610 || size <= min_unique_size)
5611 && (size < num_nonzero_elements
5612 || !can_move_by_pieces (size, align)))
5614 if (notify_temp_creation)
5615 return GS_ERROR;
5617 walk_tree (&ctor, force_labels_r, NULL, NULL);
5618 ctor = tree_output_constant_def (ctor);
5619 if (!useless_type_conversion_p (type, TREE_TYPE (ctor)))
5620 ctor = build1 (VIEW_CONVERT_EXPR, type, ctor);
5621 TREE_OPERAND (*expr_p, 1) = ctor;
5623 /* This is no longer an assignment of a CONSTRUCTOR, but
5624 we still may have processing to do on the LHS. So
5625 pretend we didn't do anything here to let that happen. */
5626 return GS_UNHANDLED;
5630 /* If a single access to the target must be ensured and there are
5631 nonzero elements or the zero elements are not assigned en masse,
5632 initialize the target from a temporary. */
5633 if (ensure_single_access && (num_nonzero_elements > 0 || !cleared))
5635 if (notify_temp_creation)
5636 return GS_ERROR;
5638 tree temp = create_tmp_var (TYPE_MAIN_VARIANT (type));
5639 TREE_OPERAND (*expr_p, 0) = temp;
5640 *expr_p = build2 (COMPOUND_EXPR, TREE_TYPE (*expr_p),
5641 *expr_p,
5642 build2 (MODIFY_EXPR, void_type_node,
5643 object, temp));
5644 return GS_OK;
5647 if (notify_temp_creation)
5648 return GS_OK;
5650 /* If there are nonzero elements and if needed, pre-evaluate to capture
5651 elements overlapping with the lhs into temporaries. We must do this
5652 before clearing to fetch the values before they are zeroed-out. */
5653 if (num_nonzero_elements > 0 && TREE_CODE (*expr_p) != INIT_EXPR)
5655 preeval_data.lhs_base_decl = get_base_address (object);
5656 if (!DECL_P (preeval_data.lhs_base_decl))
5657 preeval_data.lhs_base_decl = NULL;
5658 preeval_data.lhs_alias_set = get_alias_set (object);
5660 gimplify_init_ctor_preeval (&TREE_OPERAND (*expr_p, 1),
5661 pre_p, post_p, &preeval_data);
5664 bool ctor_has_side_effects_p
5665 = TREE_SIDE_EFFECTS (TREE_OPERAND (*expr_p, 1));
5667 if (cleared)
5669 /* Zap the CONSTRUCTOR element list, which simplifies this case.
5670 Note that we still have to gimplify, in order to handle the
5671 case of variable sized types. Avoid shared tree structures. */
5672 CONSTRUCTOR_ELTS (ctor) = NULL;
5673 TREE_SIDE_EFFECTS (ctor) = 0;
5674 object = unshare_expr (object);
5675 gimplify_stmt (expr_p, pre_p);
5678 /* If we have not block cleared the object, or if there are nonzero
5679 elements in the constructor, or if the constructor has side effects,
5680 add assignments to the individual scalar fields of the object. */
5681 if (!cleared
5682 || num_nonzero_elements > 0
5683 || ctor_has_side_effects_p)
5684 gimplify_init_ctor_eval (object, elts, pre_p, cleared);
5686 *expr_p = NULL_TREE;
5688 break;
5690 case COMPLEX_TYPE:
5692 tree r, i;
5694 if (notify_temp_creation)
5695 return GS_OK;
5697 /* Extract the real and imaginary parts out of the ctor. */
5698 gcc_assert (elts->length () == 2);
5699 r = (*elts)[0].value;
5700 i = (*elts)[1].value;
5701 if (r == NULL || i == NULL)
5703 tree zero = build_zero_cst (TREE_TYPE (type));
5704 if (r == NULL)
5705 r = zero;
5706 if (i == NULL)
5707 i = zero;
5710 /* Complex types have either COMPLEX_CST or COMPLEX_EXPR to
5711 represent creation of a complex value. */
5712 if (TREE_CONSTANT (r) && TREE_CONSTANT (i))
5714 ctor = build_complex (type, r, i);
5715 TREE_OPERAND (*expr_p, 1) = ctor;
5717 else
5719 ctor = build2 (COMPLEX_EXPR, type, r, i);
5720 TREE_OPERAND (*expr_p, 1) = ctor;
5721 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 1),
5722 pre_p,
5723 post_p,
5724 rhs_predicate_for (TREE_OPERAND (*expr_p, 0)),
5725 fb_rvalue);
5728 break;
5730 case VECTOR_TYPE:
5732 unsigned HOST_WIDE_INT ix;
5733 constructor_elt *ce;
5735 if (notify_temp_creation)
5736 return GS_OK;
5738 /* Vector types use CONSTRUCTOR all the way through gimple
5739 compilation as a general initializer. */
5740 FOR_EACH_VEC_SAFE_ELT (elts, ix, ce)
5742 enum gimplify_status tret;
5743 tret = gimplify_expr (&ce->value, pre_p, post_p, is_gimple_val,
5744 fb_rvalue);
5745 if (tret == GS_ERROR)
5746 ret = GS_ERROR;
5747 else if (TREE_STATIC (ctor)
5748 && !initializer_constant_valid_p (ce->value,
5749 TREE_TYPE (ce->value)))
5750 TREE_STATIC (ctor) = 0;
5752 recompute_constructor_flags (ctor);
5754 /* Go ahead and simplify constant constructors to VECTOR_CST. */
5755 if (TREE_CONSTANT (ctor))
5757 bool constant_p = true;
5758 tree value;
5760 /* Even when ctor is constant, it might contain non-*_CST
5761 elements, such as addresses or trapping values like
5762 1.0/0.0 - 1.0/0.0. Such expressions don't belong
5763 in VECTOR_CST nodes. */
5764 FOR_EACH_CONSTRUCTOR_VALUE (elts, ix, value)
5765 if (!CONSTANT_CLASS_P (value))
5767 constant_p = false;
5768 break;
5771 if (constant_p)
5773 TREE_OPERAND (*expr_p, 1) = build_vector_from_ctor (type, elts);
5774 break;
5778 if (!is_gimple_reg (TREE_OPERAND (*expr_p, 0)))
5779 TREE_OPERAND (*expr_p, 1) = get_formal_tmp_var (ctor, pre_p);
5781 break;
5783 default:
5784 /* So how did we get a CONSTRUCTOR for a scalar type? */
5785 gcc_unreachable ();
5788 if (ret == GS_ERROR)
5789 return GS_ERROR;
5790 /* If we have gimplified both sides of the initializer but have
5791 not emitted an assignment, do so now. */
5792 if (*expr_p
5793 /* If the type is an empty type, we don't need to emit the
5794 assignment. */
5795 && !is_empty_type (TREE_TYPE (TREE_OPERAND (*expr_p, 0))))
5797 tree lhs = TREE_OPERAND (*expr_p, 0);
5798 tree rhs = TREE_OPERAND (*expr_p, 1);
5799 if (want_value && object == lhs)
5800 lhs = unshare_expr (lhs);
5801 gassign *init = gimple_build_assign (lhs, rhs);
5802 gimplify_seq_add_stmt (pre_p, init);
5804 if (want_value)
5806 *expr_p = object;
5807 ret = GS_OK;
5809 else
5811 *expr_p = NULL;
5812 ret = GS_ALL_DONE;
5815 /* If the user requests to initialize automatic variables, we
5816 should initialize paddings inside the variable. Add a call to
5817 __builtin_clear_pading (&object, 0, for_auto_init = true) to
5818 initialize paddings of object always to zero regardless of
5819 INIT_TYPE. Note, we will not insert this call if the aggregate
5820 variable has be completely cleared already or it's initialized
5821 with an empty constructor. We cannot insert this call if the
5822 variable is a gimple register since __builtin_clear_padding will take
5823 the address of the variable. As a result, if a long double/_Complex long
5824 double variable will be spilled into stack later, its padding cannot
5825 be cleared with __builtin_clear_padding. We should clear its padding
5826 when it is spilled into memory. */
5827 if (is_init_expr
5828 && !is_gimple_reg (object)
5829 && clear_padding_type_may_have_padding_p (type)
5830 && ((AGGREGATE_TYPE_P (type) && !cleared && !is_empty_ctor)
5831 || !AGGREGATE_TYPE_P (type))
5832 && is_var_need_auto_init (object))
5833 gimple_add_padding_init_for_auto_var (object, false, pre_p);
5835 return ret;
5838 /* Given a pointer value OP0, return a simplified version of an
5839 indirection through OP0, or NULL_TREE if no simplification is
5840 possible. This may only be applied to a rhs of an expression.
5841 Note that the resulting type may be different from the type pointed
5842 to in the sense that it is still compatible from the langhooks
5843 point of view. */
5845 static tree
5846 gimple_fold_indirect_ref_rhs (tree t)
5848 return gimple_fold_indirect_ref (t);
5851 /* Subroutine of gimplify_modify_expr to do simplifications of
5852 MODIFY_EXPRs based on the code of the RHS. We loop for as long as
5853 something changes. */
5855 static enum gimplify_status
5856 gimplify_modify_expr_rhs (tree *expr_p, tree *from_p, tree *to_p,
5857 gimple_seq *pre_p, gimple_seq *post_p,
5858 bool want_value)
5860 enum gimplify_status ret = GS_UNHANDLED;
5861 bool changed;
5865 changed = false;
5866 switch (TREE_CODE (*from_p))
5868 case VAR_DECL:
5869 /* If we're assigning from a read-only variable initialized with
5870 a constructor and not volatile, do the direct assignment from
5871 the constructor, but only if the target is not volatile either
5872 since this latter assignment might end up being done on a per
5873 field basis. However, if the target is volatile and the type
5874 is aggregate and non-addressable, gimplify_init_constructor
5875 knows that it needs to ensure a single access to the target
5876 and it will return GS_OK only in this case. */
5877 if (TREE_READONLY (*from_p)
5878 && DECL_INITIAL (*from_p)
5879 && TREE_CODE (DECL_INITIAL (*from_p)) == CONSTRUCTOR
5880 && !TREE_THIS_VOLATILE (*from_p)
5881 && (!TREE_THIS_VOLATILE (*to_p)
5882 || (AGGREGATE_TYPE_P (TREE_TYPE (*to_p))
5883 && !TREE_ADDRESSABLE (TREE_TYPE (*to_p)))))
5885 tree old_from = *from_p;
5886 enum gimplify_status subret;
5888 /* Move the constructor into the RHS. */
5889 *from_p = unshare_expr (DECL_INITIAL (*from_p));
5891 /* Let's see if gimplify_init_constructor will need to put
5892 it in memory. */
5893 subret = gimplify_init_constructor (expr_p, NULL, NULL,
5894 false, true);
5895 if (subret == GS_ERROR)
5897 /* If so, revert the change. */
5898 *from_p = old_from;
5900 else
5902 ret = GS_OK;
5903 changed = true;
5906 break;
5907 case INDIRECT_REF:
5908 if (!TREE_ADDRESSABLE (TREE_TYPE (*from_p)))
5909 /* If we have code like
5911 *(const A*)(A*)&x
5913 where the type of "x" is a (possibly cv-qualified variant
5914 of "A"), treat the entire expression as identical to "x".
5915 This kind of code arises in C++ when an object is bound
5916 to a const reference, and if "x" is a TARGET_EXPR we want
5917 to take advantage of the optimization below. But not if
5918 the type is TREE_ADDRESSABLE; then C++17 says that the
5919 TARGET_EXPR needs to be a temporary. */
5920 if (tree t
5921 = gimple_fold_indirect_ref_rhs (TREE_OPERAND (*from_p, 0)))
5923 bool volatile_p = TREE_THIS_VOLATILE (*from_p);
5924 if (TREE_THIS_VOLATILE (t) != volatile_p)
5926 if (DECL_P (t))
5927 t = build_simple_mem_ref_loc (EXPR_LOCATION (*from_p),
5928 build_fold_addr_expr (t));
5929 if (REFERENCE_CLASS_P (t))
5930 TREE_THIS_VOLATILE (t) = volatile_p;
5932 *from_p = t;
5933 ret = GS_OK;
5934 changed = true;
5936 break;
5938 case TARGET_EXPR:
5940 /* If we are initializing something from a TARGET_EXPR, strip the
5941 TARGET_EXPR and initialize it directly, if possible. This can't
5942 be done if the initializer is void, since that implies that the
5943 temporary is set in some non-trivial way.
5945 ??? What about code that pulls out the temp and uses it
5946 elsewhere? I think that such code never uses the TARGET_EXPR as
5947 an initializer. If I'm wrong, we'll die because the temp won't
5948 have any RTL. In that case, I guess we'll need to replace
5949 references somehow. */
5950 tree init = TARGET_EXPR_INITIAL (*from_p);
5952 if (init
5953 && (TREE_CODE (*expr_p) != MODIFY_EXPR
5954 || !TARGET_EXPR_NO_ELIDE (*from_p))
5955 && !VOID_TYPE_P (TREE_TYPE (init)))
5957 *from_p = init;
5958 ret = GS_OK;
5959 changed = true;
5962 break;
5964 case COMPOUND_EXPR:
5965 /* Remove any COMPOUND_EXPR in the RHS so the following cases will be
5966 caught. */
5967 gimplify_compound_expr (from_p, pre_p, true);
5968 ret = GS_OK;
5969 changed = true;
5970 break;
5972 case CONSTRUCTOR:
5973 /* If we already made some changes, let the front end have a
5974 crack at this before we break it down. */
5975 if (ret != GS_UNHANDLED)
5976 break;
5978 /* If we're initializing from a CONSTRUCTOR, break this into
5979 individual MODIFY_EXPRs. */
5980 ret = gimplify_init_constructor (expr_p, pre_p, post_p, want_value,
5981 false);
5982 return ret;
5984 case COND_EXPR:
5985 /* If we're assigning to a non-register type, push the assignment
5986 down into the branches. This is mandatory for ADDRESSABLE types,
5987 since we cannot generate temporaries for such, but it saves a
5988 copy in other cases as well. */
5989 if (!is_gimple_reg_type (TREE_TYPE (*from_p)))
5991 /* This code should mirror the code in gimplify_cond_expr. */
5992 enum tree_code code = TREE_CODE (*expr_p);
5993 tree cond = *from_p;
5994 tree result = *to_p;
5996 ret = gimplify_expr (&result, pre_p, post_p,
5997 is_gimple_lvalue, fb_lvalue);
5998 if (ret != GS_ERROR)
5999 ret = GS_OK;
6001 /* If we are going to write RESULT more than once, clear
6002 TREE_READONLY flag, otherwise we might incorrectly promote
6003 the variable to static const and initialize it at compile
6004 time in one of the branches. */
6005 if (VAR_P (result)
6006 && TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node
6007 && TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
6008 TREE_READONLY (result) = 0;
6009 if (TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node)
6010 TREE_OPERAND (cond, 1)
6011 = build2 (code, void_type_node, result,
6012 TREE_OPERAND (cond, 1));
6013 if (TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
6014 TREE_OPERAND (cond, 2)
6015 = build2 (code, void_type_node, unshare_expr (result),
6016 TREE_OPERAND (cond, 2));
6018 TREE_TYPE (cond) = void_type_node;
6019 recalculate_side_effects (cond);
6021 if (want_value)
6023 gimplify_and_add (cond, pre_p);
6024 *expr_p = unshare_expr (result);
6026 else
6027 *expr_p = cond;
6028 return ret;
6030 break;
6032 case CALL_EXPR:
6033 /* For calls that return in memory, give *to_p as the CALL_EXPR's
6034 return slot so that we don't generate a temporary. */
6035 if (!CALL_EXPR_RETURN_SLOT_OPT (*from_p)
6036 && aggregate_value_p (*from_p, *from_p))
6038 bool use_target;
6040 if (!(rhs_predicate_for (*to_p))(*from_p))
6041 /* If we need a temporary, *to_p isn't accurate. */
6042 use_target = false;
6043 /* It's OK to use the return slot directly unless it's an NRV. */
6044 else if (TREE_CODE (*to_p) == RESULT_DECL
6045 && DECL_NAME (*to_p) == NULL_TREE
6046 && needs_to_live_in_memory (*to_p))
6047 use_target = true;
6048 else if (is_gimple_reg_type (TREE_TYPE (*to_p))
6049 || (DECL_P (*to_p) && DECL_REGISTER (*to_p)))
6050 /* Don't force regs into memory. */
6051 use_target = false;
6052 else if (TREE_CODE (*expr_p) == INIT_EXPR)
6053 /* It's OK to use the target directly if it's being
6054 initialized. */
6055 use_target = true;
6056 else if (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (*to_p)))
6057 != INTEGER_CST)
6058 /* Always use the target and thus RSO for variable-sized types.
6059 GIMPLE cannot deal with a variable-sized assignment
6060 embedded in a call statement. */
6061 use_target = true;
6062 else if (TREE_CODE (*to_p) != SSA_NAME
6063 && (!is_gimple_variable (*to_p)
6064 || needs_to_live_in_memory (*to_p)))
6065 /* Don't use the original target if it's already addressable;
6066 if its address escapes, and the called function uses the
6067 NRV optimization, a conforming program could see *to_p
6068 change before the called function returns; see c++/19317.
6069 When optimizing, the return_slot pass marks more functions
6070 as safe after we have escape info. */
6071 use_target = false;
6072 else
6073 use_target = true;
6075 if (use_target)
6077 CALL_EXPR_RETURN_SLOT_OPT (*from_p) = 1;
6078 mark_addressable (*to_p);
6081 break;
6083 case WITH_SIZE_EXPR:
6084 /* Likewise for calls that return an aggregate of non-constant size,
6085 since we would not be able to generate a temporary at all. */
6086 if (TREE_CODE (TREE_OPERAND (*from_p, 0)) == CALL_EXPR)
6088 *from_p = TREE_OPERAND (*from_p, 0);
6089 /* We don't change ret in this case because the
6090 WITH_SIZE_EXPR might have been added in
6091 gimplify_modify_expr, so returning GS_OK would lead to an
6092 infinite loop. */
6093 changed = true;
6095 break;
6097 /* If we're initializing from a container, push the initialization
6098 inside it. */
6099 case CLEANUP_POINT_EXPR:
6100 case BIND_EXPR:
6101 case STATEMENT_LIST:
6103 tree wrap = *from_p;
6104 tree t;
6106 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_min_lval,
6107 fb_lvalue);
6108 if (ret != GS_ERROR)
6109 ret = GS_OK;
6111 t = voidify_wrapper_expr (wrap, *expr_p);
6112 gcc_assert (t == *expr_p);
6114 if (want_value)
6116 gimplify_and_add (wrap, pre_p);
6117 *expr_p = unshare_expr (*to_p);
6119 else
6120 *expr_p = wrap;
6121 return GS_OK;
6124 case NOP_EXPR:
6125 /* Pull out compound literal expressions from a NOP_EXPR.
6126 Those are created in the C FE to drop qualifiers during
6127 lvalue conversion. */
6128 if ((TREE_CODE (TREE_OPERAND (*from_p, 0)) == COMPOUND_LITERAL_EXPR)
6129 && tree_ssa_useless_type_conversion (*from_p))
6131 *from_p = TREE_OPERAND (*from_p, 0);
6132 ret = GS_OK;
6133 changed = true;
6135 break;
6137 case COMPOUND_LITERAL_EXPR:
6139 tree complit = TREE_OPERAND (*expr_p, 1);
6140 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (complit);
6141 tree decl = DECL_EXPR_DECL (decl_s);
6142 tree init = DECL_INITIAL (decl);
6144 /* struct T x = (struct T) { 0, 1, 2 } can be optimized
6145 into struct T x = { 0, 1, 2 } if the address of the
6146 compound literal has never been taken. */
6147 if (!TREE_ADDRESSABLE (complit)
6148 && !TREE_ADDRESSABLE (decl)
6149 && init)
6151 *expr_p = copy_node (*expr_p);
6152 TREE_OPERAND (*expr_p, 1) = init;
6153 return GS_OK;
6157 default:
6158 break;
6161 while (changed);
6163 return ret;
6167 /* Return true if T looks like a valid GIMPLE statement. */
6169 static bool
6170 is_gimple_stmt (tree t)
6172 const enum tree_code code = TREE_CODE (t);
6174 switch (code)
6176 case NOP_EXPR:
6177 /* The only valid NOP_EXPR is the empty statement. */
6178 return IS_EMPTY_STMT (t);
6180 case BIND_EXPR:
6181 case COND_EXPR:
6182 /* These are only valid if they're void. */
6183 return TREE_TYPE (t) == NULL || VOID_TYPE_P (TREE_TYPE (t));
6185 case SWITCH_EXPR:
6186 case GOTO_EXPR:
6187 case RETURN_EXPR:
6188 case LABEL_EXPR:
6189 case CASE_LABEL_EXPR:
6190 case TRY_CATCH_EXPR:
6191 case TRY_FINALLY_EXPR:
6192 case EH_FILTER_EXPR:
6193 case CATCH_EXPR:
6194 case ASM_EXPR:
6195 case STATEMENT_LIST:
6196 case OACC_PARALLEL:
6197 case OACC_KERNELS:
6198 case OACC_SERIAL:
6199 case OACC_DATA:
6200 case OACC_HOST_DATA:
6201 case OACC_DECLARE:
6202 case OACC_UPDATE:
6203 case OACC_ENTER_DATA:
6204 case OACC_EXIT_DATA:
6205 case OACC_CACHE:
6206 case OMP_PARALLEL:
6207 case OMP_FOR:
6208 case OMP_SIMD:
6209 case OMP_DISTRIBUTE:
6210 case OMP_LOOP:
6211 case OACC_LOOP:
6212 case OMP_SCAN:
6213 case OMP_SCOPE:
6214 case OMP_SECTIONS:
6215 case OMP_SECTION:
6216 case OMP_STRUCTURED_BLOCK:
6217 case OMP_SINGLE:
6218 case OMP_MASTER:
6219 case OMP_MASKED:
6220 case OMP_TASKGROUP:
6221 case OMP_ORDERED:
6222 case OMP_CRITICAL:
6223 case OMP_TASK:
6224 case OMP_TARGET:
6225 case OMP_TARGET_DATA:
6226 case OMP_TARGET_UPDATE:
6227 case OMP_TARGET_ENTER_DATA:
6228 case OMP_TARGET_EXIT_DATA:
6229 case OMP_TASKLOOP:
6230 case OMP_TEAMS:
6231 /* These are always void. */
6232 return true;
6234 case CALL_EXPR:
6235 case MODIFY_EXPR:
6236 case PREDICT_EXPR:
6237 /* These are valid regardless of their type. */
6238 return true;
6240 default:
6241 return false;
6246 /* Promote partial stores to COMPLEX variables to total stores. *EXPR_P is
6247 a MODIFY_EXPR with a lhs of a REAL/IMAGPART_EXPR of a gimple register.
6249 IMPORTANT NOTE: This promotion is performed by introducing a load of the
6250 other, unmodified part of the complex object just before the total store.
6251 As a consequence, if the object is still uninitialized, an undefined value
6252 will be loaded into a register, which may result in a spurious exception
6253 if the register is floating-point and the value happens to be a signaling
6254 NaN for example. Then the fully-fledged complex operations lowering pass
6255 followed by a DCE pass are necessary in order to fix things up. */
6257 static enum gimplify_status
6258 gimplify_modify_expr_complex_part (tree *expr_p, gimple_seq *pre_p,
6259 bool want_value)
6261 enum tree_code code, ocode;
6262 tree lhs, rhs, new_rhs, other, realpart, imagpart;
6264 lhs = TREE_OPERAND (*expr_p, 0);
6265 rhs = TREE_OPERAND (*expr_p, 1);
6266 code = TREE_CODE (lhs);
6267 lhs = TREE_OPERAND (lhs, 0);
6269 ocode = code == REALPART_EXPR ? IMAGPART_EXPR : REALPART_EXPR;
6270 other = build1 (ocode, TREE_TYPE (rhs), lhs);
6271 suppress_warning (other);
6272 other = get_formal_tmp_var (other, pre_p);
6274 realpart = code == REALPART_EXPR ? rhs : other;
6275 imagpart = code == REALPART_EXPR ? other : rhs;
6277 if (TREE_CONSTANT (realpart) && TREE_CONSTANT (imagpart))
6278 new_rhs = build_complex (TREE_TYPE (lhs), realpart, imagpart);
6279 else
6280 new_rhs = build2 (COMPLEX_EXPR, TREE_TYPE (lhs), realpart, imagpart);
6282 gimplify_seq_add_stmt (pre_p, gimple_build_assign (lhs, new_rhs));
6283 *expr_p = (want_value) ? rhs : NULL_TREE;
6285 return GS_ALL_DONE;
6288 /* Gimplify the MODIFY_EXPR node pointed to by EXPR_P.
6290 modify_expr
6291 : varname '=' rhs
6292 | '*' ID '=' rhs
6294 PRE_P points to the list where side effects that must happen before
6295 *EXPR_P should be stored.
6297 POST_P points to the list where side effects that must happen after
6298 *EXPR_P should be stored.
6300 WANT_VALUE is nonzero iff we want to use the value of this expression
6301 in another expression. */
6303 static enum gimplify_status
6304 gimplify_modify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
6305 bool want_value)
6307 tree *from_p = &TREE_OPERAND (*expr_p, 1);
6308 tree *to_p = &TREE_OPERAND (*expr_p, 0);
6309 enum gimplify_status ret = GS_UNHANDLED;
6310 gimple *assign;
6311 location_t loc = EXPR_LOCATION (*expr_p);
6312 gimple_stmt_iterator gsi;
6314 if (error_operand_p (*from_p) || error_operand_p (*to_p))
6315 return GS_ERROR;
6317 gcc_assert (TREE_CODE (*expr_p) == MODIFY_EXPR
6318 || TREE_CODE (*expr_p) == INIT_EXPR);
6320 /* Trying to simplify a clobber using normal logic doesn't work,
6321 so handle it here. */
6322 if (TREE_CLOBBER_P (*from_p))
6324 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
6325 if (ret == GS_ERROR)
6326 return ret;
6327 gcc_assert (!want_value);
6328 if (!VAR_P (*to_p) && TREE_CODE (*to_p) != MEM_REF)
6330 tree addr = get_initialized_tmp_var (build_fold_addr_expr (*to_p),
6331 pre_p, post_p);
6332 *to_p = build_simple_mem_ref_loc (EXPR_LOCATION (*to_p), addr);
6334 gimplify_seq_add_stmt (pre_p, gimple_build_assign (*to_p, *from_p));
6335 *expr_p = NULL;
6336 return GS_ALL_DONE;
6339 /* Convert initialization from an empty variable-size CONSTRUCTOR to
6340 memset. */
6341 if (TREE_TYPE (*from_p) != error_mark_node
6342 && TYPE_SIZE_UNIT (TREE_TYPE (*from_p))
6343 && !poly_int_tree_p (TYPE_SIZE_UNIT (TREE_TYPE (*from_p)))
6344 && TREE_CODE (*from_p) == CONSTRUCTOR
6345 && CONSTRUCTOR_NELTS (*from_p) == 0)
6347 maybe_with_size_expr (from_p);
6348 gcc_assert (TREE_CODE (*from_p) == WITH_SIZE_EXPR);
6349 return gimplify_modify_expr_to_memset (expr_p,
6350 TREE_OPERAND (*from_p, 1),
6351 want_value, pre_p);
6354 /* Insert pointer conversions required by the middle-end that are not
6355 required by the frontend. This fixes middle-end type checking for
6356 for example gcc.dg/redecl-6.c. */
6357 if (POINTER_TYPE_P (TREE_TYPE (*to_p)))
6359 STRIP_USELESS_TYPE_CONVERSION (*from_p);
6360 if (!useless_type_conversion_p (TREE_TYPE (*to_p), TREE_TYPE (*from_p)))
6361 *from_p = fold_convert_loc (loc, TREE_TYPE (*to_p), *from_p);
6364 /* See if any simplifications can be done based on what the RHS is. */
6365 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
6366 want_value);
6367 if (ret != GS_UNHANDLED)
6368 return ret;
6370 /* For empty types only gimplify the left hand side and right hand
6371 side as statements and throw away the assignment. Do this after
6372 gimplify_modify_expr_rhs so we handle TARGET_EXPRs of addressable
6373 types properly. */
6374 if (is_empty_type (TREE_TYPE (*from_p))
6375 && !want_value
6376 /* Don't do this for calls that return addressable types, expand_call
6377 relies on those having a lhs. */
6378 && !(TREE_ADDRESSABLE (TREE_TYPE (*from_p))
6379 && TREE_CODE (*from_p) == CALL_EXPR))
6381 gimplify_stmt (from_p, pre_p);
6382 gimplify_stmt (to_p, pre_p);
6383 *expr_p = NULL_TREE;
6384 return GS_ALL_DONE;
6387 /* If the value being copied is of variable width, compute the length
6388 of the copy into a WITH_SIZE_EXPR. Note that we need to do this
6389 before gimplifying any of the operands so that we can resolve any
6390 PLACEHOLDER_EXPRs in the size. Also note that the RTL expander uses
6391 the size of the expression to be copied, not of the destination, so
6392 that is what we must do here. */
6393 maybe_with_size_expr (from_p);
6395 /* As a special case, we have to temporarily allow for assignments
6396 with a CALL_EXPR on the RHS. Since in GIMPLE a function call is
6397 a toplevel statement, when gimplifying the GENERIC expression
6398 MODIFY_EXPR <a, CALL_EXPR <foo>>, we cannot create the tuple
6399 GIMPLE_ASSIGN <a, GIMPLE_CALL <foo>>.
6401 Instead, we need to create the tuple GIMPLE_CALL <a, foo>. To
6402 prevent gimplify_expr from trying to create a new temporary for
6403 foo's LHS, we tell it that it should only gimplify until it
6404 reaches the CALL_EXPR. On return from gimplify_expr, the newly
6405 created GIMPLE_CALL <foo> will be the last statement in *PRE_P
6406 and all we need to do here is set 'a' to be its LHS. */
6408 /* Gimplify the RHS first for C++17 and bug 71104. */
6409 gimple_predicate initial_pred = initial_rhs_predicate_for (*to_p);
6410 ret = gimplify_expr (from_p, pre_p, post_p, initial_pred, fb_rvalue);
6411 if (ret == GS_ERROR)
6412 return ret;
6414 /* Then gimplify the LHS. */
6415 /* If we gimplified the RHS to a CALL_EXPR and that call may return
6416 twice we have to make sure to gimplify into non-SSA as otherwise
6417 the abnormal edge added later will make those defs not dominate
6418 their uses.
6419 ??? Technically this applies only to the registers used in the
6420 resulting non-register *TO_P. */
6421 bool saved_into_ssa = gimplify_ctxp->into_ssa;
6422 if (saved_into_ssa
6423 && TREE_CODE (*from_p) == CALL_EXPR
6424 && call_expr_flags (*from_p) & ECF_RETURNS_TWICE)
6425 gimplify_ctxp->into_ssa = false;
6426 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
6427 gimplify_ctxp->into_ssa = saved_into_ssa;
6428 if (ret == GS_ERROR)
6429 return ret;
6431 /* Now that the LHS is gimplified, re-gimplify the RHS if our initial
6432 guess for the predicate was wrong. */
6433 gimple_predicate final_pred = rhs_predicate_for (*to_p);
6434 if (final_pred != initial_pred)
6436 ret = gimplify_expr (from_p, pre_p, post_p, final_pred, fb_rvalue);
6437 if (ret == GS_ERROR)
6438 return ret;
6441 /* In case of va_arg internal fn wrappped in a WITH_SIZE_EXPR, add the type
6442 size as argument to the call. */
6443 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
6445 tree call = TREE_OPERAND (*from_p, 0);
6446 tree vlasize = TREE_OPERAND (*from_p, 1);
6448 if (TREE_CODE (call) == CALL_EXPR
6449 && CALL_EXPR_IFN (call) == IFN_VA_ARG)
6451 int nargs = call_expr_nargs (call);
6452 tree type = TREE_TYPE (call);
6453 tree ap = CALL_EXPR_ARG (call, 0);
6454 tree tag = CALL_EXPR_ARG (call, 1);
6455 tree aptag = CALL_EXPR_ARG (call, 2);
6456 tree newcall = build_call_expr_internal_loc (EXPR_LOCATION (call),
6457 IFN_VA_ARG, type,
6458 nargs + 1, ap, tag,
6459 aptag, vlasize);
6460 TREE_OPERAND (*from_p, 0) = newcall;
6464 /* Now see if the above changed *from_p to something we handle specially. */
6465 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
6466 want_value);
6467 if (ret != GS_UNHANDLED)
6468 return ret;
6470 /* If we've got a variable sized assignment between two lvalues (i.e. does
6471 not involve a call), then we can make things a bit more straightforward
6472 by converting the assignment to memcpy or memset. */
6473 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
6475 tree from = TREE_OPERAND (*from_p, 0);
6476 tree size = TREE_OPERAND (*from_p, 1);
6478 if (TREE_CODE (from) == CONSTRUCTOR)
6479 return gimplify_modify_expr_to_memset (expr_p, size, want_value, pre_p);
6480 else if (is_gimple_addressable (from)
6481 && ADDR_SPACE_GENERIC_P (TYPE_ADDR_SPACE (TREE_TYPE (*to_p)))
6482 && ADDR_SPACE_GENERIC_P (TYPE_ADDR_SPACE (TREE_TYPE (from))))
6484 *from_p = from;
6485 return gimplify_modify_expr_to_memcpy (expr_p, size, want_value,
6486 pre_p);
6490 /* Transform partial stores to non-addressable complex variables into
6491 total stores. This allows us to use real instead of virtual operands
6492 for these variables, which improves optimization. */
6493 if ((TREE_CODE (*to_p) == REALPART_EXPR
6494 || TREE_CODE (*to_p) == IMAGPART_EXPR)
6495 && is_gimple_reg (TREE_OPERAND (*to_p, 0)))
6496 return gimplify_modify_expr_complex_part (expr_p, pre_p, want_value);
6498 /* Try to alleviate the effects of the gimplification creating artificial
6499 temporaries (see for example is_gimple_reg_rhs) on the debug info, but
6500 make sure not to create DECL_DEBUG_EXPR links across functions. */
6501 if (!gimplify_ctxp->into_ssa
6502 && VAR_P (*from_p)
6503 && DECL_IGNORED_P (*from_p)
6504 && DECL_P (*to_p)
6505 && !DECL_IGNORED_P (*to_p)
6506 && decl_function_context (*to_p) == current_function_decl
6507 && decl_function_context (*from_p) == current_function_decl)
6509 if (!DECL_NAME (*from_p) && DECL_NAME (*to_p))
6510 DECL_NAME (*from_p)
6511 = create_tmp_var_name (IDENTIFIER_POINTER (DECL_NAME (*to_p)));
6512 DECL_HAS_DEBUG_EXPR_P (*from_p) = 1;
6513 SET_DECL_DEBUG_EXPR (*from_p, *to_p);
6516 if (want_value && TREE_THIS_VOLATILE (*to_p))
6517 *from_p = get_initialized_tmp_var (*from_p, pre_p, post_p);
6519 if (TREE_CODE (*from_p) == CALL_EXPR)
6521 /* Since the RHS is a CALL_EXPR, we need to create a GIMPLE_CALL
6522 instead of a GIMPLE_ASSIGN. */
6523 gcall *call_stmt;
6524 if (CALL_EXPR_FN (*from_p) == NULL_TREE)
6526 /* Gimplify internal functions created in the FEs. */
6527 int nargs = call_expr_nargs (*from_p), i;
6528 enum internal_fn ifn = CALL_EXPR_IFN (*from_p);
6529 auto_vec<tree> vargs (nargs);
6531 for (i = 0; i < nargs; i++)
6533 gimplify_arg (&CALL_EXPR_ARG (*from_p, i), pre_p,
6534 EXPR_LOCATION (*from_p));
6535 vargs.quick_push (CALL_EXPR_ARG (*from_p, i));
6537 call_stmt = gimple_build_call_internal_vec (ifn, vargs);
6538 gimple_call_set_nothrow (call_stmt, TREE_NOTHROW (*from_p));
6539 gimple_set_location (call_stmt, EXPR_LOCATION (*expr_p));
6541 else
6543 tree fnptrtype = TREE_TYPE (CALL_EXPR_FN (*from_p));
6544 CALL_EXPR_FN (*from_p) = TREE_OPERAND (CALL_EXPR_FN (*from_p), 0);
6545 STRIP_USELESS_TYPE_CONVERSION (CALL_EXPR_FN (*from_p));
6546 tree fndecl = get_callee_fndecl (*from_p);
6547 if (fndecl
6548 && fndecl_built_in_p (fndecl, BUILT_IN_EXPECT)
6549 && call_expr_nargs (*from_p) == 3)
6550 call_stmt = gimple_build_call_internal (IFN_BUILTIN_EXPECT, 3,
6551 CALL_EXPR_ARG (*from_p, 0),
6552 CALL_EXPR_ARG (*from_p, 1),
6553 CALL_EXPR_ARG (*from_p, 2));
6554 else
6556 call_stmt = gimple_build_call_from_tree (*from_p, fnptrtype);
6559 notice_special_calls (call_stmt);
6560 if (!gimple_call_noreturn_p (call_stmt) || !should_remove_lhs_p (*to_p))
6561 gimple_call_set_lhs (call_stmt, *to_p);
6562 else if (TREE_CODE (*to_p) == SSA_NAME)
6563 /* The above is somewhat premature, avoid ICEing later for a
6564 SSA name w/o a definition. We may have uses in the GIMPLE IL.
6565 ??? This doesn't make it a default-def. */
6566 SSA_NAME_DEF_STMT (*to_p) = gimple_build_nop ();
6568 assign = call_stmt;
6570 else
6572 assign = gimple_build_assign (*to_p, *from_p);
6573 gimple_set_location (assign, EXPR_LOCATION (*expr_p));
6574 if (COMPARISON_CLASS_P (*from_p))
6575 copy_warning (assign, *from_p);
6578 if (gimplify_ctxp->into_ssa && is_gimple_reg (*to_p))
6580 /* We should have got an SSA name from the start. */
6581 gcc_assert (TREE_CODE (*to_p) == SSA_NAME
6582 || ! gimple_in_ssa_p (cfun));
6585 gimplify_seq_add_stmt (pre_p, assign);
6586 gsi = gsi_last (*pre_p);
6587 maybe_fold_stmt (&gsi);
6589 if (want_value)
6591 *expr_p = TREE_THIS_VOLATILE (*to_p) ? *from_p : unshare_expr (*to_p);
6592 return GS_OK;
6594 else
6595 *expr_p = NULL;
6597 return GS_ALL_DONE;
6600 /* Gimplify a comparison between two variable-sized objects. Do this
6601 with a call to BUILT_IN_MEMCMP. */
6603 static enum gimplify_status
6604 gimplify_variable_sized_compare (tree *expr_p)
6606 location_t loc = EXPR_LOCATION (*expr_p);
6607 tree op0 = TREE_OPERAND (*expr_p, 0);
6608 tree op1 = TREE_OPERAND (*expr_p, 1);
6609 tree t, arg, dest, src, expr;
6611 arg = TYPE_SIZE_UNIT (TREE_TYPE (op0));
6612 arg = unshare_expr (arg);
6613 arg = SUBSTITUTE_PLACEHOLDER_IN_EXPR (arg, op0);
6614 src = build_fold_addr_expr_loc (loc, op1);
6615 dest = build_fold_addr_expr_loc (loc, op0);
6616 t = builtin_decl_implicit (BUILT_IN_MEMCMP);
6617 t = build_call_expr_loc (loc, t, 3, dest, src, arg);
6619 expr
6620 = build2 (TREE_CODE (*expr_p), TREE_TYPE (*expr_p), t, integer_zero_node);
6621 SET_EXPR_LOCATION (expr, loc);
6622 *expr_p = expr;
6624 return GS_OK;
6627 /* Gimplify a comparison between two aggregate objects of integral scalar
6628 mode as a comparison between the bitwise equivalent scalar values. */
6630 static enum gimplify_status
6631 gimplify_scalar_mode_aggregate_compare (tree *expr_p)
6633 location_t loc = EXPR_LOCATION (*expr_p);
6634 tree op0 = TREE_OPERAND (*expr_p, 0);
6635 tree op1 = TREE_OPERAND (*expr_p, 1);
6637 tree type = TREE_TYPE (op0);
6638 tree scalar_type = lang_hooks.types.type_for_mode (TYPE_MODE (type), 1);
6640 op0 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op0);
6641 op1 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op1);
6643 *expr_p
6644 = fold_build2_loc (loc, TREE_CODE (*expr_p), TREE_TYPE (*expr_p), op0, op1);
6646 return GS_OK;
6649 /* Gimplify an expression sequence. This function gimplifies each
6650 expression and rewrites the original expression with the last
6651 expression of the sequence in GIMPLE form.
6653 PRE_P points to the list where the side effects for all the
6654 expressions in the sequence will be emitted.
6656 WANT_VALUE is true when the result of the last COMPOUND_EXPR is used. */
6658 static enum gimplify_status
6659 gimplify_compound_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
6661 tree t = *expr_p;
6665 tree *sub_p = &TREE_OPERAND (t, 0);
6667 if (TREE_CODE (*sub_p) == COMPOUND_EXPR)
6668 gimplify_compound_expr (sub_p, pre_p, false);
6669 else
6670 gimplify_stmt (sub_p, pre_p);
6672 t = TREE_OPERAND (t, 1);
6674 while (TREE_CODE (t) == COMPOUND_EXPR);
6676 *expr_p = t;
6677 if (want_value)
6678 return GS_OK;
6679 else
6681 gimplify_stmt (expr_p, pre_p);
6682 return GS_ALL_DONE;
6686 /* Gimplify a SAVE_EXPR node. EXPR_P points to the expression to
6687 gimplify. After gimplification, EXPR_P will point to a new temporary
6688 that holds the original value of the SAVE_EXPR node.
6690 PRE_P points to the list where side effects that must happen before
6691 *EXPR_P should be stored. */
6693 static enum gimplify_status
6694 gimplify_save_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6696 enum gimplify_status ret = GS_ALL_DONE;
6697 tree val;
6699 gcc_assert (TREE_CODE (*expr_p) == SAVE_EXPR);
6700 val = TREE_OPERAND (*expr_p, 0);
6702 if (val && TREE_TYPE (val) == error_mark_node)
6703 return GS_ERROR;
6705 /* If the SAVE_EXPR has not been resolved, then evaluate it once. */
6706 if (!SAVE_EXPR_RESOLVED_P (*expr_p))
6708 /* The operand may be a void-valued expression. It is
6709 being executed only for its side-effects. */
6710 if (TREE_TYPE (val) == void_type_node)
6712 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
6713 is_gimple_stmt, fb_none);
6714 val = NULL;
6716 else
6717 /* The temporary may not be an SSA name as later abnormal and EH
6718 control flow may invalidate use/def domination. When in SSA
6719 form then assume there are no such issues and SAVE_EXPRs only
6720 appear via GENERIC foldings. */
6721 val = get_initialized_tmp_var (val, pre_p, post_p,
6722 gimple_in_ssa_p (cfun));
6724 TREE_OPERAND (*expr_p, 0) = val;
6725 SAVE_EXPR_RESOLVED_P (*expr_p) = 1;
6728 *expr_p = val;
6730 return ret;
6733 /* Rewrite the ADDR_EXPR node pointed to by EXPR_P
6735 unary_expr
6736 : ...
6737 | '&' varname
6740 PRE_P points to the list where side effects that must happen before
6741 *EXPR_P should be stored.
6743 POST_P points to the list where side effects that must happen after
6744 *EXPR_P should be stored. */
6746 static enum gimplify_status
6747 gimplify_addr_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6749 tree expr = *expr_p;
6750 tree op0 = TREE_OPERAND (expr, 0);
6751 enum gimplify_status ret;
6752 location_t loc = EXPR_LOCATION (*expr_p);
6754 switch (TREE_CODE (op0))
6756 case INDIRECT_REF:
6757 do_indirect_ref:
6758 /* Check if we are dealing with an expression of the form '&*ptr'.
6759 While the front end folds away '&*ptr' into 'ptr', these
6760 expressions may be generated internally by the compiler (e.g.,
6761 builtins like __builtin_va_end). */
6762 /* Caution: the silent array decomposition semantics we allow for
6763 ADDR_EXPR means we can't always discard the pair. */
6764 /* Gimplification of the ADDR_EXPR operand may drop
6765 cv-qualification conversions, so make sure we add them if
6766 needed. */
6768 tree op00 = TREE_OPERAND (op0, 0);
6769 tree t_expr = TREE_TYPE (expr);
6770 tree t_op00 = TREE_TYPE (op00);
6772 if (!useless_type_conversion_p (t_expr, t_op00))
6773 op00 = fold_convert_loc (loc, TREE_TYPE (expr), op00);
6774 *expr_p = op00;
6775 ret = GS_OK;
6777 break;
6779 case VIEW_CONVERT_EXPR:
6780 /* Take the address of our operand and then convert it to the type of
6781 this ADDR_EXPR.
6783 ??? The interactions of VIEW_CONVERT_EXPR and aliasing is not at
6784 all clear. The impact of this transformation is even less clear. */
6786 /* If the operand is a useless conversion, look through it. Doing so
6787 guarantees that the ADDR_EXPR and its operand will remain of the
6788 same type. */
6789 if (tree_ssa_useless_type_conversion (TREE_OPERAND (op0, 0)))
6790 op0 = TREE_OPERAND (op0, 0);
6792 *expr_p = fold_convert_loc (loc, TREE_TYPE (expr),
6793 build_fold_addr_expr_loc (loc,
6794 TREE_OPERAND (op0, 0)));
6795 ret = GS_OK;
6796 break;
6798 case MEM_REF:
6799 if (integer_zerop (TREE_OPERAND (op0, 1)))
6800 goto do_indirect_ref;
6802 /* fall through */
6804 default:
6805 /* If we see a call to a declared builtin or see its address
6806 being taken (we can unify those cases here) then we can mark
6807 the builtin for implicit generation by GCC. */
6808 if (TREE_CODE (op0) == FUNCTION_DECL
6809 && fndecl_built_in_p (op0, BUILT_IN_NORMAL)
6810 && builtin_decl_declared_p (DECL_FUNCTION_CODE (op0)))
6811 set_builtin_decl_implicit_p (DECL_FUNCTION_CODE (op0), true);
6813 /* We use fb_either here because the C frontend sometimes takes
6814 the address of a call that returns a struct; see
6815 gcc.dg/c99-array-lval-1.c. The gimplifier will correctly make
6816 the implied temporary explicit. */
6818 /* Make the operand addressable. */
6819 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, post_p,
6820 is_gimple_addressable, fb_either);
6821 if (ret == GS_ERROR)
6822 break;
6824 /* Then mark it. Beware that it may not be possible to do so directly
6825 if a temporary has been created by the gimplification. */
6826 prepare_gimple_addressable (&TREE_OPERAND (expr, 0), pre_p);
6828 op0 = TREE_OPERAND (expr, 0);
6830 /* For various reasons, the gimplification of the expression
6831 may have made a new INDIRECT_REF. */
6832 if (INDIRECT_REF_P (op0)
6833 || (TREE_CODE (op0) == MEM_REF
6834 && integer_zerop (TREE_OPERAND (op0, 1))))
6835 goto do_indirect_ref;
6837 mark_addressable (TREE_OPERAND (expr, 0));
6839 /* The FEs may end up building ADDR_EXPRs early on a decl with
6840 an incomplete type. Re-build ADDR_EXPRs in canonical form
6841 here. */
6842 if (!types_compatible_p (TREE_TYPE (op0), TREE_TYPE (TREE_TYPE (expr))))
6843 *expr_p = build_fold_addr_expr (op0);
6845 /* Make sure TREE_CONSTANT and TREE_SIDE_EFFECTS are set properly. */
6846 recompute_tree_invariant_for_addr_expr (*expr_p);
6848 /* If we re-built the ADDR_EXPR add a conversion to the original type
6849 if required. */
6850 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
6851 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
6853 break;
6856 return ret;
6859 /* Gimplify the operands of an ASM_EXPR. Input operands should be a gimple
6860 value; output operands should be a gimple lvalue. */
6862 static enum gimplify_status
6863 gimplify_asm_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6865 tree expr;
6866 int noutputs;
6867 const char **oconstraints;
6868 int i;
6869 tree link;
6870 const char *constraint;
6871 bool allows_mem, allows_reg, is_inout;
6872 enum gimplify_status ret, tret;
6873 gasm *stmt;
6874 vec<tree, va_gc> *inputs;
6875 vec<tree, va_gc> *outputs;
6876 vec<tree, va_gc> *clobbers;
6877 vec<tree, va_gc> *labels;
6878 tree link_next;
6880 expr = *expr_p;
6881 noutputs = list_length (ASM_OUTPUTS (expr));
6882 oconstraints = (const char **) alloca ((noutputs) * sizeof (const char *));
6884 inputs = NULL;
6885 outputs = NULL;
6886 clobbers = NULL;
6887 labels = NULL;
6889 ret = GS_ALL_DONE;
6890 link_next = NULL_TREE;
6891 for (i = 0, link = ASM_OUTPUTS (expr); link; ++i, link = link_next)
6893 bool ok;
6894 size_t constraint_len;
6896 link_next = TREE_CHAIN (link);
6898 oconstraints[i]
6899 = constraint
6900 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
6901 constraint_len = strlen (constraint);
6902 if (constraint_len == 0)
6903 continue;
6905 ok = parse_output_constraint (&constraint, i, 0, 0,
6906 &allows_mem, &allows_reg, &is_inout);
6907 if (!ok)
6909 ret = GS_ERROR;
6910 is_inout = false;
6913 /* If we can't make copies, we can only accept memory.
6914 Similarly for VLAs. */
6915 tree outtype = TREE_TYPE (TREE_VALUE (link));
6916 if (outtype != error_mark_node
6917 && (TREE_ADDRESSABLE (outtype)
6918 || !COMPLETE_TYPE_P (outtype)
6919 || !tree_fits_poly_uint64_p (TYPE_SIZE_UNIT (outtype))))
6921 if (allows_mem)
6922 allows_reg = 0;
6923 else
6925 error ("impossible constraint in %<asm%>");
6926 error ("non-memory output %d must stay in memory", i);
6927 return GS_ERROR;
6931 if (!allows_reg && allows_mem)
6932 mark_addressable (TREE_VALUE (link));
6934 tree orig = TREE_VALUE (link);
6935 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6936 is_inout ? is_gimple_min_lval : is_gimple_lvalue,
6937 fb_lvalue | fb_mayfail);
6938 if (tret == GS_ERROR)
6940 if (orig != error_mark_node)
6941 error ("invalid lvalue in %<asm%> output %d", i);
6942 ret = tret;
6945 /* If the constraint does not allow memory make sure we gimplify
6946 it to a register if it is not already but its base is. This
6947 happens for complex and vector components. */
6948 if (!allows_mem)
6950 tree op = TREE_VALUE (link);
6951 if (! is_gimple_val (op)
6952 && is_gimple_reg_type (TREE_TYPE (op))
6953 && is_gimple_reg (get_base_address (op)))
6955 tree tem = create_tmp_reg (TREE_TYPE (op));
6956 tree ass;
6957 if (is_inout)
6959 ass = build2 (MODIFY_EXPR, TREE_TYPE (tem),
6960 tem, unshare_expr (op));
6961 gimplify_and_add (ass, pre_p);
6963 ass = build2 (MODIFY_EXPR, TREE_TYPE (tem), op, tem);
6964 gimplify_and_add (ass, post_p);
6966 TREE_VALUE (link) = tem;
6967 tret = GS_OK;
6971 vec_safe_push (outputs, link);
6972 TREE_CHAIN (link) = NULL_TREE;
6974 if (is_inout)
6976 /* An input/output operand. To give the optimizers more
6977 flexibility, split it into separate input and output
6978 operands. */
6979 tree input;
6980 /* Buffer big enough to format a 32-bit UINT_MAX into. */
6981 char buf[11];
6983 /* Turn the in/out constraint into an output constraint. */
6984 char *p = xstrdup (constraint);
6985 p[0] = '=';
6986 TREE_VALUE (TREE_PURPOSE (link)) = build_string (constraint_len, p);
6988 /* And add a matching input constraint. */
6989 if (allows_reg)
6991 sprintf (buf, "%u", i);
6993 /* If there are multiple alternatives in the constraint,
6994 handle each of them individually. Those that allow register
6995 will be replaced with operand number, the others will stay
6996 unchanged. */
6997 if (strchr (p, ',') != NULL)
6999 size_t len = 0, buflen = strlen (buf);
7000 char *beg, *end, *str, *dst;
7002 for (beg = p + 1;;)
7004 end = strchr (beg, ',');
7005 if (end == NULL)
7006 end = strchr (beg, '\0');
7007 if ((size_t) (end - beg) < buflen)
7008 len += buflen + 1;
7009 else
7010 len += end - beg + 1;
7011 if (*end)
7012 beg = end + 1;
7013 else
7014 break;
7017 str = (char *) alloca (len);
7018 for (beg = p + 1, dst = str;;)
7020 const char *tem;
7021 bool mem_p, reg_p, inout_p;
7023 end = strchr (beg, ',');
7024 if (end)
7025 *end = '\0';
7026 beg[-1] = '=';
7027 tem = beg - 1;
7028 parse_output_constraint (&tem, i, 0, 0,
7029 &mem_p, &reg_p, &inout_p);
7030 if (dst != str)
7031 *dst++ = ',';
7032 if (reg_p)
7034 memcpy (dst, buf, buflen);
7035 dst += buflen;
7037 else
7039 if (end)
7040 len = end - beg;
7041 else
7042 len = strlen (beg);
7043 memcpy (dst, beg, len);
7044 dst += len;
7046 if (end)
7047 beg = end + 1;
7048 else
7049 break;
7051 *dst = '\0';
7052 input = build_string (dst - str, str);
7054 else
7055 input = build_string (strlen (buf), buf);
7057 else
7058 input = build_string (constraint_len - 1, constraint + 1);
7060 free (p);
7062 input = build_tree_list (build_tree_list (NULL_TREE, input),
7063 unshare_expr (TREE_VALUE (link)));
7064 ASM_INPUTS (expr) = chainon (ASM_INPUTS (expr), input);
7068 link_next = NULL_TREE;
7069 for (link = ASM_INPUTS (expr); link; ++i, link = link_next)
7071 link_next = TREE_CHAIN (link);
7072 constraint = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
7073 parse_input_constraint (&constraint, 0, 0, noutputs, 0,
7074 oconstraints, &allows_mem, &allows_reg);
7076 /* If we can't make copies, we can only accept memory. */
7077 tree intype = TREE_TYPE (TREE_VALUE (link));
7078 if (intype != error_mark_node
7079 && (TREE_ADDRESSABLE (intype)
7080 || !COMPLETE_TYPE_P (intype)
7081 || !tree_fits_poly_uint64_p (TYPE_SIZE_UNIT (intype))))
7083 if (allows_mem)
7084 allows_reg = 0;
7085 else
7087 error ("impossible constraint in %<asm%>");
7088 error ("non-memory input %d must stay in memory", i);
7089 return GS_ERROR;
7093 /* If the operand is a memory input, it should be an lvalue. */
7094 if (!allows_reg && allows_mem)
7096 tree inputv = TREE_VALUE (link);
7097 STRIP_NOPS (inputv);
7098 if (TREE_CODE (inputv) == PREDECREMENT_EXPR
7099 || TREE_CODE (inputv) == PREINCREMENT_EXPR
7100 || TREE_CODE (inputv) == POSTDECREMENT_EXPR
7101 || TREE_CODE (inputv) == POSTINCREMENT_EXPR
7102 || TREE_CODE (inputv) == MODIFY_EXPR)
7103 TREE_VALUE (link) = error_mark_node;
7104 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
7105 is_gimple_lvalue, fb_lvalue | fb_mayfail);
7106 if (tret != GS_ERROR)
7108 /* Unlike output operands, memory inputs are not guaranteed
7109 to be lvalues by the FE, and while the expressions are
7110 marked addressable there, if it is e.g. a statement
7111 expression, temporaries in it might not end up being
7112 addressable. They might be already used in the IL and thus
7113 it is too late to make them addressable now though. */
7114 tree x = TREE_VALUE (link);
7115 while (handled_component_p (x))
7116 x = TREE_OPERAND (x, 0);
7117 if (TREE_CODE (x) == MEM_REF
7118 && TREE_CODE (TREE_OPERAND (x, 0)) == ADDR_EXPR)
7119 x = TREE_OPERAND (TREE_OPERAND (x, 0), 0);
7120 if ((VAR_P (x)
7121 || TREE_CODE (x) == PARM_DECL
7122 || TREE_CODE (x) == RESULT_DECL)
7123 && !TREE_ADDRESSABLE (x)
7124 && is_gimple_reg (x))
7126 warning_at (EXPR_LOC_OR_LOC (TREE_VALUE (link),
7127 input_location), 0,
7128 "memory input %d is not directly addressable",
7130 prepare_gimple_addressable (&TREE_VALUE (link), pre_p);
7133 mark_addressable (TREE_VALUE (link));
7134 if (tret == GS_ERROR)
7136 if (inputv != error_mark_node)
7137 error_at (EXPR_LOC_OR_LOC (TREE_VALUE (link), input_location),
7138 "memory input %d is not directly addressable", i);
7139 ret = tret;
7142 else
7144 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
7145 is_gimple_asm_val, fb_rvalue);
7146 if (tret == GS_ERROR)
7147 ret = tret;
7150 TREE_CHAIN (link) = NULL_TREE;
7151 vec_safe_push (inputs, link);
7154 link_next = NULL_TREE;
7155 for (link = ASM_CLOBBERS (expr); link; ++i, link = link_next)
7157 link_next = TREE_CHAIN (link);
7158 TREE_CHAIN (link) = NULL_TREE;
7159 vec_safe_push (clobbers, link);
7162 link_next = NULL_TREE;
7163 for (link = ASM_LABELS (expr); link; ++i, link = link_next)
7165 link_next = TREE_CHAIN (link);
7166 TREE_CHAIN (link) = NULL_TREE;
7167 vec_safe_push (labels, link);
7170 /* Do not add ASMs with errors to the gimple IL stream. */
7171 if (ret != GS_ERROR)
7173 stmt = gimple_build_asm_vec (TREE_STRING_POINTER (ASM_STRING (expr)),
7174 inputs, outputs, clobbers, labels);
7176 /* asm is volatile if it was marked by the user as volatile or
7177 there are no outputs or this is an asm goto. */
7178 gimple_asm_set_volatile (stmt,
7179 ASM_VOLATILE_P (expr)
7180 || noutputs == 0
7181 || labels);
7182 gimple_asm_set_input (stmt, ASM_INPUT_P (expr));
7183 gimple_asm_set_inline (stmt, ASM_INLINE_P (expr));
7185 gimplify_seq_add_stmt (pre_p, stmt);
7188 return ret;
7191 /* Gimplify a CLEANUP_POINT_EXPR. Currently this works by adding
7192 GIMPLE_WITH_CLEANUP_EXPRs to the prequeue as we encounter cleanups while
7193 gimplifying the body, and converting them to TRY_FINALLY_EXPRs when we
7194 return to this function.
7196 FIXME should we complexify the prequeue handling instead? Or use flags
7197 for all the cleanups and let the optimizer tighten them up? The current
7198 code seems pretty fragile; it will break on a cleanup within any
7199 non-conditional nesting. But any such nesting would be broken, anyway;
7200 we can't write a TRY_FINALLY_EXPR that starts inside a nesting construct
7201 and continues out of it. We can do that at the RTL level, though, so
7202 having an optimizer to tighten up try/finally regions would be a Good
7203 Thing. */
7205 static enum gimplify_status
7206 gimplify_cleanup_point_expr (tree *expr_p, gimple_seq *pre_p)
7208 gimple_stmt_iterator iter;
7209 gimple_seq body_sequence = NULL;
7211 tree temp = voidify_wrapper_expr (*expr_p, NULL);
7213 /* We only care about the number of conditions between the innermost
7214 CLEANUP_POINT_EXPR and the cleanup. So save and reset the count and
7215 any cleanups collected outside the CLEANUP_POINT_EXPR. */
7216 int old_conds = gimplify_ctxp->conditions;
7217 gimple_seq old_cleanups = gimplify_ctxp->conditional_cleanups;
7218 bool old_in_cleanup_point_expr = gimplify_ctxp->in_cleanup_point_expr;
7219 gimplify_ctxp->conditions = 0;
7220 gimplify_ctxp->conditional_cleanups = NULL;
7221 gimplify_ctxp->in_cleanup_point_expr = true;
7223 gimplify_stmt (&TREE_OPERAND (*expr_p, 0), &body_sequence);
7225 gimplify_ctxp->conditions = old_conds;
7226 gimplify_ctxp->conditional_cleanups = old_cleanups;
7227 gimplify_ctxp->in_cleanup_point_expr = old_in_cleanup_point_expr;
7229 for (iter = gsi_start (body_sequence); !gsi_end_p (iter); )
7231 gimple *wce = gsi_stmt (iter);
7233 if (gimple_code (wce) == GIMPLE_WITH_CLEANUP_EXPR)
7235 if (gsi_one_before_end_p (iter))
7237 /* Note that gsi_insert_seq_before and gsi_remove do not
7238 scan operands, unlike some other sequence mutators. */
7239 if (!gimple_wce_cleanup_eh_only (wce))
7240 gsi_insert_seq_before_without_update (&iter,
7241 gimple_wce_cleanup (wce),
7242 GSI_SAME_STMT);
7243 gsi_remove (&iter, true);
7244 break;
7246 else
7248 gtry *gtry;
7249 gimple_seq seq;
7250 enum gimple_try_flags kind;
7252 if (gimple_wce_cleanup_eh_only (wce))
7253 kind = GIMPLE_TRY_CATCH;
7254 else
7255 kind = GIMPLE_TRY_FINALLY;
7256 seq = gsi_split_seq_after (iter);
7258 gtry = gimple_build_try (seq, gimple_wce_cleanup (wce), kind);
7259 /* Do not use gsi_replace here, as it may scan operands.
7260 We want to do a simple structural modification only. */
7261 gsi_set_stmt (&iter, gtry);
7262 iter = gsi_start (gtry->eval);
7265 else
7266 gsi_next (&iter);
7269 gimplify_seq_add_seq (pre_p, body_sequence);
7270 if (temp)
7272 *expr_p = temp;
7273 return GS_OK;
7275 else
7277 *expr_p = NULL;
7278 return GS_ALL_DONE;
7282 /* Insert a cleanup marker for gimplify_cleanup_point_expr. CLEANUP
7283 is the cleanup action required. EH_ONLY is true if the cleanup should
7284 only be executed if an exception is thrown, not on normal exit.
7285 If FORCE_UNCOND is true perform the cleanup unconditionally; this is
7286 only valid for clobbers. */
7288 static void
7289 gimple_push_cleanup (tree var, tree cleanup, bool eh_only, gimple_seq *pre_p,
7290 bool force_uncond = false)
7292 gimple *wce;
7293 gimple_seq cleanup_stmts = NULL;
7295 /* Errors can result in improperly nested cleanups. Which results in
7296 confusion when trying to resolve the GIMPLE_WITH_CLEANUP_EXPR. */
7297 if (seen_error ())
7298 return;
7300 if (gimple_conditional_context ())
7302 /* If we're in a conditional context, this is more complex. We only
7303 want to run the cleanup if we actually ran the initialization that
7304 necessitates it, but we want to run it after the end of the
7305 conditional context. So we wrap the try/finally around the
7306 condition and use a flag to determine whether or not to actually
7307 run the destructor. Thus
7309 test ? f(A()) : 0
7311 becomes (approximately)
7313 flag = 0;
7314 try {
7315 if (test) { A::A(temp); flag = 1; val = f(temp); }
7316 else { val = 0; }
7317 } finally {
7318 if (flag) A::~A(temp);
7322 if (force_uncond)
7324 gimplify_stmt (&cleanup, &cleanup_stmts);
7325 wce = gimple_build_wce (cleanup_stmts);
7326 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, wce);
7328 else
7330 tree flag = create_tmp_var (boolean_type_node, "cleanup");
7331 gassign *ffalse = gimple_build_assign (flag, boolean_false_node);
7332 gassign *ftrue = gimple_build_assign (flag, boolean_true_node);
7334 cleanup = build3 (COND_EXPR, void_type_node, flag, cleanup, NULL);
7335 gimplify_stmt (&cleanup, &cleanup_stmts);
7336 wce = gimple_build_wce (cleanup_stmts);
7337 gimple_wce_set_cleanup_eh_only (wce, eh_only);
7339 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, ffalse);
7340 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, wce);
7341 gimplify_seq_add_stmt (pre_p, ftrue);
7343 /* Because of this manipulation, and the EH edges that jump
7344 threading cannot redirect, the temporary (VAR) will appear
7345 to be used uninitialized. Don't warn. */
7346 suppress_warning (var, OPT_Wuninitialized);
7349 else
7351 gimplify_stmt (&cleanup, &cleanup_stmts);
7352 wce = gimple_build_wce (cleanup_stmts);
7353 gimple_wce_set_cleanup_eh_only (wce, eh_only);
7354 gimplify_seq_add_stmt (pre_p, wce);
7358 /* Gimplify a TARGET_EXPR which doesn't appear on the rhs of an INIT_EXPR. */
7360 static enum gimplify_status
7361 gimplify_target_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
7363 tree targ = *expr_p;
7364 tree temp = TARGET_EXPR_SLOT (targ);
7365 tree init = TARGET_EXPR_INITIAL (targ);
7366 enum gimplify_status ret;
7368 bool unpoison_empty_seq = false;
7369 gimple_stmt_iterator unpoison_it;
7371 if (init)
7373 gimple_seq init_pre_p = NULL;
7375 /* TARGET_EXPR temps aren't part of the enclosing block, so add it
7376 to the temps list. Handle also variable length TARGET_EXPRs. */
7377 if (!poly_int_tree_p (DECL_SIZE (temp)))
7379 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (temp)))
7380 gimplify_type_sizes (TREE_TYPE (temp), &init_pre_p);
7381 /* FIXME: this is correct only when the size of the type does
7382 not depend on expressions evaluated in init. */
7383 gimplify_vla_decl (temp, &init_pre_p);
7385 else
7387 /* Save location where we need to place unpoisoning. It's possible
7388 that a variable will be converted to needs_to_live_in_memory. */
7389 unpoison_it = gsi_last (*pre_p);
7390 unpoison_empty_seq = gsi_end_p (unpoison_it);
7392 gimple_add_tmp_var (temp);
7395 /* If TARGET_EXPR_INITIAL is void, then the mere evaluation of the
7396 expression is supposed to initialize the slot. */
7397 if (VOID_TYPE_P (TREE_TYPE (init)))
7398 ret = gimplify_expr (&init, &init_pre_p, post_p, is_gimple_stmt,
7399 fb_none);
7400 else
7402 tree init_expr = build2 (INIT_EXPR, void_type_node, temp, init);
7403 init = init_expr;
7404 ret = gimplify_expr (&init, &init_pre_p, post_p, is_gimple_stmt,
7405 fb_none);
7406 init = NULL;
7407 ggc_free (init_expr);
7409 if (ret == GS_ERROR)
7411 /* PR c++/28266 Make sure this is expanded only once. */
7412 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
7413 return GS_ERROR;
7416 if (init)
7417 gimplify_and_add (init, &init_pre_p);
7419 /* Add a clobber for the temporary going out of scope, like
7420 gimplify_bind_expr. But only if we did not promote the
7421 temporary to static storage. */
7422 if (gimplify_ctxp->in_cleanup_point_expr
7423 && !TREE_STATIC (temp)
7424 && needs_to_live_in_memory (temp))
7426 if (flag_stack_reuse == SR_ALL)
7428 tree clobber = build_clobber (TREE_TYPE (temp),
7429 CLOBBER_STORAGE_END);
7430 clobber = build2 (MODIFY_EXPR, TREE_TYPE (temp), temp, clobber);
7431 gimple_push_cleanup (temp, clobber, false, pre_p, true);
7433 if (asan_poisoned_variables
7434 && DECL_ALIGN (temp) <= MAX_SUPPORTED_STACK_ALIGNMENT
7435 && !TREE_STATIC (temp)
7436 && dbg_cnt (asan_use_after_scope)
7437 && !gimplify_omp_ctxp)
7439 tree asan_cleanup = build_asan_poison_call_expr (temp);
7440 if (asan_cleanup)
7442 if (unpoison_empty_seq)
7443 unpoison_it = gsi_start (*pre_p);
7445 asan_poison_variable (temp, false, &unpoison_it,
7446 unpoison_empty_seq);
7447 gimple_push_cleanup (temp, asan_cleanup, false, pre_p);
7452 gimple_seq_add_seq (pre_p, init_pre_p);
7454 /* If needed, push the cleanup for the temp. */
7455 if (TARGET_EXPR_CLEANUP (targ))
7456 gimple_push_cleanup (temp, TARGET_EXPR_CLEANUP (targ),
7457 CLEANUP_EH_ONLY (targ), pre_p);
7459 /* Only expand this once. */
7460 TREE_OPERAND (targ, 3) = init;
7461 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
7463 else
7464 /* We should have expanded this before. */
7465 gcc_assert (DECL_SEEN_IN_BIND_EXPR_P (temp));
7467 *expr_p = temp;
7468 return GS_OK;
7471 /* Gimplification of expression trees. */
7473 /* Gimplify an expression which appears at statement context. The
7474 corresponding GIMPLE statements are added to *SEQ_P. If *SEQ_P is
7475 NULL, a new sequence is allocated.
7477 Return true if we actually added a statement to the queue. */
7479 bool
7480 gimplify_stmt (tree *stmt_p, gimple_seq *seq_p)
7482 gimple_seq_node last;
7484 last = gimple_seq_last (*seq_p);
7485 gimplify_expr (stmt_p, seq_p, NULL, is_gimple_stmt, fb_none);
7486 return last != gimple_seq_last (*seq_p);
7489 /* Add FIRSTPRIVATE entries for DECL in the OpenMP the surrounding parallels
7490 to CTX. If entries already exist, force them to be some flavor of private.
7491 If there is no enclosing parallel, do nothing. */
7493 void
7494 omp_firstprivatize_variable (struct gimplify_omp_ctx *ctx, tree decl)
7496 splay_tree_node n;
7498 if (decl == NULL || !DECL_P (decl) || ctx->region_type == ORT_NONE)
7499 return;
7503 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7504 if (n != NULL)
7506 if (n->value & GOVD_SHARED)
7507 n->value = GOVD_FIRSTPRIVATE | (n->value & GOVD_SEEN);
7508 else if (n->value & GOVD_MAP)
7509 n->value |= GOVD_MAP_TO_ONLY;
7510 else
7511 return;
7513 else if ((ctx->region_type & ORT_TARGET) != 0)
7515 if (ctx->defaultmap[GDMK_SCALAR] & GOVD_FIRSTPRIVATE)
7516 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
7517 else
7518 omp_add_variable (ctx, decl, GOVD_MAP | GOVD_MAP_TO_ONLY);
7520 else if (ctx->region_type != ORT_WORKSHARE
7521 && ctx->region_type != ORT_TASKGROUP
7522 && ctx->region_type != ORT_SIMD
7523 && ctx->region_type != ORT_ACC
7524 && !(ctx->region_type & ORT_TARGET_DATA))
7525 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
7527 ctx = ctx->outer_context;
7529 while (ctx);
7532 /* Similarly for each of the type sizes of TYPE. */
7534 static void
7535 omp_firstprivatize_type_sizes (struct gimplify_omp_ctx *ctx, tree type)
7537 if (type == NULL || type == error_mark_node)
7538 return;
7539 type = TYPE_MAIN_VARIANT (type);
7541 if (ctx->privatized_types->add (type))
7542 return;
7544 switch (TREE_CODE (type))
7546 case INTEGER_TYPE:
7547 case ENUMERAL_TYPE:
7548 case BOOLEAN_TYPE:
7549 case REAL_TYPE:
7550 case FIXED_POINT_TYPE:
7551 omp_firstprivatize_variable (ctx, TYPE_MIN_VALUE (type));
7552 omp_firstprivatize_variable (ctx, TYPE_MAX_VALUE (type));
7553 break;
7555 case ARRAY_TYPE:
7556 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
7557 omp_firstprivatize_type_sizes (ctx, TYPE_DOMAIN (type));
7558 break;
7560 case RECORD_TYPE:
7561 case UNION_TYPE:
7562 case QUAL_UNION_TYPE:
7564 tree field;
7565 for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
7566 if (TREE_CODE (field) == FIELD_DECL)
7568 omp_firstprivatize_variable (ctx, DECL_FIELD_OFFSET (field));
7569 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (field));
7572 break;
7574 case POINTER_TYPE:
7575 case REFERENCE_TYPE:
7576 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
7577 break;
7579 default:
7580 break;
7583 omp_firstprivatize_variable (ctx, TYPE_SIZE (type));
7584 omp_firstprivatize_variable (ctx, TYPE_SIZE_UNIT (type));
7585 lang_hooks.types.omp_firstprivatize_type_sizes (ctx, type);
7588 /* Add an entry for DECL in the OMP context CTX with FLAGS. */
7590 static void
7591 omp_add_variable (struct gimplify_omp_ctx *ctx, tree decl, unsigned int flags)
7593 splay_tree_node n;
7594 unsigned int nflags;
7595 tree t;
7597 if (error_operand_p (decl) || ctx->region_type == ORT_NONE)
7598 return;
7600 /* Never elide decls whose type has TREE_ADDRESSABLE set. This means
7601 there are constructors involved somewhere. Exception is a shared clause,
7602 there is nothing privatized in that case. */
7603 if ((flags & GOVD_SHARED) == 0
7604 && (TREE_ADDRESSABLE (TREE_TYPE (decl))
7605 || TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (decl))))
7606 flags |= GOVD_SEEN;
7608 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7609 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
7611 /* We shouldn't be re-adding the decl with the same data
7612 sharing class. */
7613 gcc_assert ((n->value & GOVD_DATA_SHARE_CLASS & flags) == 0);
7614 nflags = n->value | flags;
7615 /* The only combination of data sharing classes we should see is
7616 FIRSTPRIVATE and LASTPRIVATE. However, OpenACC permits
7617 reduction variables to be used in data sharing clauses. */
7618 gcc_assert ((ctx->region_type & ORT_ACC) != 0
7619 || ((nflags & GOVD_DATA_SHARE_CLASS)
7620 == (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE))
7621 || (flags & GOVD_DATA_SHARE_CLASS) == 0);
7622 n->value = nflags;
7623 return;
7626 /* When adding a variable-sized variable, we have to handle all sorts
7627 of additional bits of data: the pointer replacement variable, and
7628 the parameters of the type. */
7629 if (DECL_SIZE (decl) && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
7631 /* Add the pointer replacement variable as PRIVATE if the variable
7632 replacement is private, else FIRSTPRIVATE since we'll need the
7633 address of the original variable either for SHARED, or for the
7634 copy into or out of the context. */
7635 if (!(flags & GOVD_LOCAL) && ctx->region_type != ORT_TASKGROUP)
7637 if (flags & GOVD_MAP)
7638 nflags = GOVD_MAP | GOVD_MAP_TO_ONLY | GOVD_EXPLICIT;
7639 else if (flags & GOVD_PRIVATE)
7640 nflags = GOVD_PRIVATE;
7641 else if (((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0
7642 && (flags & GOVD_FIRSTPRIVATE))
7643 || (ctx->region_type == ORT_TARGET_DATA
7644 && (flags & GOVD_DATA_SHARE_CLASS) == 0))
7645 nflags = GOVD_PRIVATE | GOVD_EXPLICIT;
7646 else
7647 nflags = GOVD_FIRSTPRIVATE;
7648 nflags |= flags & GOVD_SEEN;
7649 t = DECL_VALUE_EXPR (decl);
7650 gcc_assert (INDIRECT_REF_P (t));
7651 t = TREE_OPERAND (t, 0);
7652 gcc_assert (DECL_P (t));
7653 omp_add_variable (ctx, t, nflags);
7656 /* Add all of the variable and type parameters (which should have
7657 been gimplified to a formal temporary) as FIRSTPRIVATE. */
7658 omp_firstprivatize_variable (ctx, DECL_SIZE_UNIT (decl));
7659 omp_firstprivatize_variable (ctx, DECL_SIZE (decl));
7660 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
7662 /* The variable-sized variable itself is never SHARED, only some form
7663 of PRIVATE. The sharing would take place via the pointer variable
7664 which we remapped above. */
7665 if (flags & GOVD_SHARED)
7666 flags = GOVD_SHARED | GOVD_DEBUG_PRIVATE
7667 | (flags & (GOVD_SEEN | GOVD_EXPLICIT));
7669 /* We're going to make use of the TYPE_SIZE_UNIT at least in the
7670 alloca statement we generate for the variable, so make sure it
7671 is available. This isn't automatically needed for the SHARED
7672 case, since we won't be allocating local storage then.
7673 For local variables TYPE_SIZE_UNIT might not be gimplified yet,
7674 in this case omp_notice_variable will be called later
7675 on when it is gimplified. */
7676 else if (! (flags & (GOVD_LOCAL | GOVD_MAP))
7677 && DECL_P (TYPE_SIZE_UNIT (TREE_TYPE (decl))))
7678 omp_notice_variable (ctx, TYPE_SIZE_UNIT (TREE_TYPE (decl)), true);
7680 else if ((flags & (GOVD_MAP | GOVD_LOCAL)) == 0
7681 && omp_privatize_by_reference (decl))
7683 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
7685 /* Similar to the direct variable sized case above, we'll need the
7686 size of references being privatized. */
7687 if ((flags & GOVD_SHARED) == 0)
7689 t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
7690 if (t && DECL_P (t))
7691 omp_notice_variable (ctx, t, true);
7695 if (n != NULL)
7696 n->value |= flags;
7697 else
7698 splay_tree_insert (ctx->variables, (splay_tree_key)decl, flags);
7700 /* For reductions clauses in OpenACC loop directives, by default create a
7701 copy clause on the enclosing parallel construct for carrying back the
7702 results. */
7703 if (ctx->region_type == ORT_ACC && (flags & GOVD_REDUCTION))
7705 struct gimplify_omp_ctx *outer_ctx = ctx->outer_context;
7706 while (outer_ctx)
7708 n = splay_tree_lookup (outer_ctx->variables, (splay_tree_key)decl);
7709 if (n != NULL)
7711 /* Ignore local variables and explicitly declared clauses. */
7712 if (n->value & (GOVD_LOCAL | GOVD_EXPLICIT))
7713 break;
7714 else if (outer_ctx->region_type == ORT_ACC_KERNELS)
7716 /* According to the OpenACC spec, such a reduction variable
7717 should already have a copy map on a kernels construct,
7718 verify that here. */
7719 gcc_assert (!(n->value & GOVD_FIRSTPRIVATE)
7720 && (n->value & GOVD_MAP));
7722 else if (outer_ctx->region_type == ORT_ACC_PARALLEL)
7724 /* Remove firstprivate and make it a copy map. */
7725 n->value &= ~GOVD_FIRSTPRIVATE;
7726 n->value |= GOVD_MAP;
7729 else if (outer_ctx->region_type == ORT_ACC_PARALLEL)
7731 splay_tree_insert (outer_ctx->variables, (splay_tree_key)decl,
7732 GOVD_MAP | GOVD_SEEN);
7733 break;
7735 outer_ctx = outer_ctx->outer_context;
7740 /* Notice a threadprivate variable DECL used in OMP context CTX.
7741 This just prints out diagnostics about threadprivate variable uses
7742 in untied tasks. If DECL2 is non-NULL, prevent this warning
7743 on that variable. */
7745 static bool
7746 omp_notice_threadprivate_variable (struct gimplify_omp_ctx *ctx, tree decl,
7747 tree decl2)
7749 splay_tree_node n;
7750 struct gimplify_omp_ctx *octx;
7752 for (octx = ctx; octx; octx = octx->outer_context)
7753 if ((octx->region_type & ORT_TARGET) != 0
7754 || octx->order_concurrent)
7756 n = splay_tree_lookup (octx->variables, (splay_tree_key)decl);
7757 if (n == NULL)
7759 if (octx->order_concurrent)
7761 error ("threadprivate variable %qE used in a region with"
7762 " %<order(concurrent)%> clause", DECL_NAME (decl));
7763 inform (octx->location, "enclosing region");
7765 else
7767 error ("threadprivate variable %qE used in target region",
7768 DECL_NAME (decl));
7769 inform (octx->location, "enclosing target region");
7771 splay_tree_insert (octx->variables, (splay_tree_key)decl, 0);
7773 if (decl2)
7774 splay_tree_insert (octx->variables, (splay_tree_key)decl2, 0);
7777 if (ctx->region_type != ORT_UNTIED_TASK)
7778 return false;
7779 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7780 if (n == NULL)
7782 error ("threadprivate variable %qE used in untied task",
7783 DECL_NAME (decl));
7784 inform (ctx->location, "enclosing task");
7785 splay_tree_insert (ctx->variables, (splay_tree_key)decl, 0);
7787 if (decl2)
7788 splay_tree_insert (ctx->variables, (splay_tree_key)decl2, 0);
7789 return false;
7792 /* Return true if global var DECL is device resident. */
7794 static bool
7795 device_resident_p (tree decl)
7797 tree attr = lookup_attribute ("oacc declare target", DECL_ATTRIBUTES (decl));
7799 if (!attr)
7800 return false;
7802 for (tree t = TREE_VALUE (attr); t; t = TREE_PURPOSE (t))
7804 tree c = TREE_VALUE (t);
7805 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_DEVICE_RESIDENT)
7806 return true;
7809 return false;
7812 /* Return true if DECL has an ACC DECLARE attribute. */
7814 static bool
7815 is_oacc_declared (tree decl)
7817 tree t = TREE_CODE (decl) == MEM_REF ? TREE_OPERAND (decl, 0) : decl;
7818 tree declared = lookup_attribute ("oacc declare target", DECL_ATTRIBUTES (t));
7819 return declared != NULL_TREE;
7822 /* Determine outer default flags for DECL mentioned in an OMP region
7823 but not declared in an enclosing clause.
7825 ??? Some compiler-generated variables (like SAVE_EXPRs) could be
7826 remapped firstprivate instead of shared. To some extent this is
7827 addressed in omp_firstprivatize_type_sizes, but not
7828 effectively. */
7830 static unsigned
7831 omp_default_clause (struct gimplify_omp_ctx *ctx, tree decl,
7832 bool in_code, unsigned flags)
7834 enum omp_clause_default_kind default_kind = ctx->default_kind;
7835 enum omp_clause_default_kind kind;
7837 kind = lang_hooks.decls.omp_predetermined_sharing (decl);
7838 if (ctx->region_type & ORT_TASK)
7840 tree detach_clause = omp_find_clause (ctx->clauses, OMP_CLAUSE_DETACH);
7842 /* The event-handle specified by a detach clause should always be firstprivate,
7843 regardless of the current default. */
7844 if (detach_clause && OMP_CLAUSE_DECL (detach_clause) == decl)
7845 kind = OMP_CLAUSE_DEFAULT_FIRSTPRIVATE;
7847 if (kind != OMP_CLAUSE_DEFAULT_UNSPECIFIED)
7848 default_kind = kind;
7849 else if (VAR_P (decl) && TREE_STATIC (decl) && DECL_IN_CONSTANT_POOL (decl))
7850 default_kind = OMP_CLAUSE_DEFAULT_SHARED;
7851 /* For C/C++ default({,first}private), variables with static storage duration
7852 declared in a namespace or global scope and referenced in construct
7853 must be explicitly specified, i.e. acts as default(none). */
7854 else if ((default_kind == OMP_CLAUSE_DEFAULT_PRIVATE
7855 || default_kind == OMP_CLAUSE_DEFAULT_FIRSTPRIVATE)
7856 && VAR_P (decl)
7857 && is_global_var (decl)
7858 && (DECL_FILE_SCOPE_P (decl)
7859 || (DECL_CONTEXT (decl)
7860 && TREE_CODE (DECL_CONTEXT (decl)) == NAMESPACE_DECL))
7861 && !lang_GNU_Fortran ())
7862 default_kind = OMP_CLAUSE_DEFAULT_NONE;
7864 switch (default_kind)
7866 case OMP_CLAUSE_DEFAULT_NONE:
7868 const char *rtype;
7870 if (ctx->region_type & ORT_PARALLEL)
7871 rtype = "parallel";
7872 else if ((ctx->region_type & ORT_TASKLOOP) == ORT_TASKLOOP)
7873 rtype = "taskloop";
7874 else if (ctx->region_type & ORT_TASK)
7875 rtype = "task";
7876 else if (ctx->region_type & ORT_TEAMS)
7877 rtype = "teams";
7878 else
7879 gcc_unreachable ();
7881 error ("%qE not specified in enclosing %qs",
7882 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)), rtype);
7883 inform (ctx->location, "enclosing %qs", rtype);
7885 /* FALLTHRU */
7886 case OMP_CLAUSE_DEFAULT_SHARED:
7887 flags |= GOVD_SHARED;
7888 break;
7889 case OMP_CLAUSE_DEFAULT_PRIVATE:
7890 flags |= GOVD_PRIVATE;
7891 break;
7892 case OMP_CLAUSE_DEFAULT_FIRSTPRIVATE:
7893 flags |= GOVD_FIRSTPRIVATE;
7894 break;
7895 case OMP_CLAUSE_DEFAULT_UNSPECIFIED:
7896 /* decl will be either GOVD_FIRSTPRIVATE or GOVD_SHARED. */
7897 gcc_assert ((ctx->region_type & ORT_TASK) != 0);
7898 if (struct gimplify_omp_ctx *octx = ctx->outer_context)
7900 omp_notice_variable (octx, decl, in_code);
7901 for (; octx; octx = octx->outer_context)
7903 splay_tree_node n2;
7905 n2 = splay_tree_lookup (octx->variables, (splay_tree_key) decl);
7906 if ((octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)) != 0
7907 && (n2 == NULL || (n2->value & GOVD_DATA_SHARE_CLASS) == 0))
7908 continue;
7909 if (n2 && (n2->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED)
7911 flags |= GOVD_FIRSTPRIVATE;
7912 goto found_outer;
7914 if ((octx->region_type & (ORT_PARALLEL | ORT_TEAMS)) != 0)
7916 flags |= GOVD_SHARED;
7917 goto found_outer;
7922 if (TREE_CODE (decl) == PARM_DECL
7923 || (!is_global_var (decl)
7924 && DECL_CONTEXT (decl) == current_function_decl))
7925 flags |= GOVD_FIRSTPRIVATE;
7926 else
7927 flags |= GOVD_SHARED;
7928 found_outer:
7929 break;
7931 default:
7932 gcc_unreachable ();
7935 return flags;
7938 /* Return string name for types of OpenACC constructs from ORT_* values. */
7940 static const char *
7941 oacc_region_type_name (enum omp_region_type region_type)
7943 switch (region_type)
7945 case ORT_ACC_DATA:
7946 return "data";
7947 case ORT_ACC_PARALLEL:
7948 return "parallel";
7949 case ORT_ACC_KERNELS:
7950 return "kernels";
7951 case ORT_ACC_SERIAL:
7952 return "serial";
7953 default:
7954 gcc_unreachable ();
7958 /* Determine outer default flags for DECL mentioned in an OACC region
7959 but not declared in an enclosing clause. */
7961 static unsigned
7962 oacc_default_clause (struct gimplify_omp_ctx *ctx, tree decl, unsigned flags)
7964 struct gimplify_omp_ctx *ctx_default = ctx;
7965 /* If no 'default' clause appears on this compute construct... */
7966 if (ctx_default->default_kind == OMP_CLAUSE_DEFAULT_SHARED)
7968 /* ..., see if one appears on a lexically containing 'data'
7969 construct. */
7970 while ((ctx_default = ctx_default->outer_context))
7972 if (ctx_default->region_type == ORT_ACC_DATA
7973 && ctx_default->default_kind != OMP_CLAUSE_DEFAULT_SHARED)
7974 break;
7976 /* If not, reset. */
7977 if (!ctx_default)
7978 ctx_default = ctx;
7981 bool on_device = false;
7982 bool is_private = false;
7983 bool declared = is_oacc_declared (decl);
7984 tree type = TREE_TYPE (decl);
7986 if (omp_privatize_by_reference (decl))
7987 type = TREE_TYPE (type);
7989 /* For Fortran COMMON blocks, only used variables in those blocks are
7990 transfered and remapped. The block itself will have a private clause to
7991 avoid transfering the data twice.
7992 The hook evaluates to false by default. For a variable in Fortran's COMMON
7993 or EQUIVALENCE block, returns 'true' (as we have shared=false) - as only
7994 the variables in such a COMMON/EQUIVALENCE block shall be privatized not
7995 the whole block. For C++ and Fortran, it can also be true under certain
7996 other conditions, if DECL_HAS_VALUE_EXPR. */
7997 if (RECORD_OR_UNION_TYPE_P (type))
7998 is_private = lang_hooks.decls.omp_disregard_value_expr (decl, false);
8000 if ((ctx->region_type & (ORT_ACC_PARALLEL | ORT_ACC_KERNELS)) != 0
8001 && is_global_var (decl)
8002 && device_resident_p (decl)
8003 && !is_private)
8005 on_device = true;
8006 flags |= GOVD_MAP_TO_ONLY;
8009 switch (ctx->region_type)
8011 case ORT_ACC_KERNELS:
8012 if (is_private)
8013 flags |= GOVD_FIRSTPRIVATE;
8014 else if (AGGREGATE_TYPE_P (type))
8016 /* Aggregates default to 'present_or_copy', or 'present'. */
8017 if (ctx_default->default_kind != OMP_CLAUSE_DEFAULT_PRESENT)
8018 flags |= GOVD_MAP;
8019 else
8020 flags |= GOVD_MAP | GOVD_MAP_FORCE_PRESENT;
8022 else
8023 /* Scalars default to 'copy'. */
8024 flags |= GOVD_MAP | GOVD_MAP_FORCE;
8026 break;
8028 case ORT_ACC_PARALLEL:
8029 case ORT_ACC_SERIAL:
8030 if (is_private)
8031 flags |= GOVD_FIRSTPRIVATE;
8032 else if (on_device || declared)
8033 flags |= GOVD_MAP;
8034 else if (AGGREGATE_TYPE_P (type))
8036 /* Aggregates default to 'present_or_copy', or 'present'. */
8037 if (ctx_default->default_kind != OMP_CLAUSE_DEFAULT_PRESENT)
8038 flags |= GOVD_MAP;
8039 else
8040 flags |= GOVD_MAP | GOVD_MAP_FORCE_PRESENT;
8042 else
8043 /* Scalars default to 'firstprivate'. */
8044 flags |= GOVD_FIRSTPRIVATE;
8046 break;
8048 default:
8049 gcc_unreachable ();
8052 if (DECL_ARTIFICIAL (decl))
8053 ; /* We can get compiler-generated decls, and should not complain
8054 about them. */
8055 else if (ctx_default->default_kind == OMP_CLAUSE_DEFAULT_NONE)
8057 error ("%qE not specified in enclosing OpenACC %qs construct",
8058 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)),
8059 oacc_region_type_name (ctx->region_type));
8060 if (ctx_default != ctx)
8061 inform (ctx->location, "enclosing OpenACC %qs construct and",
8062 oacc_region_type_name (ctx->region_type));
8063 inform (ctx_default->location,
8064 "enclosing OpenACC %qs construct with %qs clause",
8065 oacc_region_type_name (ctx_default->region_type),
8066 "default(none)");
8068 else if (ctx_default->default_kind == OMP_CLAUSE_DEFAULT_PRESENT)
8069 ; /* Handled above. */
8070 else
8071 gcc_checking_assert (ctx_default->default_kind == OMP_CLAUSE_DEFAULT_SHARED);
8073 return flags;
8076 /* Record the fact that DECL was used within the OMP context CTX.
8077 IN_CODE is true when real code uses DECL, and false when we should
8078 merely emit default(none) errors. Return true if DECL is going to
8079 be remapped and thus DECL shouldn't be gimplified into its
8080 DECL_VALUE_EXPR (if any). */
8082 static bool
8083 omp_notice_variable (struct gimplify_omp_ctx *ctx, tree decl, bool in_code)
8085 splay_tree_node n;
8086 unsigned flags = in_code ? GOVD_SEEN : 0;
8087 bool ret = false, shared;
8089 if (error_operand_p (decl))
8090 return false;
8092 if (DECL_ARTIFICIAL (decl))
8094 tree attr = lookup_attribute ("omp allocate var", DECL_ATTRIBUTES (decl));
8095 if (attr)
8096 decl = TREE_VALUE (TREE_VALUE (attr));
8099 if (ctx->region_type == ORT_NONE)
8100 return lang_hooks.decls.omp_disregard_value_expr (decl, false);
8102 if (is_global_var (decl))
8104 /* Threadprivate variables are predetermined. */
8105 if (DECL_THREAD_LOCAL_P (decl))
8106 return omp_notice_threadprivate_variable (ctx, decl, NULL_TREE);
8108 if (DECL_HAS_VALUE_EXPR_P (decl))
8110 if (ctx->region_type & ORT_ACC)
8111 /* For OpenACC, defer expansion of value to avoid transfering
8112 privatized common block data instead of im-/explicitly transfered
8113 variables which are in common blocks. */
8115 else
8117 tree value = get_base_address (DECL_VALUE_EXPR (decl));
8119 if (value && DECL_P (value) && DECL_THREAD_LOCAL_P (value))
8120 return omp_notice_threadprivate_variable (ctx, decl, value);
8124 if (gimplify_omp_ctxp->outer_context == NULL
8125 && VAR_P (decl)
8126 && oacc_get_fn_attrib (current_function_decl))
8128 location_t loc = DECL_SOURCE_LOCATION (decl);
8130 if (lookup_attribute ("omp declare target link",
8131 DECL_ATTRIBUTES (decl)))
8133 error_at (loc,
8134 "%qE with %<link%> clause used in %<routine%> function",
8135 DECL_NAME (decl));
8136 return false;
8138 else if (!lookup_attribute ("omp declare target",
8139 DECL_ATTRIBUTES (decl)))
8141 error_at (loc,
8142 "%qE requires a %<declare%> directive for use "
8143 "in a %<routine%> function", DECL_NAME (decl));
8144 return false;
8149 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
8150 if ((ctx->region_type & ORT_TARGET) != 0)
8152 if (n == NULL)
8154 unsigned nflags = flags;
8155 if ((ctx->region_type & ORT_ACC) == 0)
8157 bool is_declare_target = false;
8158 if (is_global_var (decl)
8159 && varpool_node::get_create (decl)->offloadable)
8161 struct gimplify_omp_ctx *octx;
8162 for (octx = ctx->outer_context;
8163 octx; octx = octx->outer_context)
8165 n = splay_tree_lookup (octx->variables,
8166 (splay_tree_key)decl);
8167 if (n
8168 && (n->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED
8169 && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
8170 break;
8172 is_declare_target = octx == NULL;
8174 if (!is_declare_target)
8176 int gdmk;
8177 enum omp_clause_defaultmap_kind kind;
8178 if (lang_hooks.decls.omp_allocatable_p (decl))
8179 gdmk = GDMK_ALLOCATABLE;
8180 else if (lang_hooks.decls.omp_scalar_target_p (decl))
8181 gdmk = GDMK_SCALAR_TARGET;
8182 else if (lang_hooks.decls.omp_scalar_p (decl, false))
8183 gdmk = GDMK_SCALAR;
8184 else if (TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE
8185 || (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
8186 && (TREE_CODE (TREE_TYPE (TREE_TYPE (decl)))
8187 == POINTER_TYPE)))
8188 gdmk = GDMK_POINTER;
8189 else
8190 gdmk = GDMK_AGGREGATE;
8191 kind = lang_hooks.decls.omp_predetermined_mapping (decl);
8192 if (kind != OMP_CLAUSE_DEFAULTMAP_CATEGORY_UNSPECIFIED)
8194 if (kind == OMP_CLAUSE_DEFAULTMAP_FIRSTPRIVATE)
8195 nflags |= GOVD_FIRSTPRIVATE;
8196 else if (kind == OMP_CLAUSE_DEFAULTMAP_TO)
8197 nflags |= GOVD_MAP | GOVD_MAP_TO_ONLY;
8198 else
8199 gcc_unreachable ();
8201 else if (ctx->defaultmap[gdmk] == 0)
8203 tree d = lang_hooks.decls.omp_report_decl (decl);
8204 error ("%qE not specified in enclosing %<target%>",
8205 DECL_NAME (d));
8206 inform (ctx->location, "enclosing %<target%>");
8208 else if (ctx->defaultmap[gdmk]
8209 & (GOVD_MAP_0LEN_ARRAY | GOVD_FIRSTPRIVATE))
8210 nflags |= ctx->defaultmap[gdmk];
8211 else if (ctx->defaultmap[gdmk] & GOVD_MAP_FORCE_PRESENT)
8213 gcc_assert (ctx->defaultmap[gdmk] & GOVD_MAP);
8214 nflags |= ctx->defaultmap[gdmk] | GOVD_MAP_ALLOC_ONLY;
8216 else
8218 gcc_assert (ctx->defaultmap[gdmk] & GOVD_MAP);
8219 nflags |= ctx->defaultmap[gdmk] & ~GOVD_MAP;
8224 struct gimplify_omp_ctx *octx = ctx->outer_context;
8225 if ((ctx->region_type & ORT_ACC) && octx)
8227 /* Look in outer OpenACC contexts, to see if there's a
8228 data attribute for this variable. */
8229 omp_notice_variable (octx, decl, in_code);
8231 for (; octx; octx = octx->outer_context)
8233 if (!(octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)))
8234 break;
8235 splay_tree_node n2
8236 = splay_tree_lookup (octx->variables,
8237 (splay_tree_key) decl);
8238 if (n2)
8240 if (octx->region_type == ORT_ACC_HOST_DATA)
8241 error ("variable %qE declared in enclosing "
8242 "%<host_data%> region", DECL_NAME (decl));
8243 nflags |= GOVD_MAP;
8244 if (octx->region_type == ORT_ACC_DATA
8245 && (n2->value & GOVD_MAP_0LEN_ARRAY))
8246 nflags |= GOVD_MAP_0LEN_ARRAY;
8247 goto found_outer;
8252 if ((nflags & ~(GOVD_MAP_TO_ONLY | GOVD_MAP_FROM_ONLY
8253 | GOVD_MAP_ALLOC_ONLY)) == flags)
8255 tree type = TREE_TYPE (decl);
8257 if (gimplify_omp_ctxp->target_firstprivatize_array_bases
8258 && omp_privatize_by_reference (decl))
8259 type = TREE_TYPE (type);
8260 if (!omp_mappable_type (type))
8262 error ("%qD referenced in target region does not have "
8263 "a mappable type", decl);
8264 nflags |= GOVD_MAP | GOVD_EXPLICIT;
8266 else
8268 if ((ctx->region_type & ORT_ACC) != 0)
8269 nflags = oacc_default_clause (ctx, decl, flags);
8270 else
8271 nflags |= GOVD_MAP;
8274 found_outer:
8275 omp_add_variable (ctx, decl, nflags);
8276 if (ctx->region_type & ORT_ACC)
8277 /* For OpenACC, as remarked above, defer expansion. */
8278 shared = false;
8279 else
8280 shared = (nflags & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE)) == 0;
8281 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
8283 else
8285 if (ctx->region_type & ORT_ACC)
8286 /* For OpenACC, as remarked above, defer expansion. */
8287 shared = false;
8288 else
8289 shared = ((n->value | flags)
8290 & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE)) == 0;
8291 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
8292 /* If nothing changed, there's nothing left to do. */
8293 if ((n->value & flags) == flags)
8294 return ret;
8295 flags |= n->value;
8296 n->value = flags;
8298 goto do_outer;
8301 if (n == NULL)
8303 if (ctx->region_type == ORT_WORKSHARE
8304 || ctx->region_type == ORT_TASKGROUP
8305 || ctx->region_type == ORT_SIMD
8306 || ctx->region_type == ORT_ACC
8307 || (ctx->region_type & ORT_TARGET_DATA) != 0)
8308 goto do_outer;
8310 flags = omp_default_clause (ctx, decl, in_code, flags);
8312 if ((flags & GOVD_PRIVATE)
8313 && lang_hooks.decls.omp_private_outer_ref (decl))
8314 flags |= GOVD_PRIVATE_OUTER_REF;
8316 omp_add_variable (ctx, decl, flags);
8318 shared = (flags & GOVD_SHARED) != 0;
8319 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
8320 goto do_outer;
8323 /* Don't mark as GOVD_SEEN addressable temporaries seen only in simd
8324 lb, b or incr expressions, those shouldn't be turned into simd arrays. */
8325 if (ctx->region_type == ORT_SIMD
8326 && ctx->in_for_exprs
8327 && ((n->value & (GOVD_PRIVATE | GOVD_SEEN | GOVD_EXPLICIT))
8328 == GOVD_PRIVATE))
8329 flags &= ~GOVD_SEEN;
8331 if ((n->value & (GOVD_SEEN | GOVD_LOCAL)) == 0
8332 && (flags & (GOVD_SEEN | GOVD_LOCAL)) == GOVD_SEEN
8333 && DECL_SIZE (decl))
8335 if (TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
8337 splay_tree_node n2;
8338 tree t = DECL_VALUE_EXPR (decl);
8339 gcc_assert (INDIRECT_REF_P (t));
8340 t = TREE_OPERAND (t, 0);
8341 gcc_assert (DECL_P (t));
8342 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
8343 n2->value |= GOVD_SEEN;
8345 else if (omp_privatize_by_reference (decl)
8346 && TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)))
8347 && (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl))))
8348 != INTEGER_CST))
8350 splay_tree_node n2;
8351 tree t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
8352 gcc_assert (DECL_P (t));
8353 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
8354 if (n2)
8355 omp_notice_variable (ctx, t, true);
8359 if (ctx->region_type & ORT_ACC)
8360 /* For OpenACC, as remarked above, defer expansion. */
8361 shared = false;
8362 else
8363 shared = ((flags | n->value) & GOVD_SHARED) != 0;
8364 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
8366 /* If nothing changed, there's nothing left to do. */
8367 if ((n->value & flags) == flags)
8368 return ret;
8369 flags |= n->value;
8370 n->value = flags;
8372 do_outer:
8373 /* If the variable is private in the current context, then we don't
8374 need to propagate anything to an outer context. */
8375 if ((flags & GOVD_PRIVATE) && !(flags & GOVD_PRIVATE_OUTER_REF))
8376 return ret;
8377 if ((flags & (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
8378 == (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
8379 return ret;
8380 if ((flags & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
8381 | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
8382 == (GOVD_LASTPRIVATE | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
8383 return ret;
8384 if (ctx->outer_context
8385 && omp_notice_variable (ctx->outer_context, decl, in_code))
8386 return true;
8387 return ret;
8390 /* Verify that DECL is private within CTX. If there's specific information
8391 to the contrary in the innermost scope, generate an error. */
8393 static bool
8394 omp_is_private (struct gimplify_omp_ctx *ctx, tree decl, int simd)
8396 splay_tree_node n;
8398 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
8399 if (n != NULL)
8401 if (n->value & GOVD_SHARED)
8403 if (ctx == gimplify_omp_ctxp)
8405 if (simd)
8406 error ("iteration variable %qE is predetermined linear",
8407 DECL_NAME (decl));
8408 else
8409 error ("iteration variable %qE should be private",
8410 DECL_NAME (decl));
8411 n->value = GOVD_PRIVATE;
8412 return true;
8414 else
8415 return false;
8417 else if ((n->value & GOVD_EXPLICIT) != 0
8418 && (ctx == gimplify_omp_ctxp
8419 || (ctx->region_type == ORT_COMBINED_PARALLEL
8420 && gimplify_omp_ctxp->outer_context == ctx)))
8422 if ((n->value & GOVD_FIRSTPRIVATE) != 0)
8423 error ("iteration variable %qE should not be firstprivate",
8424 DECL_NAME (decl));
8425 else if ((n->value & GOVD_REDUCTION) != 0)
8426 error ("iteration variable %qE should not be reduction",
8427 DECL_NAME (decl));
8428 else if (simd != 1 && (n->value & GOVD_LINEAR) != 0)
8429 error ("iteration variable %qE should not be linear",
8430 DECL_NAME (decl));
8432 return (ctx == gimplify_omp_ctxp
8433 || (ctx->region_type == ORT_COMBINED_PARALLEL
8434 && gimplify_omp_ctxp->outer_context == ctx));
8437 if (ctx->region_type != ORT_WORKSHARE
8438 && ctx->region_type != ORT_TASKGROUP
8439 && ctx->region_type != ORT_SIMD
8440 && ctx->region_type != ORT_ACC)
8441 return false;
8442 else if (ctx->outer_context)
8443 return omp_is_private (ctx->outer_context, decl, simd);
8444 return false;
8447 /* Return true if DECL is private within a parallel region
8448 that binds to the current construct's context or in parallel
8449 region's REDUCTION clause. */
8451 static bool
8452 omp_check_private (struct gimplify_omp_ctx *ctx, tree decl, bool copyprivate)
8454 splay_tree_node n;
8458 ctx = ctx->outer_context;
8459 if (ctx == NULL)
8461 if (is_global_var (decl))
8462 return false;
8464 /* References might be private, but might be shared too,
8465 when checking for copyprivate, assume they might be
8466 private, otherwise assume they might be shared. */
8467 if (copyprivate)
8468 return true;
8470 if (omp_privatize_by_reference (decl))
8471 return false;
8473 /* Treat C++ privatized non-static data members outside
8474 of the privatization the same. */
8475 if (omp_member_access_dummy_var (decl))
8476 return false;
8478 return true;
8481 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
8483 if ((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0
8484 && (n == NULL || (n->value & GOVD_DATA_SHARE_CLASS) == 0))
8486 if ((ctx->region_type & ORT_TARGET_DATA) != 0
8487 || n == NULL
8488 || (n->value & GOVD_MAP) == 0)
8489 continue;
8490 return false;
8493 if (n != NULL)
8495 if ((n->value & GOVD_LOCAL) != 0
8496 && omp_member_access_dummy_var (decl))
8497 return false;
8498 return (n->value & GOVD_SHARED) == 0;
8501 if (ctx->region_type == ORT_WORKSHARE
8502 || ctx->region_type == ORT_TASKGROUP
8503 || ctx->region_type == ORT_SIMD
8504 || ctx->region_type == ORT_ACC)
8505 continue;
8507 break;
8509 while (1);
8510 return false;
8513 /* Callback for walk_tree to find a DECL_EXPR for the given DECL. */
8515 static tree
8516 find_decl_expr (tree *tp, int *walk_subtrees, void *data)
8518 tree t = *tp;
8520 /* If this node has been visited, unmark it and keep looking. */
8521 if (TREE_CODE (t) == DECL_EXPR && DECL_EXPR_DECL (t) == (tree) data)
8522 return t;
8524 if (IS_TYPE_OR_DECL_P (t))
8525 *walk_subtrees = 0;
8526 return NULL_TREE;
8530 /* Gimplify the affinity clause but effectively ignore it.
8531 Generate:
8532 var = begin;
8533 if ((step > 1) ? var <= end : var > end)
8534 locatator_var_expr; */
8536 static void
8537 gimplify_omp_affinity (tree *list_p, gimple_seq *pre_p)
8539 tree last_iter = NULL_TREE;
8540 tree last_bind = NULL_TREE;
8541 tree label = NULL_TREE;
8542 tree *last_body = NULL;
8543 for (tree c = *list_p; c; c = OMP_CLAUSE_CHAIN (c))
8544 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_AFFINITY)
8546 tree t = OMP_CLAUSE_DECL (c);
8547 if (TREE_CODE (t) == TREE_LIST
8548 && TREE_PURPOSE (t)
8549 && TREE_CODE (TREE_PURPOSE (t)) == TREE_VEC)
8551 if (TREE_VALUE (t) == null_pointer_node)
8552 continue;
8553 if (TREE_PURPOSE (t) != last_iter)
8555 if (last_bind)
8557 append_to_statement_list (label, last_body);
8558 gimplify_and_add (last_bind, pre_p);
8559 last_bind = NULL_TREE;
8561 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8563 if (gimplify_expr (&TREE_VEC_ELT (it, 1), pre_p, NULL,
8564 is_gimple_val, fb_rvalue) == GS_ERROR
8565 || gimplify_expr (&TREE_VEC_ELT (it, 2), pre_p, NULL,
8566 is_gimple_val, fb_rvalue) == GS_ERROR
8567 || gimplify_expr (&TREE_VEC_ELT (it, 3), pre_p, NULL,
8568 is_gimple_val, fb_rvalue) == GS_ERROR
8569 || (gimplify_expr (&TREE_VEC_ELT (it, 4), pre_p, NULL,
8570 is_gimple_val, fb_rvalue)
8571 == GS_ERROR))
8572 return;
8574 last_iter = TREE_PURPOSE (t);
8575 tree block = TREE_VEC_ELT (TREE_PURPOSE (t), 5);
8576 last_bind = build3 (BIND_EXPR, void_type_node, BLOCK_VARS (block),
8577 NULL, block);
8578 last_body = &BIND_EXPR_BODY (last_bind);
8579 tree cond = NULL_TREE;
8580 location_t loc = OMP_CLAUSE_LOCATION (c);
8581 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8583 tree var = TREE_VEC_ELT (it, 0);
8584 tree begin = TREE_VEC_ELT (it, 1);
8585 tree end = TREE_VEC_ELT (it, 2);
8586 tree step = TREE_VEC_ELT (it, 3);
8587 loc = DECL_SOURCE_LOCATION (var);
8588 tree tem = build2_loc (loc, MODIFY_EXPR, void_type_node,
8589 var, begin);
8590 append_to_statement_list_force (tem, last_body);
8592 tree cond1 = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8593 step, build_zero_cst (TREE_TYPE (step)));
8594 tree cond2 = fold_build2_loc (loc, LE_EXPR, boolean_type_node,
8595 var, end);
8596 tree cond3 = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8597 var, end);
8598 cond1 = fold_build3_loc (loc, COND_EXPR, boolean_type_node,
8599 cond1, cond2, cond3);
8600 if (cond)
8601 cond = fold_build2_loc (loc, TRUTH_AND_EXPR,
8602 boolean_type_node, cond, cond1);
8603 else
8604 cond = cond1;
8606 tree cont_label = create_artificial_label (loc);
8607 label = build1 (LABEL_EXPR, void_type_node, cont_label);
8608 tree tem = fold_build3_loc (loc, COND_EXPR, void_type_node, cond,
8609 void_node,
8610 build_and_jump (&cont_label));
8611 append_to_statement_list_force (tem, last_body);
8613 if (TREE_CODE (TREE_VALUE (t)) == COMPOUND_EXPR)
8615 append_to_statement_list (TREE_OPERAND (TREE_VALUE (t), 0),
8616 last_body);
8617 TREE_VALUE (t) = TREE_OPERAND (TREE_VALUE (t), 1);
8619 if (error_operand_p (TREE_VALUE (t)))
8620 return;
8621 append_to_statement_list_force (TREE_VALUE (t), last_body);
8622 TREE_VALUE (t) = null_pointer_node;
8624 else
8626 if (last_bind)
8628 append_to_statement_list (label, last_body);
8629 gimplify_and_add (last_bind, pre_p);
8630 last_bind = NULL_TREE;
8632 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
8634 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
8635 NULL, is_gimple_val, fb_rvalue);
8636 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
8638 if (error_operand_p (OMP_CLAUSE_DECL (c)))
8639 return;
8640 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
8641 is_gimple_lvalue, fb_lvalue) == GS_ERROR)
8642 return;
8643 gimplify_and_add (OMP_CLAUSE_DECL (c), pre_p);
8646 if (last_bind)
8648 append_to_statement_list (label, last_body);
8649 gimplify_and_add (last_bind, pre_p);
8651 return;
8654 /* If *LIST_P contains any OpenMP depend clauses with iterators,
8655 lower all the depend clauses by populating corresponding depend
8656 array. Returns 0 if there are no such depend clauses, or
8657 2 if all depend clauses should be removed, 1 otherwise. */
8659 static int
8660 gimplify_omp_depend (tree *list_p, gimple_seq *pre_p)
8662 tree c;
8663 gimple *g;
8664 size_t n[5] = { 0, 0, 0, 0, 0 };
8665 bool unused[5];
8666 tree counts[5] = { NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE };
8667 tree last_iter = NULL_TREE, last_count = NULL_TREE;
8668 size_t i, j;
8669 location_t first_loc = UNKNOWN_LOCATION;
8671 for (c = *list_p; c; c = OMP_CLAUSE_CHAIN (c))
8672 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND)
8674 switch (OMP_CLAUSE_DEPEND_KIND (c))
8676 case OMP_CLAUSE_DEPEND_IN:
8677 i = 2;
8678 break;
8679 case OMP_CLAUSE_DEPEND_OUT:
8680 case OMP_CLAUSE_DEPEND_INOUT:
8681 i = 0;
8682 break;
8683 case OMP_CLAUSE_DEPEND_MUTEXINOUTSET:
8684 i = 1;
8685 break;
8686 case OMP_CLAUSE_DEPEND_DEPOBJ:
8687 i = 3;
8688 break;
8689 case OMP_CLAUSE_DEPEND_INOUTSET:
8690 i = 4;
8691 break;
8692 default:
8693 gcc_unreachable ();
8695 tree t = OMP_CLAUSE_DECL (c);
8696 if (first_loc == UNKNOWN_LOCATION)
8697 first_loc = OMP_CLAUSE_LOCATION (c);
8698 if (TREE_CODE (t) == TREE_LIST
8699 && TREE_PURPOSE (t)
8700 && TREE_CODE (TREE_PURPOSE (t)) == TREE_VEC)
8702 if (TREE_PURPOSE (t) != last_iter)
8704 tree tcnt = size_one_node;
8705 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8707 if (gimplify_expr (&TREE_VEC_ELT (it, 1), pre_p, NULL,
8708 is_gimple_val, fb_rvalue) == GS_ERROR
8709 || gimplify_expr (&TREE_VEC_ELT (it, 2), pre_p, NULL,
8710 is_gimple_val, fb_rvalue) == GS_ERROR
8711 || gimplify_expr (&TREE_VEC_ELT (it, 3), pre_p, NULL,
8712 is_gimple_val, fb_rvalue) == GS_ERROR
8713 || (gimplify_expr (&TREE_VEC_ELT (it, 4), pre_p, NULL,
8714 is_gimple_val, fb_rvalue)
8715 == GS_ERROR))
8716 return 2;
8717 tree var = TREE_VEC_ELT (it, 0);
8718 tree begin = TREE_VEC_ELT (it, 1);
8719 tree end = TREE_VEC_ELT (it, 2);
8720 tree step = TREE_VEC_ELT (it, 3);
8721 tree orig_step = TREE_VEC_ELT (it, 4);
8722 tree type = TREE_TYPE (var);
8723 tree stype = TREE_TYPE (step);
8724 location_t loc = DECL_SOURCE_LOCATION (var);
8725 tree endmbegin;
8726 /* Compute count for this iterator as
8727 orig_step > 0
8728 ? (begin < end ? (end - begin + (step - 1)) / step : 0)
8729 : (begin > end ? (end - begin + (step + 1)) / step : 0)
8730 and compute product of those for the entire depend
8731 clause. */
8732 if (POINTER_TYPE_P (type))
8733 endmbegin = fold_build2_loc (loc, POINTER_DIFF_EXPR,
8734 stype, end, begin);
8735 else
8736 endmbegin = fold_build2_loc (loc, MINUS_EXPR, type,
8737 end, begin);
8738 tree stepm1 = fold_build2_loc (loc, MINUS_EXPR, stype,
8739 step,
8740 build_int_cst (stype, 1));
8741 tree stepp1 = fold_build2_loc (loc, PLUS_EXPR, stype, step,
8742 build_int_cst (stype, 1));
8743 tree pos = fold_build2_loc (loc, PLUS_EXPR, stype,
8744 unshare_expr (endmbegin),
8745 stepm1);
8746 pos = fold_build2_loc (loc, TRUNC_DIV_EXPR, stype,
8747 pos, step);
8748 tree neg = fold_build2_loc (loc, PLUS_EXPR, stype,
8749 endmbegin, stepp1);
8750 if (TYPE_UNSIGNED (stype))
8752 neg = fold_build1_loc (loc, NEGATE_EXPR, stype, neg);
8753 step = fold_build1_loc (loc, NEGATE_EXPR, stype, step);
8755 neg = fold_build2_loc (loc, TRUNC_DIV_EXPR, stype,
8756 neg, step);
8757 step = NULL_TREE;
8758 tree cond = fold_build2_loc (loc, LT_EXPR,
8759 boolean_type_node,
8760 begin, end);
8761 pos = fold_build3_loc (loc, COND_EXPR, stype, cond, pos,
8762 build_int_cst (stype, 0));
8763 cond = fold_build2_loc (loc, LT_EXPR, boolean_type_node,
8764 end, begin);
8765 neg = fold_build3_loc (loc, COND_EXPR, stype, cond, neg,
8766 build_int_cst (stype, 0));
8767 tree osteptype = TREE_TYPE (orig_step);
8768 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8769 orig_step,
8770 build_int_cst (osteptype, 0));
8771 tree cnt = fold_build3_loc (loc, COND_EXPR, stype,
8772 cond, pos, neg);
8773 cnt = fold_convert_loc (loc, sizetype, cnt);
8774 if (gimplify_expr (&cnt, pre_p, NULL, is_gimple_val,
8775 fb_rvalue) == GS_ERROR)
8776 return 2;
8777 tcnt = size_binop_loc (loc, MULT_EXPR, tcnt, cnt);
8779 if (gimplify_expr (&tcnt, pre_p, NULL, is_gimple_val,
8780 fb_rvalue) == GS_ERROR)
8781 return 2;
8782 last_iter = TREE_PURPOSE (t);
8783 last_count = tcnt;
8785 if (counts[i] == NULL_TREE)
8786 counts[i] = last_count;
8787 else
8788 counts[i] = size_binop_loc (OMP_CLAUSE_LOCATION (c),
8789 PLUS_EXPR, counts[i], last_count);
8791 else
8792 n[i]++;
8794 for (i = 0; i < 5; i++)
8795 if (counts[i])
8796 break;
8797 if (i == 5)
8798 return 0;
8800 tree total = size_zero_node;
8801 for (i = 0; i < 5; i++)
8803 unused[i] = counts[i] == NULL_TREE && n[i] == 0;
8804 if (counts[i] == NULL_TREE)
8805 counts[i] = size_zero_node;
8806 if (n[i])
8807 counts[i] = size_binop (PLUS_EXPR, counts[i], size_int (n[i]));
8808 if (gimplify_expr (&counts[i], pre_p, NULL, is_gimple_val,
8809 fb_rvalue) == GS_ERROR)
8810 return 2;
8811 total = size_binop (PLUS_EXPR, total, counts[i]);
8814 if (gimplify_expr (&total, pre_p, NULL, is_gimple_val, fb_rvalue)
8815 == GS_ERROR)
8816 return 2;
8817 bool is_old = unused[1] && unused[3] && unused[4];
8818 tree totalpx = size_binop (PLUS_EXPR, unshare_expr (total),
8819 size_int (is_old ? 1 : 4));
8820 if (!unused[4])
8821 totalpx = size_binop (PLUS_EXPR, totalpx,
8822 size_binop (MULT_EXPR, counts[4], size_int (2)));
8823 tree type = build_array_type (ptr_type_node, build_index_type (totalpx));
8824 tree array = create_tmp_var_raw (type);
8825 TREE_ADDRESSABLE (array) = 1;
8826 if (!poly_int_tree_p (totalpx))
8828 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (array)))
8829 gimplify_type_sizes (TREE_TYPE (array), pre_p);
8830 if (gimplify_omp_ctxp)
8832 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8833 while (ctx
8834 && (ctx->region_type == ORT_WORKSHARE
8835 || ctx->region_type == ORT_TASKGROUP
8836 || ctx->region_type == ORT_SIMD
8837 || ctx->region_type == ORT_ACC))
8838 ctx = ctx->outer_context;
8839 if (ctx)
8840 omp_add_variable (ctx, array, GOVD_LOCAL | GOVD_SEEN);
8842 gimplify_vla_decl (array, pre_p);
8844 else
8845 gimple_add_tmp_var (array);
8846 tree r = build4 (ARRAY_REF, ptr_type_node, array, size_int (0), NULL_TREE,
8847 NULL_TREE);
8848 tree tem;
8849 if (!is_old)
8851 tem = build2 (MODIFY_EXPR, void_type_node, r,
8852 build_int_cst (ptr_type_node, 0));
8853 gimplify_and_add (tem, pre_p);
8854 r = build4 (ARRAY_REF, ptr_type_node, array, size_int (1), NULL_TREE,
8855 NULL_TREE);
8857 tem = build2 (MODIFY_EXPR, void_type_node, r,
8858 fold_convert (ptr_type_node, total));
8859 gimplify_and_add (tem, pre_p);
8860 for (i = 1; i < (is_old ? 2 : 4); i++)
8862 r = build4 (ARRAY_REF, ptr_type_node, array, size_int (i + !is_old),
8863 NULL_TREE, NULL_TREE);
8864 tem = build2 (MODIFY_EXPR, void_type_node, r, counts[i - 1]);
8865 gimplify_and_add (tem, pre_p);
8868 tree cnts[6];
8869 for (j = 5; j; j--)
8870 if (!unused[j - 1])
8871 break;
8872 for (i = 0; i < 5; i++)
8874 if (i && (i >= j || unused[i - 1]))
8876 cnts[i] = cnts[i - 1];
8877 continue;
8879 cnts[i] = create_tmp_var (sizetype);
8880 if (i == 0)
8881 g = gimple_build_assign (cnts[i], size_int (is_old ? 2 : 5));
8882 else
8884 tree t;
8885 if (is_old)
8886 t = size_binop (PLUS_EXPR, counts[0], size_int (2));
8887 else
8888 t = size_binop (PLUS_EXPR, cnts[i - 1], counts[i - 1]);
8889 if (gimplify_expr (&t, pre_p, NULL, is_gimple_val, fb_rvalue)
8890 == GS_ERROR)
8891 return 2;
8892 g = gimple_build_assign (cnts[i], t);
8894 gimple_seq_add_stmt (pre_p, g);
8896 if (unused[4])
8897 cnts[5] = NULL_TREE;
8898 else
8900 tree t = size_binop (PLUS_EXPR, total, size_int (5));
8901 cnts[5] = create_tmp_var (sizetype);
8902 g = gimple_build_assign (cnts[i], t);
8903 gimple_seq_add_stmt (pre_p, g);
8906 last_iter = NULL_TREE;
8907 tree last_bind = NULL_TREE;
8908 tree *last_body = NULL;
8909 for (c = *list_p; c; c = OMP_CLAUSE_CHAIN (c))
8910 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND)
8912 switch (OMP_CLAUSE_DEPEND_KIND (c))
8914 case OMP_CLAUSE_DEPEND_IN:
8915 i = 2;
8916 break;
8917 case OMP_CLAUSE_DEPEND_OUT:
8918 case OMP_CLAUSE_DEPEND_INOUT:
8919 i = 0;
8920 break;
8921 case OMP_CLAUSE_DEPEND_MUTEXINOUTSET:
8922 i = 1;
8923 break;
8924 case OMP_CLAUSE_DEPEND_DEPOBJ:
8925 i = 3;
8926 break;
8927 case OMP_CLAUSE_DEPEND_INOUTSET:
8928 i = 4;
8929 break;
8930 default:
8931 gcc_unreachable ();
8933 tree t = OMP_CLAUSE_DECL (c);
8934 if (TREE_CODE (t) == TREE_LIST
8935 && TREE_PURPOSE (t)
8936 && TREE_CODE (TREE_PURPOSE (t)) == TREE_VEC)
8938 if (TREE_PURPOSE (t) != last_iter)
8940 if (last_bind)
8941 gimplify_and_add (last_bind, pre_p);
8942 tree block = TREE_VEC_ELT (TREE_PURPOSE (t), 5);
8943 last_bind = build3 (BIND_EXPR, void_type_node,
8944 BLOCK_VARS (block), NULL, block);
8945 TREE_SIDE_EFFECTS (last_bind) = 1;
8946 SET_EXPR_LOCATION (last_bind, OMP_CLAUSE_LOCATION (c));
8947 tree *p = &BIND_EXPR_BODY (last_bind);
8948 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8950 tree var = TREE_VEC_ELT (it, 0);
8951 tree begin = TREE_VEC_ELT (it, 1);
8952 tree end = TREE_VEC_ELT (it, 2);
8953 tree step = TREE_VEC_ELT (it, 3);
8954 tree orig_step = TREE_VEC_ELT (it, 4);
8955 tree type = TREE_TYPE (var);
8956 location_t loc = DECL_SOURCE_LOCATION (var);
8957 /* Emit:
8958 var = begin;
8959 goto cond_label;
8960 beg_label:
8962 var = var + step;
8963 cond_label:
8964 if (orig_step > 0) {
8965 if (var < end) goto beg_label;
8966 } else {
8967 if (var > end) goto beg_label;
8969 for each iterator, with inner iterators added to
8970 the ... above. */
8971 tree beg_label = create_artificial_label (loc);
8972 tree cond_label = NULL_TREE;
8973 tem = build2_loc (loc, MODIFY_EXPR, void_type_node,
8974 var, begin);
8975 append_to_statement_list_force (tem, p);
8976 tem = build_and_jump (&cond_label);
8977 append_to_statement_list_force (tem, p);
8978 tem = build1 (LABEL_EXPR, void_type_node, beg_label);
8979 append_to_statement_list (tem, p);
8980 tree bind = build3 (BIND_EXPR, void_type_node, NULL_TREE,
8981 NULL_TREE, NULL_TREE);
8982 TREE_SIDE_EFFECTS (bind) = 1;
8983 SET_EXPR_LOCATION (bind, loc);
8984 append_to_statement_list_force (bind, p);
8985 if (POINTER_TYPE_P (type))
8986 tem = build2_loc (loc, POINTER_PLUS_EXPR, type,
8987 var, fold_convert_loc (loc, sizetype,
8988 step));
8989 else
8990 tem = build2_loc (loc, PLUS_EXPR, type, var, step);
8991 tem = build2_loc (loc, MODIFY_EXPR, void_type_node,
8992 var, tem);
8993 append_to_statement_list_force (tem, p);
8994 tem = build1 (LABEL_EXPR, void_type_node, cond_label);
8995 append_to_statement_list (tem, p);
8996 tree cond = fold_build2_loc (loc, LT_EXPR,
8997 boolean_type_node,
8998 var, end);
8999 tree pos
9000 = fold_build3_loc (loc, COND_EXPR, void_type_node,
9001 cond, build_and_jump (&beg_label),
9002 void_node);
9003 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
9004 var, end);
9005 tree neg
9006 = fold_build3_loc (loc, COND_EXPR, void_type_node,
9007 cond, build_and_jump (&beg_label),
9008 void_node);
9009 tree osteptype = TREE_TYPE (orig_step);
9010 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
9011 orig_step,
9012 build_int_cst (osteptype, 0));
9013 tem = fold_build3_loc (loc, COND_EXPR, void_type_node,
9014 cond, pos, neg);
9015 append_to_statement_list_force (tem, p);
9016 p = &BIND_EXPR_BODY (bind);
9018 last_body = p;
9020 last_iter = TREE_PURPOSE (t);
9021 if (TREE_CODE (TREE_VALUE (t)) == COMPOUND_EXPR)
9023 append_to_statement_list (TREE_OPERAND (TREE_VALUE (t),
9024 0), last_body);
9025 TREE_VALUE (t) = TREE_OPERAND (TREE_VALUE (t), 1);
9027 if (error_operand_p (TREE_VALUE (t)))
9028 return 2;
9029 if (TREE_VALUE (t) != null_pointer_node)
9030 TREE_VALUE (t) = build_fold_addr_expr (TREE_VALUE (t));
9031 if (i == 4)
9033 r = build4 (ARRAY_REF, ptr_type_node, array, cnts[i],
9034 NULL_TREE, NULL_TREE);
9035 tree r2 = build4 (ARRAY_REF, ptr_type_node, array, cnts[5],
9036 NULL_TREE, NULL_TREE);
9037 r2 = build_fold_addr_expr_with_type (r2, ptr_type_node);
9038 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
9039 void_type_node, r, r2);
9040 append_to_statement_list_force (tem, last_body);
9041 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
9042 void_type_node, cnts[i],
9043 size_binop (PLUS_EXPR, cnts[i],
9044 size_int (1)));
9045 append_to_statement_list_force (tem, last_body);
9046 i = 5;
9048 r = build4 (ARRAY_REF, ptr_type_node, array, cnts[i],
9049 NULL_TREE, NULL_TREE);
9050 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
9051 void_type_node, r, TREE_VALUE (t));
9052 append_to_statement_list_force (tem, last_body);
9053 if (i == 5)
9055 r = build4 (ARRAY_REF, ptr_type_node, array,
9056 size_binop (PLUS_EXPR, cnts[i], size_int (1)),
9057 NULL_TREE, NULL_TREE);
9058 tem = build_int_cst (ptr_type_node, GOMP_DEPEND_INOUTSET);
9059 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
9060 void_type_node, r, tem);
9061 append_to_statement_list_force (tem, last_body);
9063 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
9064 void_type_node, cnts[i],
9065 size_binop (PLUS_EXPR, cnts[i],
9066 size_int (1 + (i == 5))));
9067 append_to_statement_list_force (tem, last_body);
9068 TREE_VALUE (t) = null_pointer_node;
9070 else
9072 if (last_bind)
9074 gimplify_and_add (last_bind, pre_p);
9075 last_bind = NULL_TREE;
9077 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
9079 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
9080 NULL, is_gimple_val, fb_rvalue);
9081 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
9083 if (error_operand_p (OMP_CLAUSE_DECL (c)))
9084 return 2;
9085 if (OMP_CLAUSE_DECL (c) != null_pointer_node)
9086 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (OMP_CLAUSE_DECL (c));
9087 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
9088 is_gimple_val, fb_rvalue) == GS_ERROR)
9089 return 2;
9090 if (i == 4)
9092 r = build4 (ARRAY_REF, ptr_type_node, array, cnts[i],
9093 NULL_TREE, NULL_TREE);
9094 tree r2 = build4 (ARRAY_REF, ptr_type_node, array, cnts[5],
9095 NULL_TREE, NULL_TREE);
9096 r2 = build_fold_addr_expr_with_type (r2, ptr_type_node);
9097 tem = build2 (MODIFY_EXPR, void_type_node, r, r2);
9098 gimplify_and_add (tem, pre_p);
9099 g = gimple_build_assign (cnts[i], size_binop (PLUS_EXPR,
9100 cnts[i],
9101 size_int (1)));
9102 gimple_seq_add_stmt (pre_p, g);
9103 i = 5;
9105 r = build4 (ARRAY_REF, ptr_type_node, array, cnts[i],
9106 NULL_TREE, NULL_TREE);
9107 tem = build2 (MODIFY_EXPR, void_type_node, r, OMP_CLAUSE_DECL (c));
9108 gimplify_and_add (tem, pre_p);
9109 if (i == 5)
9111 r = build4 (ARRAY_REF, ptr_type_node, array,
9112 size_binop (PLUS_EXPR, cnts[i], size_int (1)),
9113 NULL_TREE, NULL_TREE);
9114 tem = build_int_cst (ptr_type_node, GOMP_DEPEND_INOUTSET);
9115 tem = build2 (MODIFY_EXPR, void_type_node, r, tem);
9116 append_to_statement_list_force (tem, last_body);
9117 gimplify_and_add (tem, pre_p);
9119 g = gimple_build_assign (cnts[i],
9120 size_binop (PLUS_EXPR, cnts[i],
9121 size_int (1 + (i == 5))));
9122 gimple_seq_add_stmt (pre_p, g);
9125 if (last_bind)
9126 gimplify_and_add (last_bind, pre_p);
9127 tree cond = boolean_false_node;
9128 if (is_old)
9130 if (!unused[0])
9131 cond = build2_loc (first_loc, NE_EXPR, boolean_type_node, cnts[0],
9132 size_binop_loc (first_loc, PLUS_EXPR, counts[0],
9133 size_int (2)));
9134 if (!unused[2])
9135 cond = build2_loc (first_loc, TRUTH_OR_EXPR, boolean_type_node, cond,
9136 build2_loc (first_loc, NE_EXPR, boolean_type_node,
9137 cnts[2],
9138 size_binop_loc (first_loc, PLUS_EXPR,
9139 totalpx,
9140 size_int (1))));
9142 else
9144 tree prev = size_int (5);
9145 for (i = 0; i < 5; i++)
9147 if (unused[i])
9148 continue;
9149 prev = size_binop_loc (first_loc, PLUS_EXPR, counts[i], prev);
9150 cond = build2_loc (first_loc, TRUTH_OR_EXPR, boolean_type_node, cond,
9151 build2_loc (first_loc, NE_EXPR, boolean_type_node,
9152 cnts[i], unshare_expr (prev)));
9155 tem = build3_loc (first_loc, COND_EXPR, void_type_node, cond,
9156 build_call_expr_loc (first_loc,
9157 builtin_decl_explicit (BUILT_IN_TRAP),
9158 0), void_node);
9159 gimplify_and_add (tem, pre_p);
9160 c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_DEPEND);
9161 OMP_CLAUSE_DEPEND_KIND (c) = OMP_CLAUSE_DEPEND_LAST;
9162 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (array);
9163 OMP_CLAUSE_CHAIN (c) = *list_p;
9164 *list_p = c;
9165 return 1;
9168 /* True if mapping node C maps, or unmaps, a (Fortran) array descriptor. */
9170 static bool
9171 omp_map_clause_descriptor_p (tree c)
9173 if (OMP_CLAUSE_CODE (c) != OMP_CLAUSE_MAP)
9174 return false;
9176 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_TO_PSET)
9177 return true;
9179 if ((OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_RELEASE
9180 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_DELETE)
9181 && OMP_CLAUSE_RELEASE_DESCRIPTOR (c))
9182 return true;
9184 return false;
9187 /* For a set of mappings describing an array section pointed to by a struct
9188 (or derived type, etc.) component, create an "alloc" or "release" node to
9189 insert into a list following a GOMP_MAP_STRUCT node. For some types of
9190 mapping (e.g. Fortran arrays with descriptors), an additional mapping may
9191 be created that is inserted into the list of mapping nodes attached to the
9192 directive being processed -- not part of the sorted list of nodes after
9193 GOMP_MAP_STRUCT.
9195 CODE is the code of the directive being processed. GRP_START and GRP_END
9196 are the first and last of two or three nodes representing this array section
9197 mapping (e.g. a data movement node like GOMP_MAP_{TO,FROM}, optionally a
9198 GOMP_MAP_TO_PSET, and finally a GOMP_MAP_ALWAYS_POINTER). EXTRA_NODE is
9199 filled with the additional node described above, if needed.
9201 This function does not add the new nodes to any lists itself. It is the
9202 responsibility of the caller to do that. */
9204 static tree
9205 build_omp_struct_comp_nodes (enum tree_code code, tree grp_start, tree grp_end,
9206 tree *extra_node)
9208 enum gomp_map_kind mkind
9209 = (code == OMP_TARGET_EXIT_DATA || code == OACC_EXIT_DATA)
9210 ? GOMP_MAP_RELEASE : GOMP_MAP_ALLOC;
9212 gcc_assert (grp_start != grp_end);
9214 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (grp_end), OMP_CLAUSE_MAP);
9215 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
9216 OMP_CLAUSE_DECL (c2) = unshare_expr (OMP_CLAUSE_DECL (grp_end));
9217 OMP_CLAUSE_CHAIN (c2) = NULL_TREE;
9218 tree grp_mid = NULL_TREE;
9219 if (OMP_CLAUSE_CHAIN (grp_start) != grp_end)
9220 grp_mid = OMP_CLAUSE_CHAIN (grp_start);
9222 if (grp_mid && omp_map_clause_descriptor_p (grp_mid))
9223 OMP_CLAUSE_SIZE (c2) = OMP_CLAUSE_SIZE (grp_mid);
9224 else
9225 OMP_CLAUSE_SIZE (c2) = TYPE_SIZE_UNIT (ptr_type_node);
9227 if (grp_mid
9228 && OMP_CLAUSE_CODE (grp_mid) == OMP_CLAUSE_MAP
9229 && OMP_CLAUSE_MAP_KIND (grp_mid) == GOMP_MAP_ALWAYS_POINTER)
9231 tree c3
9232 = build_omp_clause (OMP_CLAUSE_LOCATION (grp_end), OMP_CLAUSE_MAP);
9233 OMP_CLAUSE_SET_MAP_KIND (c3, mkind);
9234 OMP_CLAUSE_DECL (c3) = unshare_expr (OMP_CLAUSE_DECL (grp_mid));
9235 OMP_CLAUSE_SIZE (c3) = TYPE_SIZE_UNIT (ptr_type_node);
9236 OMP_CLAUSE_CHAIN (c3) = NULL_TREE;
9238 *extra_node = c3;
9240 else
9241 *extra_node = NULL_TREE;
9243 return c2;
9246 /* Strip ARRAY_REFS or an indirect ref off BASE, find the containing object,
9247 and set *BITPOSP and *POFFSETP to the bit offset of the access.
9248 If BASE_REF is non-NULL and the containing object is a reference, set
9249 *BASE_REF to that reference before dereferencing the object.
9250 If BASE_REF is NULL, check that the containing object is a COMPONENT_REF or
9251 has array type, else return NULL. */
9253 static tree
9254 extract_base_bit_offset (tree base, poly_int64 *bitposp,
9255 poly_offset_int *poffsetp,
9256 bool *variable_offset)
9258 tree offset;
9259 poly_int64 bitsize, bitpos;
9260 machine_mode mode;
9261 int unsignedp, reversep, volatilep = 0;
9262 poly_offset_int poffset;
9264 STRIP_NOPS (base);
9266 base = get_inner_reference (base, &bitsize, &bitpos, &offset, &mode,
9267 &unsignedp, &reversep, &volatilep);
9269 STRIP_NOPS (base);
9271 if (offset && poly_int_tree_p (offset))
9273 poffset = wi::to_poly_offset (offset);
9274 *variable_offset = false;
9276 else
9278 poffset = 0;
9279 *variable_offset = (offset != NULL_TREE);
9282 if (maybe_ne (bitpos, 0))
9283 poffset += bits_to_bytes_round_down (bitpos);
9285 *bitposp = bitpos;
9286 *poffsetp = poffset;
9288 return base;
9291 /* Used for topological sorting of mapping groups. UNVISITED means we haven't
9292 started processing the group yet. The TEMPORARY mark is used when we first
9293 encounter a group on a depth-first traversal, and the PERMANENT mark is used
9294 when we have processed all the group's children (i.e. all the base pointers
9295 referred to by the group's mapping nodes, recursively). */
9297 enum omp_tsort_mark {
9298 UNVISITED,
9299 TEMPORARY,
9300 PERMANENT
9303 /* Hash for trees based on operand_equal_p. Like tree_operand_hash
9304 but ignores side effects in the equality comparisons. */
9306 struct tree_operand_hash_no_se : tree_operand_hash
9308 static inline bool equal (const value_type &,
9309 const compare_type &);
9312 inline bool
9313 tree_operand_hash_no_se::equal (const value_type &t1,
9314 const compare_type &t2)
9316 return operand_equal_p (t1, t2, OEP_MATCH_SIDE_EFFECTS);
9319 /* A group of OMP_CLAUSE_MAP nodes that correspond to a single "map"
9320 clause. */
9322 struct omp_mapping_group {
9323 tree *grp_start;
9324 tree grp_end;
9325 omp_tsort_mark mark;
9326 /* If we've removed the group but need to reindex, mark the group as
9327 deleted. */
9328 bool deleted;
9329 /* The group points to an already-created "GOMP_MAP_STRUCT
9330 GOMP_MAP_ATTACH_DETACH" pair. */
9331 bool reprocess_struct;
9332 /* The group should use "zero-length" allocations for pointers that are not
9333 mapped "to" on the same directive. */
9334 bool fragile;
9335 struct omp_mapping_group *sibling;
9336 struct omp_mapping_group *next;
9339 DEBUG_FUNCTION void
9340 debug_mapping_group (omp_mapping_group *grp)
9342 tree tmp = OMP_CLAUSE_CHAIN (grp->grp_end);
9343 OMP_CLAUSE_CHAIN (grp->grp_end) = NULL;
9344 debug_generic_expr (*grp->grp_start);
9345 OMP_CLAUSE_CHAIN (grp->grp_end) = tmp;
9348 /* Return the OpenMP "base pointer" of an expression EXPR, or NULL if there
9349 isn't one. */
9351 static tree
9352 omp_get_base_pointer (tree expr)
9354 while (TREE_CODE (expr) == ARRAY_REF
9355 || TREE_CODE (expr) == COMPONENT_REF)
9356 expr = TREE_OPERAND (expr, 0);
9358 if (INDIRECT_REF_P (expr)
9359 || (TREE_CODE (expr) == MEM_REF
9360 && integer_zerop (TREE_OPERAND (expr, 1))))
9362 expr = TREE_OPERAND (expr, 0);
9363 while (TREE_CODE (expr) == COMPOUND_EXPR)
9364 expr = TREE_OPERAND (expr, 1);
9365 if (TREE_CODE (expr) == POINTER_PLUS_EXPR)
9366 expr = TREE_OPERAND (expr, 0);
9367 if (TREE_CODE (expr) == SAVE_EXPR)
9368 expr = TREE_OPERAND (expr, 0);
9369 STRIP_NOPS (expr);
9370 return expr;
9373 return NULL_TREE;
9376 /* An attach or detach operation depends directly on the address being
9377 attached/detached. Return that address, or none if there are no
9378 attachments/detachments. */
9380 static tree
9381 omp_get_attachment (omp_mapping_group *grp)
9383 tree node = *grp->grp_start;
9385 switch (OMP_CLAUSE_MAP_KIND (node))
9387 case GOMP_MAP_TO:
9388 case GOMP_MAP_FROM:
9389 case GOMP_MAP_TOFROM:
9390 case GOMP_MAP_ALWAYS_FROM:
9391 case GOMP_MAP_ALWAYS_TO:
9392 case GOMP_MAP_ALWAYS_TOFROM:
9393 case GOMP_MAP_FORCE_FROM:
9394 case GOMP_MAP_FORCE_TO:
9395 case GOMP_MAP_FORCE_TOFROM:
9396 case GOMP_MAP_FORCE_PRESENT:
9397 case GOMP_MAP_PRESENT_ALLOC:
9398 case GOMP_MAP_PRESENT_FROM:
9399 case GOMP_MAP_PRESENT_TO:
9400 case GOMP_MAP_PRESENT_TOFROM:
9401 case GOMP_MAP_ALWAYS_PRESENT_FROM:
9402 case GOMP_MAP_ALWAYS_PRESENT_TO:
9403 case GOMP_MAP_ALWAYS_PRESENT_TOFROM:
9404 case GOMP_MAP_ALLOC:
9405 case GOMP_MAP_RELEASE:
9406 case GOMP_MAP_DELETE:
9407 case GOMP_MAP_FORCE_ALLOC:
9408 if (node == grp->grp_end)
9409 return NULL_TREE;
9411 node = OMP_CLAUSE_CHAIN (node);
9412 if (node && omp_map_clause_descriptor_p (node))
9414 gcc_assert (node != grp->grp_end);
9415 node = OMP_CLAUSE_CHAIN (node);
9417 if (node)
9418 switch (OMP_CLAUSE_MAP_KIND (node))
9420 case GOMP_MAP_POINTER:
9421 case GOMP_MAP_ALWAYS_POINTER:
9422 case GOMP_MAP_FIRSTPRIVATE_POINTER:
9423 case GOMP_MAP_FIRSTPRIVATE_REFERENCE:
9424 case GOMP_MAP_POINTER_TO_ZERO_LENGTH_ARRAY_SECTION:
9425 return NULL_TREE;
9427 case GOMP_MAP_ATTACH_DETACH:
9428 case GOMP_MAP_ATTACH_ZERO_LENGTH_ARRAY_SECTION:
9429 case GOMP_MAP_DETACH:
9430 return OMP_CLAUSE_DECL (node);
9432 default:
9433 internal_error ("unexpected mapping node");
9435 return error_mark_node;
9437 case GOMP_MAP_TO_PSET:
9438 gcc_assert (node != grp->grp_end);
9439 node = OMP_CLAUSE_CHAIN (node);
9440 if (OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_ATTACH
9441 || OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_DETACH)
9442 return OMP_CLAUSE_DECL (node);
9443 else
9444 internal_error ("unexpected mapping node");
9445 return error_mark_node;
9447 case GOMP_MAP_ATTACH:
9448 case GOMP_MAP_DETACH:
9449 node = OMP_CLAUSE_CHAIN (node);
9450 if (!node || *grp->grp_start == grp->grp_end)
9451 return OMP_CLAUSE_DECL (*grp->grp_start);
9452 if (OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_FIRSTPRIVATE_POINTER
9453 || OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_FIRSTPRIVATE_REFERENCE)
9454 return OMP_CLAUSE_DECL (*grp->grp_start);
9455 else
9456 internal_error ("unexpected mapping node");
9457 return error_mark_node;
9459 case GOMP_MAP_STRUCT:
9460 case GOMP_MAP_STRUCT_UNORD:
9461 case GOMP_MAP_FORCE_DEVICEPTR:
9462 case GOMP_MAP_DEVICE_RESIDENT:
9463 case GOMP_MAP_LINK:
9464 case GOMP_MAP_IF_PRESENT:
9465 case GOMP_MAP_FIRSTPRIVATE:
9466 case GOMP_MAP_FIRSTPRIVATE_INT:
9467 case GOMP_MAP_USE_DEVICE_PTR:
9468 case GOMP_MAP_ATTACH_ZERO_LENGTH_ARRAY_SECTION:
9469 return NULL_TREE;
9471 default:
9472 internal_error ("unexpected mapping node");
9475 return error_mark_node;
9478 /* Given a pointer START_P to the start of a group of related (e.g. pointer)
9479 mappings, return the chain pointer to the end of that group in the list. */
9481 static tree *
9482 omp_group_last (tree *start_p)
9484 tree c = *start_p, nc, *grp_last_p = start_p;
9486 gcc_assert (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP);
9488 nc = OMP_CLAUSE_CHAIN (c);
9490 if (!nc || OMP_CLAUSE_CODE (nc) != OMP_CLAUSE_MAP)
9491 return grp_last_p;
9493 switch (OMP_CLAUSE_MAP_KIND (c))
9495 default:
9496 while (nc
9497 && OMP_CLAUSE_CODE (nc) == OMP_CLAUSE_MAP
9498 && (OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_FIRSTPRIVATE_REFERENCE
9499 || OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_FIRSTPRIVATE_POINTER
9500 || OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_ATTACH_DETACH
9501 || OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_POINTER
9502 || (OMP_CLAUSE_MAP_KIND (nc)
9503 == GOMP_MAP_POINTER_TO_ZERO_LENGTH_ARRAY_SECTION)
9504 || (OMP_CLAUSE_MAP_KIND (nc)
9505 == GOMP_MAP_ATTACH_ZERO_LENGTH_ARRAY_SECTION)
9506 || OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_DETACH
9507 || OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_ALWAYS_POINTER
9508 || omp_map_clause_descriptor_p (nc)))
9510 tree nc2 = OMP_CLAUSE_CHAIN (nc);
9511 if (OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_DETACH)
9513 /* In the specific case we're doing "exit data" on an array
9514 slice of a reference-to-pointer struct component, we will see
9515 DETACH followed by ATTACH_DETACH here. We want to treat that
9516 as a single group. In other cases DETACH might represent a
9517 stand-alone "detach" clause, so we don't want to consider
9518 that part of the group. */
9519 if (nc2
9520 && OMP_CLAUSE_CODE (nc2) == OMP_CLAUSE_MAP
9521 && OMP_CLAUSE_MAP_KIND (nc2) == GOMP_MAP_ATTACH_DETACH)
9522 goto consume_two_nodes;
9523 else
9524 break;
9526 if (nc2
9527 && OMP_CLAUSE_CODE (nc2) == OMP_CLAUSE_MAP
9528 && (OMP_CLAUSE_MAP_KIND (nc)
9529 == GOMP_MAP_POINTER_TO_ZERO_LENGTH_ARRAY_SECTION)
9530 && OMP_CLAUSE_MAP_KIND (nc2) == GOMP_MAP_ATTACH)
9532 consume_two_nodes:
9533 grp_last_p = &OMP_CLAUSE_CHAIN (nc);
9534 c = nc2;
9535 nc = OMP_CLAUSE_CHAIN (nc2);
9537 else
9539 grp_last_p = &OMP_CLAUSE_CHAIN (c);
9540 c = nc;
9541 nc = nc2;
9544 break;
9546 case GOMP_MAP_ATTACH:
9547 case GOMP_MAP_DETACH:
9548 /* This is a weird artifact of how directives are parsed: bare attach or
9549 detach clauses get a subsequent (meaningless) FIRSTPRIVATE_POINTER or
9550 FIRSTPRIVATE_REFERENCE node. FIXME. */
9551 if (nc
9552 && OMP_CLAUSE_CODE (nc) == OMP_CLAUSE_MAP
9553 && (OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_FIRSTPRIVATE_REFERENCE
9554 || OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_FIRSTPRIVATE_POINTER))
9555 grp_last_p = &OMP_CLAUSE_CHAIN (c);
9556 break;
9558 case GOMP_MAP_TO_PSET:
9559 if (OMP_CLAUSE_CODE (nc) == OMP_CLAUSE_MAP
9560 && (OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_ATTACH
9561 || OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_DETACH))
9562 grp_last_p = &OMP_CLAUSE_CHAIN (c);
9563 break;
9565 case GOMP_MAP_STRUCT:
9566 case GOMP_MAP_STRUCT_UNORD:
9568 unsigned HOST_WIDE_INT num_mappings
9569 = tree_to_uhwi (OMP_CLAUSE_SIZE (c));
9570 if (OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_FIRSTPRIVATE_POINTER
9571 || OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_FIRSTPRIVATE_REFERENCE
9572 || OMP_CLAUSE_MAP_KIND (nc) == GOMP_MAP_ATTACH_DETACH)
9573 grp_last_p = &OMP_CLAUSE_CHAIN (*grp_last_p);
9574 for (unsigned i = 0; i < num_mappings; i++)
9575 grp_last_p = &OMP_CLAUSE_CHAIN (*grp_last_p);
9577 break;
9580 return grp_last_p;
9583 /* Walk through LIST_P, and return a list of groups of mappings found (e.g.
9584 OMP_CLAUSE_MAP with GOMP_MAP_{TO/FROM/TOFROM} followed by one or two
9585 associated GOMP_MAP_POINTER mappings). Return a vector of omp_mapping_group
9586 if we have more than one such group, else return NULL. */
9588 static void
9589 omp_gather_mapping_groups_1 (tree *list_p, vec<omp_mapping_group> *groups,
9590 tree gather_sentinel)
9592 for (tree *cp = list_p;
9593 *cp && *cp != gather_sentinel;
9594 cp = &OMP_CLAUSE_CHAIN (*cp))
9596 if (OMP_CLAUSE_CODE (*cp) != OMP_CLAUSE_MAP)
9597 continue;
9599 tree *grp_last_p = omp_group_last (cp);
9600 omp_mapping_group grp;
9602 grp.grp_start = cp;
9603 grp.grp_end = *grp_last_p;
9604 grp.mark = UNVISITED;
9605 grp.sibling = NULL;
9606 grp.deleted = false;
9607 grp.reprocess_struct = false;
9608 grp.fragile = false;
9609 grp.next = NULL;
9610 groups->safe_push (grp);
9612 cp = grp_last_p;
9616 static vec<omp_mapping_group> *
9617 omp_gather_mapping_groups (tree *list_p)
9619 vec<omp_mapping_group> *groups = new vec<omp_mapping_group> ();
9621 omp_gather_mapping_groups_1 (list_p, groups, NULL_TREE);
9623 if (groups->length () > 0)
9624 return groups;
9625 else
9627 delete groups;
9628 return NULL;
9632 /* A pointer mapping group GRP may define a block of memory starting at some
9633 base address, and maybe also define a firstprivate pointer or firstprivate
9634 reference that points to that block. The return value is a node containing
9635 the former, and the *FIRSTPRIVATE pointer is set if we have the latter.
9636 If we define several base pointers, i.e. for a GOMP_MAP_STRUCT mapping,
9637 return the number of consecutive chained nodes in CHAINED. */
9639 static tree
9640 omp_group_base (omp_mapping_group *grp, unsigned int *chained,
9641 tree *firstprivate)
9643 tree node = *grp->grp_start;
9645 *firstprivate = NULL_TREE;
9646 *chained = 1;
9648 switch (OMP_CLAUSE_MAP_KIND (node))
9650 case GOMP_MAP_TO:
9651 case GOMP_MAP_FROM:
9652 case GOMP_MAP_TOFROM:
9653 case GOMP_MAP_ALWAYS_FROM:
9654 case GOMP_MAP_ALWAYS_TO:
9655 case GOMP_MAP_ALWAYS_TOFROM:
9656 case GOMP_MAP_FORCE_FROM:
9657 case GOMP_MAP_FORCE_TO:
9658 case GOMP_MAP_FORCE_TOFROM:
9659 case GOMP_MAP_FORCE_PRESENT:
9660 case GOMP_MAP_PRESENT_ALLOC:
9661 case GOMP_MAP_PRESENT_FROM:
9662 case GOMP_MAP_PRESENT_TO:
9663 case GOMP_MAP_PRESENT_TOFROM:
9664 case GOMP_MAP_ALWAYS_PRESENT_FROM:
9665 case GOMP_MAP_ALWAYS_PRESENT_TO:
9666 case GOMP_MAP_ALWAYS_PRESENT_TOFROM:
9667 case GOMP_MAP_ALLOC:
9668 case GOMP_MAP_RELEASE:
9669 case GOMP_MAP_DELETE:
9670 case GOMP_MAP_FORCE_ALLOC:
9671 case GOMP_MAP_IF_PRESENT:
9672 if (node == grp->grp_end)
9673 return node;
9675 node = OMP_CLAUSE_CHAIN (node);
9676 if (!node)
9677 internal_error ("unexpected mapping node");
9678 if (omp_map_clause_descriptor_p (node))
9680 if (node == grp->grp_end)
9681 return *grp->grp_start;
9682 node = OMP_CLAUSE_CHAIN (node);
9684 switch (OMP_CLAUSE_MAP_KIND (node))
9686 case GOMP_MAP_POINTER:
9687 case GOMP_MAP_FIRSTPRIVATE_POINTER:
9688 case GOMP_MAP_FIRSTPRIVATE_REFERENCE:
9689 case GOMP_MAP_POINTER_TO_ZERO_LENGTH_ARRAY_SECTION:
9690 *firstprivate = OMP_CLAUSE_DECL (node);
9691 return *grp->grp_start;
9693 case GOMP_MAP_ALWAYS_POINTER:
9694 case GOMP_MAP_ATTACH_DETACH:
9695 case GOMP_MAP_ATTACH_ZERO_LENGTH_ARRAY_SECTION:
9696 case GOMP_MAP_DETACH:
9697 return *grp->grp_start;
9699 default:
9700 internal_error ("unexpected mapping node");
9702 return error_mark_node;
9704 case GOMP_MAP_TO_PSET:
9705 gcc_assert (node != grp->grp_end);
9706 node = OMP_CLAUSE_CHAIN (node);
9707 if (OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_ATTACH
9708 || OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_DETACH)
9709 return NULL_TREE;
9710 else
9711 internal_error ("unexpected mapping node");
9712 return error_mark_node;
9714 case GOMP_MAP_ATTACH:
9715 case GOMP_MAP_DETACH:
9716 node = OMP_CLAUSE_CHAIN (node);
9717 if (!node || *grp->grp_start == grp->grp_end)
9718 return NULL_TREE;
9719 if (OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_FIRSTPRIVATE_POINTER
9720 || OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_FIRSTPRIVATE_REFERENCE)
9722 /* We're mapping the base pointer itself in a bare attach or detach
9723 node. This is a side effect of how parsing works, and the mapping
9724 will be removed anyway (at least for enter/exit data directives).
9725 We should ignore the mapping here. FIXME. */
9726 return NULL_TREE;
9728 else
9729 internal_error ("unexpected mapping node");
9730 return error_mark_node;
9732 case GOMP_MAP_STRUCT:
9733 case GOMP_MAP_STRUCT_UNORD:
9735 unsigned HOST_WIDE_INT num_mappings
9736 = tree_to_uhwi (OMP_CLAUSE_SIZE (node));
9737 node = OMP_CLAUSE_CHAIN (node);
9738 if (OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_FIRSTPRIVATE_POINTER
9739 || OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_FIRSTPRIVATE_REFERENCE)
9741 *firstprivate = OMP_CLAUSE_DECL (node);
9742 node = OMP_CLAUSE_CHAIN (node);
9744 else if (OMP_CLAUSE_MAP_KIND (node) == GOMP_MAP_ATTACH_DETACH)
9745 node = OMP_CLAUSE_CHAIN (node);
9746 *chained = num_mappings;
9747 return node;
9750 case GOMP_MAP_FORCE_DEVICEPTR:
9751 case GOMP_MAP_DEVICE_RESIDENT:
9752 case GOMP_MAP_LINK:
9753 case GOMP_MAP_FIRSTPRIVATE:
9754 case GOMP_MAP_FIRSTPRIVATE_INT:
9755 case GOMP_MAP_USE_DEVICE_PTR:
9756 case GOMP_MAP_ATTACH_ZERO_LENGTH_ARRAY_SECTION:
9757 return NULL_TREE;
9759 case GOMP_MAP_FIRSTPRIVATE_POINTER:
9760 case GOMP_MAP_FIRSTPRIVATE_REFERENCE:
9761 case GOMP_MAP_POINTER:
9762 case GOMP_MAP_ALWAYS_POINTER:
9763 case GOMP_MAP_POINTER_TO_ZERO_LENGTH_ARRAY_SECTION:
9764 /* These shouldn't appear by themselves. */
9765 if (!seen_error ())
9766 internal_error ("unexpected pointer mapping node");
9767 return error_mark_node;
9769 default:
9770 gcc_unreachable ();
9773 return error_mark_node;
9776 /* Given a vector of omp_mapping_groups, build a hash table so we can look up
9777 nodes by tree_operand_hash_no_se. */
9779 static void
9780 omp_index_mapping_groups_1 (hash_map<tree_operand_hash_no_se,
9781 omp_mapping_group *> *grpmap,
9782 vec<omp_mapping_group> *groups,
9783 tree reindex_sentinel)
9785 omp_mapping_group *grp;
9786 unsigned int i;
9787 bool reindexing = reindex_sentinel != NULL_TREE, above_hwm = false;
9789 FOR_EACH_VEC_ELT (*groups, i, grp)
9791 if (reindexing && *grp->grp_start == reindex_sentinel)
9792 above_hwm = true;
9794 if (reindexing && !above_hwm)
9795 continue;
9797 if (grp->reprocess_struct)
9798 continue;
9800 tree fpp;
9801 unsigned int chained;
9802 tree node = omp_group_base (grp, &chained, &fpp);
9804 if (node == error_mark_node || (!node && !fpp))
9805 continue;
9807 for (unsigned j = 0;
9808 node && j < chained;
9809 node = OMP_CLAUSE_CHAIN (node), j++)
9811 tree decl = OMP_CLAUSE_DECL (node);
9812 /* Sometimes we see zero-offset MEM_REF instead of INDIRECT_REF,
9813 meaning node-hash lookups don't work. This is a workaround for
9814 that, but ideally we should just create the INDIRECT_REF at
9815 source instead. FIXME. */
9816 if (TREE_CODE (decl) == MEM_REF
9817 && integer_zerop (TREE_OPERAND (decl, 1)))
9818 decl = build_fold_indirect_ref (TREE_OPERAND (decl, 0));
9820 omp_mapping_group **prev = grpmap->get (decl);
9822 if (prev && *prev == grp)
9823 /* Empty. */;
9824 else if (prev)
9826 /* Mapping the same thing twice is normally diagnosed as an error,
9827 but can happen under some circumstances, e.g. in pr99928-16.c,
9828 the directive:
9830 #pragma omp target simd reduction(+:a[:3]) \
9831 map(always, tofrom: a[:6])
9834 will result in two "a[0]" mappings (of different sizes). */
9836 grp->sibling = (*prev)->sibling;
9837 (*prev)->sibling = grp;
9839 else
9840 grpmap->put (decl, grp);
9843 if (!fpp)
9844 continue;
9846 omp_mapping_group **prev = grpmap->get (fpp);
9847 if (prev && *prev != grp)
9849 grp->sibling = (*prev)->sibling;
9850 (*prev)->sibling = grp;
9852 else
9853 grpmap->put (fpp, grp);
9857 static hash_map<tree_operand_hash_no_se, omp_mapping_group *> *
9858 omp_index_mapping_groups (vec<omp_mapping_group> *groups)
9860 hash_map<tree_operand_hash_no_se, omp_mapping_group *> *grpmap
9861 = new hash_map<tree_operand_hash_no_se, omp_mapping_group *>;
9863 omp_index_mapping_groups_1 (grpmap, groups, NULL_TREE);
9865 return grpmap;
9868 /* Rebuild group map from partially-processed clause list (during
9869 omp_build_struct_sibling_lists). We have already processed nodes up until
9870 a high-water mark (HWM). This is a bit tricky because the list is being
9871 reordered as it is scanned, but we know:
9873 1. The list after HWM has not been touched yet, so we can reindex it safely.
9875 2. The list before and including HWM has been altered, but remains
9876 well-formed throughout the sibling-list building operation.
9878 so, we can do the reindex operation in two parts, on the processed and
9879 then the unprocessed halves of the list. */
9881 static hash_map<tree_operand_hash_no_se, omp_mapping_group *> *
9882 omp_reindex_mapping_groups (tree *list_p,
9883 vec<omp_mapping_group> *groups,
9884 vec<omp_mapping_group> *processed_groups,
9885 tree sentinel)
9887 hash_map<tree_operand_hash_no_se, omp_mapping_group *> *grpmap
9888 = new hash_map<tree_operand_hash_no_se, omp_mapping_group *>;
9890 processed_groups->truncate (0);
9892 omp_gather_mapping_groups_1 (list_p, processed_groups, sentinel);
9893 omp_index_mapping_groups_1 (grpmap, processed_groups, NULL_TREE);
9894 if (sentinel)
9895 omp_index_mapping_groups_1 (grpmap, groups, sentinel);
9897 return grpmap;
9900 /* Find the immediately-containing struct for a component ref (etc.)
9901 expression EXPR. */
9903 static tree
9904 omp_containing_struct (tree expr)
9906 tree expr0 = expr;
9908 STRIP_NOPS (expr);
9910 /* Note: don't strip NOPs unless we're also stripping off array refs or a
9911 component ref. */
9912 if (TREE_CODE (expr) != ARRAY_REF && TREE_CODE (expr) != COMPONENT_REF)
9913 return expr0;
9915 while (TREE_CODE (expr) == ARRAY_REF)
9916 expr = TREE_OPERAND (expr, 0);
9918 if (TREE_CODE (expr) == COMPONENT_REF)
9919 expr = TREE_OPERAND (expr, 0);
9921 return expr;
9924 /* Return TRUE if DECL describes a component that is part of a whole structure
9925 that is mapped elsewhere in GRPMAP. *MAPPED_BY_GROUP is set to the group
9926 that maps that structure, if present. */
9928 static bool
9929 omp_mapped_by_containing_struct (hash_map<tree_operand_hash_no_se,
9930 omp_mapping_group *> *grpmap,
9931 tree decl,
9932 omp_mapping_group **mapped_by_group)
9934 tree wsdecl = NULL_TREE;
9936 *mapped_by_group = NULL;
9938 while (true)
9940 wsdecl = omp_containing_struct (decl);
9941 if (wsdecl == decl)
9942 break;
9943 omp_mapping_group **wholestruct = grpmap->get (wsdecl);
9944 if (!wholestruct
9945 && TREE_CODE (wsdecl) == MEM_REF
9946 && integer_zerop (TREE_OPERAND (wsdecl, 1)))
9948 tree deref = TREE_OPERAND (wsdecl, 0);
9949 deref = build_fold_indirect_ref (deref);
9950 wholestruct = grpmap->get (deref);
9952 if (wholestruct)
9954 *mapped_by_group = *wholestruct;
9955 return true;
9957 decl = wsdecl;
9960 return false;
9963 /* Helper function for omp_tsort_mapping_groups. Returns TRUE on success, or
9964 FALSE on error. */
9966 static bool
9967 omp_tsort_mapping_groups_1 (omp_mapping_group ***outlist,
9968 vec<omp_mapping_group> *groups,
9969 hash_map<tree_operand_hash_no_se,
9970 omp_mapping_group *> *grpmap,
9971 omp_mapping_group *grp)
9973 if (grp->mark == PERMANENT)
9974 return true;
9975 if (grp->mark == TEMPORARY)
9977 fprintf (stderr, "when processing group:\n");
9978 debug_mapping_group (grp);
9979 internal_error ("base pointer cycle detected");
9980 return false;
9982 grp->mark = TEMPORARY;
9984 tree attaches_to = omp_get_attachment (grp);
9986 if (attaches_to)
9988 omp_mapping_group **basep = grpmap->get (attaches_to);
9990 if (basep && *basep != grp)
9992 for (omp_mapping_group *w = *basep; w; w = w->sibling)
9993 if (!omp_tsort_mapping_groups_1 (outlist, groups, grpmap, w))
9994 return false;
9998 tree decl = OMP_CLAUSE_DECL (*grp->grp_start);
10000 while (decl)
10002 tree base = omp_get_base_pointer (decl);
10004 if (!base)
10005 break;
10007 omp_mapping_group **innerp = grpmap->get (base);
10008 omp_mapping_group *wholestruct;
10010 /* We should treat whole-structure mappings as if all (pointer, in this
10011 case) members are mapped as individual list items. Check if we have
10012 such a whole-structure mapping, if we don't have an explicit reference
10013 to the pointer member itself. */
10014 if (!innerp
10015 && TREE_CODE (base) == COMPONENT_REF
10016 && omp_mapped_by_containing_struct (grpmap, base, &wholestruct))
10017 innerp = &wholestruct;
10019 if (innerp && *innerp != grp)
10021 for (omp_mapping_group *w = *innerp; w; w = w->sibling)
10022 if (!omp_tsort_mapping_groups_1 (outlist, groups, grpmap, w))
10023 return false;
10024 break;
10027 decl = base;
10030 grp->mark = PERMANENT;
10032 /* Emit grp to output list. */
10034 **outlist = grp;
10035 *outlist = &grp->next;
10037 return true;
10040 /* Topologically sort GROUPS, so that OMP 5.0-defined base pointers come
10041 before mappings that use those pointers. This is an implementation of the
10042 depth-first search algorithm, described e.g. at:
10044 https://en.wikipedia.org/wiki/Topological_sorting
10047 static omp_mapping_group *
10048 omp_tsort_mapping_groups (vec<omp_mapping_group> *groups,
10049 hash_map<tree_operand_hash_no_se, omp_mapping_group *>
10050 *grpmap,
10051 bool enter_exit_data)
10053 omp_mapping_group *grp, *outlist = NULL, **cursor;
10054 unsigned int i;
10055 bool saw_runtime_implicit = false;
10057 cursor = &outlist;
10059 FOR_EACH_VEC_ELT (*groups, i, grp)
10061 if (grp->mark != PERMANENT)
10063 if (OMP_CLAUSE_MAP_RUNTIME_IMPLICIT_P (*grp->grp_start))
10065 saw_runtime_implicit = true;
10066 continue;
10068 if (!omp_tsort_mapping_groups_1 (&cursor, groups, grpmap, grp))
10069 return NULL;
10073 if (!saw_runtime_implicit)
10074 return outlist;
10076 FOR_EACH_VEC_ELT (*groups, i, grp)
10078 if (grp->mark != PERMANENT
10079 && OMP_CLAUSE_MAP_RUNTIME_IMPLICIT_P (*grp->grp_start))
10081 /* Clear the flag for enter/exit data because it is currently
10082 meaningless for those operations in libgomp. */
10083 if (enter_exit_data)
10084 OMP_CLAUSE_MAP_RUNTIME_IMPLICIT_P (*grp->grp_start) = 0;
10086 if (!omp_tsort_mapping_groups_1 (&cursor, groups, grpmap, grp))
10087 return NULL;
10091 return outlist;
10094 /* Split INLIST into three parts:
10096 - "present" alloc/to/from groups
10097 - other to/from groups
10098 - other alloc/release/delete groups
10100 These sub-lists are then concatenated together to form the final list.
10101 Each sub-list retains the order of the original list.
10102 Note that ATTACH nodes are later moved to the end of the list in
10103 gimplify_adjust_omp_clauses, for target regions. */
10105 static omp_mapping_group *
10106 omp_segregate_mapping_groups (omp_mapping_group *inlist)
10108 omp_mapping_group *ard_groups = NULL, *tf_groups = NULL;
10109 omp_mapping_group *p_groups = NULL;
10110 omp_mapping_group **ard_tail = &ard_groups, **tf_tail = &tf_groups;
10111 omp_mapping_group **p_tail = &p_groups;
10113 for (omp_mapping_group *w = inlist; w;)
10115 tree c = *w->grp_start;
10116 omp_mapping_group *next = w->next;
10118 gcc_assert (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP);
10120 switch (OMP_CLAUSE_MAP_KIND (c))
10122 case GOMP_MAP_ALLOC:
10123 case GOMP_MAP_RELEASE:
10124 case GOMP_MAP_DELETE:
10125 *ard_tail = w;
10126 w->next = NULL;
10127 ard_tail = &w->next;
10128 break;
10130 /* These map types are all semantically identical, so are moved into a
10131 single group. They will each be changed into GOMP_MAP_FORCE_PRESENT
10132 in gimplify_adjust_omp_clauses. */
10133 case GOMP_MAP_PRESENT_ALLOC:
10134 case GOMP_MAP_PRESENT_FROM:
10135 case GOMP_MAP_PRESENT_TO:
10136 case GOMP_MAP_PRESENT_TOFROM:
10137 *p_tail = w;
10138 w->next = NULL;
10139 p_tail = &w->next;
10140 break;
10142 default:
10143 *tf_tail = w;
10144 w->next = NULL;
10145 tf_tail = &w->next;
10148 w = next;
10151 /* Now splice the lists together... */
10152 *tf_tail = ard_groups;
10153 *p_tail = tf_groups;
10155 return p_groups;
10158 /* Given a list LIST_P containing groups of mappings given by GROUPS, reorder
10159 those groups based on the output list of omp_tsort_mapping_groups --
10160 singly-linked, threaded through each element's NEXT pointer starting at
10161 HEAD. Each list element appears exactly once in that linked list.
10163 Each element of GROUPS may correspond to one or several mapping nodes.
10164 Node groups are kept together, and in the reordered list, the positions of
10165 the original groups are reused for the positions of the reordered list.
10166 Hence if we have e.g.
10168 {to ptr ptr} firstprivate {tofrom ptr} ...
10169 ^ ^ ^
10170 first group non-"map" second group
10172 and say the second group contains a base pointer for the first so must be
10173 moved before it, the resulting list will contain:
10175 {tofrom ptr} firstprivate {to ptr ptr} ...
10176 ^ prev. second group ^ prev. first group
10179 static tree *
10180 omp_reorder_mapping_groups (vec<omp_mapping_group> *groups,
10181 omp_mapping_group *head,
10182 tree *list_p)
10184 omp_mapping_group *grp;
10185 unsigned int i;
10186 unsigned numgroups = groups->length ();
10187 auto_vec<tree> old_heads (numgroups);
10188 auto_vec<tree *> old_headps (numgroups);
10189 auto_vec<tree> new_heads (numgroups);
10190 auto_vec<tree> old_succs (numgroups);
10191 bool map_at_start = (list_p == (*groups)[0].grp_start);
10193 tree *new_grp_tail = NULL;
10195 /* Stash the start & end nodes of each mapping group before we start
10196 modifying the list. */
10197 FOR_EACH_VEC_ELT (*groups, i, grp)
10199 old_headps.quick_push (grp->grp_start);
10200 old_heads.quick_push (*grp->grp_start);
10201 old_succs.quick_push (OMP_CLAUSE_CHAIN (grp->grp_end));
10204 /* And similarly, the heads of the groups in the order we want to rearrange
10205 the list to. */
10206 for (omp_mapping_group *w = head; w; w = w->next)
10207 new_heads.quick_push (*w->grp_start);
10209 FOR_EACH_VEC_ELT (*groups, i, grp)
10211 gcc_assert (head);
10213 if (new_grp_tail && old_succs[i - 1] == old_heads[i])
10215 /* a {b c d} {e f g} h i j (original)
10217 a {k l m} {e f g} h i j (inserted new group on last iter)
10219 a {k l m} {n o p} h i j (this time, chain last group to new one)
10220 ^new_grp_tail
10222 *new_grp_tail = new_heads[i];
10224 else if (new_grp_tail)
10226 /* a {b c d} e {f g h} i j k (original)
10228 a {l m n} e {f g h} i j k (gap after last iter's group)
10230 a {l m n} e {o p q} h i j (chain last group to old successor)
10231 ^new_grp_tail
10233 *new_grp_tail = old_succs[i - 1];
10234 *old_headps[i] = new_heads[i];
10236 else
10238 /* The first inserted group -- point to new group, and leave end
10239 open.
10240 a {b c d} e f
10242 a {g h i...
10244 *grp->grp_start = new_heads[i];
10247 new_grp_tail = &OMP_CLAUSE_CHAIN (head->grp_end);
10249 head = head->next;
10252 if (new_grp_tail)
10253 *new_grp_tail = old_succs[numgroups - 1];
10255 gcc_assert (!head);
10257 return map_at_start ? (*groups)[0].grp_start : list_p;
10260 /* DECL is supposed to have lastprivate semantics in the outer contexts
10261 of combined/composite constructs, starting with OCTX.
10262 Add needed lastprivate, shared or map clause if no data sharing or
10263 mapping clause are present. IMPLICIT_P is true if it is an implicit
10264 clause (IV on simd), in which case the lastprivate will not be
10265 copied to some constructs. */
10267 static void
10268 omp_lastprivate_for_combined_outer_constructs (struct gimplify_omp_ctx *octx,
10269 tree decl, bool implicit_p)
10271 struct gimplify_omp_ctx *orig_octx = octx;
10272 for (; octx; octx = octx->outer_context)
10274 if ((octx->region_type == ORT_COMBINED_PARALLEL
10275 || (octx->region_type & ORT_COMBINED_TEAMS) == ORT_COMBINED_TEAMS)
10276 && splay_tree_lookup (octx->variables,
10277 (splay_tree_key) decl) == NULL)
10279 omp_add_variable (octx, decl, GOVD_SHARED | GOVD_SEEN);
10280 continue;
10282 if ((octx->region_type & ORT_TASK) != 0
10283 && octx->combined_loop
10284 && splay_tree_lookup (octx->variables,
10285 (splay_tree_key) decl) == NULL)
10287 omp_add_variable (octx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
10288 continue;
10290 if (implicit_p
10291 && octx->region_type == ORT_WORKSHARE
10292 && octx->combined_loop
10293 && splay_tree_lookup (octx->variables,
10294 (splay_tree_key) decl) == NULL
10295 && octx->outer_context
10296 && octx->outer_context->region_type == ORT_COMBINED_PARALLEL
10297 && splay_tree_lookup (octx->outer_context->variables,
10298 (splay_tree_key) decl) == NULL)
10300 octx = octx->outer_context;
10301 omp_add_variable (octx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
10302 continue;
10304 if ((octx->region_type == ORT_WORKSHARE || octx->region_type == ORT_ACC)
10305 && octx->combined_loop
10306 && splay_tree_lookup (octx->variables,
10307 (splay_tree_key) decl) == NULL
10308 && !omp_check_private (octx, decl, false))
10310 omp_add_variable (octx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
10311 continue;
10313 if (octx->region_type == ORT_COMBINED_TARGET)
10315 splay_tree_node n = splay_tree_lookup (octx->variables,
10316 (splay_tree_key) decl);
10317 if (n == NULL)
10319 omp_add_variable (octx, decl, GOVD_MAP | GOVD_SEEN);
10320 octx = octx->outer_context;
10322 else if (!implicit_p
10323 && (n->value & GOVD_FIRSTPRIVATE_IMPLICIT))
10325 n->value &= ~(GOVD_FIRSTPRIVATE
10326 | GOVD_FIRSTPRIVATE_IMPLICIT
10327 | GOVD_EXPLICIT);
10328 omp_add_variable (octx, decl, GOVD_MAP | GOVD_SEEN);
10329 octx = octx->outer_context;
10332 break;
10334 if (octx && (implicit_p || octx != orig_octx))
10335 omp_notice_variable (octx, decl, true);
10338 /* We might have indexed several groups for DECL, e.g. a "TO" mapping and also
10339 a "FIRSTPRIVATE" mapping. Return the one that isn't firstprivate, etc. */
10341 static omp_mapping_group *
10342 omp_get_nonfirstprivate_group (hash_map<tree_operand_hash_no_se,
10343 omp_mapping_group *> *grpmap,
10344 tree decl, bool allow_deleted = false)
10346 omp_mapping_group **to_group_p = grpmap->get (decl);
10348 if (!to_group_p)
10349 return NULL;
10351 omp_mapping_group *to_group = *to_group_p;
10353 for (; to_group; to_group = to_group->sibling)
10355 tree grp_end = to_group->grp_end;
10356 switch (OMP_CLAUSE_MAP_KIND (grp_end))
10358 case GOMP_MAP_FIRSTPRIVATE_POINTER:
10359 case GOMP_MAP_FIRSTPRIVATE_REFERENCE:
10360 break;
10362 default:
10363 if (allow_deleted || !to_group->deleted)
10364 return to_group;
10368 return NULL;
10371 /* Return TRUE if the directive (whose clauses are described by the hash table
10372 of mapping groups, GRPMAP) maps DECL explicitly. If TO_SPECIFICALLY is
10373 true, only count TO mappings. If ALLOW_DELETED is true, ignore the
10374 "deleted" flag for groups. If CONTAINED_IN_STRUCT is true, also return
10375 TRUE if DECL is mapped as a member of a whole-struct mapping. */
10377 static bool
10378 omp_directive_maps_explicitly (hash_map<tree_operand_hash_no_se,
10379 omp_mapping_group *> *grpmap,
10380 tree decl, omp_mapping_group **base_group,
10381 bool to_specifically, bool allow_deleted,
10382 bool contained_in_struct)
10384 omp_mapping_group *decl_group
10385 = omp_get_nonfirstprivate_group (grpmap, decl, allow_deleted);
10387 *base_group = NULL;
10389 if (decl_group)
10391 tree grp_first = *decl_group->grp_start;
10392 /* We might be called during omp_build_struct_sibling_lists, when
10393 GOMP_MAP_STRUCT might have been inserted at the start of the group.
10394 Skip over that, and also possibly the node after it. */
10395 if (OMP_CLAUSE_MAP_KIND (grp_first) == GOMP_MAP_STRUCT
10396 || OMP_CLAUSE_MAP_KIND (grp_first) == GOMP_MAP_STRUCT_UNORD)
10398 grp_first = OMP_CLAUSE_CHAIN (grp_first);
10399 if (OMP_CLAUSE_MAP_KIND (grp_first) == GOMP_MAP_FIRSTPRIVATE_POINTER
10400 || (OMP_CLAUSE_MAP_KIND (grp_first)
10401 == GOMP_MAP_FIRSTPRIVATE_REFERENCE)
10402 || OMP_CLAUSE_MAP_KIND (grp_first) == GOMP_MAP_ATTACH_DETACH)
10403 grp_first = OMP_CLAUSE_CHAIN (grp_first);
10405 enum gomp_map_kind first_kind = OMP_CLAUSE_MAP_KIND (grp_first);
10406 if (!to_specifically
10407 || GOMP_MAP_COPY_TO_P (first_kind)
10408 || first_kind == GOMP_MAP_ALLOC)
10410 *base_group = decl_group;
10411 return true;
10415 if (contained_in_struct
10416 && omp_mapped_by_containing_struct (grpmap, decl, base_group))
10417 return true;
10419 return false;
10422 /* If we have mappings INNER and OUTER, where INNER is a component access and
10423 OUTER is a mapping of the whole containing struct, check that the mappings
10424 are compatible. We'll be deleting the inner mapping, so we need to make
10425 sure the outer mapping does (at least) the same transfers to/from the device
10426 as the inner mapping. */
10428 bool
10429 omp_check_mapping_compatibility (location_t loc,
10430 omp_mapping_group *outer,
10431 omp_mapping_group *inner)
10433 tree first_outer = *outer->grp_start, first_inner = *inner->grp_start;
10435 gcc_assert (OMP_CLAUSE_CODE (first_outer) == OMP_CLAUSE_MAP);
10436 gcc_assert (OMP_CLAUSE_CODE (first_inner) == OMP_CLAUSE_MAP);
10438 enum gomp_map_kind outer_kind = OMP_CLAUSE_MAP_KIND (first_outer);
10439 enum gomp_map_kind inner_kind = OMP_CLAUSE_MAP_KIND (first_inner);
10441 if (outer_kind == inner_kind)
10442 return true;
10444 switch (outer_kind)
10446 case GOMP_MAP_ALWAYS_TO:
10447 if (inner_kind == GOMP_MAP_FORCE_PRESENT
10448 || inner_kind == GOMP_MAP_ALLOC
10449 || inner_kind == GOMP_MAP_TO)
10450 return true;
10451 break;
10453 case GOMP_MAP_ALWAYS_FROM:
10454 if (inner_kind == GOMP_MAP_FORCE_PRESENT
10455 || inner_kind == GOMP_MAP_RELEASE
10456 || inner_kind == GOMP_MAP_FROM)
10457 return true;
10458 break;
10460 case GOMP_MAP_TO:
10461 if (inner_kind == GOMP_MAP_FORCE_PRESENT
10462 || inner_kind == GOMP_MAP_ALLOC)
10463 return true;
10464 break;
10466 case GOMP_MAP_FROM:
10467 if (inner_kind == GOMP_MAP_RELEASE
10468 || inner_kind == GOMP_MAP_FORCE_PRESENT)
10469 return true;
10470 break;
10472 case GOMP_MAP_ALWAYS_TOFROM:
10473 case GOMP_MAP_TOFROM:
10474 if (inner_kind == GOMP_MAP_FORCE_PRESENT
10475 || inner_kind == GOMP_MAP_ALLOC
10476 || inner_kind == GOMP_MAP_TO
10477 || inner_kind == GOMP_MAP_FROM
10478 || inner_kind == GOMP_MAP_TOFROM)
10479 return true;
10480 break;
10482 default:
10486 error_at (loc, "data movement for component %qE is not compatible with "
10487 "movement for struct %qE", OMP_CLAUSE_DECL (first_inner),
10488 OMP_CLAUSE_DECL (first_outer));
10490 return false;
10493 /* This function handles several cases where clauses on a mapping directive
10494 can interact with each other.
10496 If we have a FIRSTPRIVATE_POINTER node and we're also mapping the pointer
10497 on the same directive, change the mapping of the first node to
10498 ATTACH_DETACH. We should have detected that this will happen already in
10499 c-omp.cc:c_omp_adjust_map_clauses and marked the appropriate decl
10500 as addressable. (If we didn't, bail out.)
10502 If we have a FIRSTPRIVATE_REFERENCE (for a reference to pointer) and we're
10503 mapping the base pointer also, we may need to change the mapping type to
10504 ATTACH_DETACH and synthesize an alloc node for the reference itself.
10506 If we have an ATTACH_DETACH node, this is an array section with a pointer
10507 base. If we're mapping the base on the same directive too, we can drop its
10508 mapping. However, if we have a reference to pointer, make other appropriate
10509 adjustments to the mapping nodes instead.
10511 If we have an ATTACH_DETACH node with a Fortran pointer-set (array
10512 descriptor) mapping for a derived-type component, and we're also mapping the
10513 whole of the derived-type variable on another clause, the pointer-set
10514 mapping is removed.
10516 If we have a component access but we're also mapping the whole of the
10517 containing struct, drop the former access.
10519 If the expression is a component access, and we're also mapping a base
10520 pointer used in that component access in the same expression, change the
10521 mapping type of the latter to ALLOC (ready for processing by
10522 omp_build_struct_sibling_lists). */
10524 void
10525 omp_resolve_clause_dependencies (enum tree_code code,
10526 vec<omp_mapping_group> *groups,
10527 hash_map<tree_operand_hash_no_se,
10528 omp_mapping_group *> *grpmap)
10530 int i;
10531 omp_mapping_group *grp;
10532 bool repair_chain = false;
10534 FOR_EACH_VEC_ELT (*groups, i, grp)
10536 tree grp_end = grp->grp_end;
10537 tree decl = OMP_CLAUSE_DECL (grp_end);
10539 gcc_assert (OMP_CLAUSE_CODE (grp_end) == OMP_CLAUSE_MAP);
10541 switch (OMP_CLAUSE_MAP_KIND (grp_end))
10543 case GOMP_MAP_FIRSTPRIVATE_POINTER:
10545 omp_mapping_group *to_group
10546 = omp_get_nonfirstprivate_group (grpmap, decl);
10548 if (!to_group || to_group == grp)
10549 continue;
10551 tree grp_first = *to_group->grp_start;
10552 enum gomp_map_kind first_kind = OMP_CLAUSE_MAP_KIND (grp_first);
10554 if ((GOMP_MAP_COPY_TO_P (first_kind)
10555 || first_kind == GOMP_MAP_ALLOC)
10556 && (OMP_CLAUSE_MAP_KIND (to_group->grp_end)
10557 != GOMP_MAP_FIRSTPRIVATE_POINTER))
10559 gcc_assert (TREE_ADDRESSABLE (OMP_CLAUSE_DECL (grp_end)));
10560 OMP_CLAUSE_SET_MAP_KIND (grp_end, GOMP_MAP_ATTACH_DETACH);
10563 break;
10565 case GOMP_MAP_FIRSTPRIVATE_REFERENCE:
10567 tree ptr = build_fold_indirect_ref (decl);
10569 omp_mapping_group *to_group
10570 = omp_get_nonfirstprivate_group (grpmap, ptr);
10572 if (!to_group || to_group == grp)
10573 continue;
10575 tree grp_first = *to_group->grp_start;
10576 enum gomp_map_kind first_kind = OMP_CLAUSE_MAP_KIND (grp_first);
10578 if (GOMP_MAP_COPY_TO_P (first_kind)
10579 || first_kind == GOMP_MAP_ALLOC)
10581 OMP_CLAUSE_SET_MAP_KIND (grp_end, GOMP_MAP_ATTACH_DETACH);
10582 OMP_CLAUSE_DECL (grp_end) = ptr;
10583 if ((OMP_CLAUSE_CHAIN (*to_group->grp_start)
10584 == to_group->grp_end)
10585 && (OMP_CLAUSE_MAP_KIND (to_group->grp_end)
10586 == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
10588 gcc_assert (TREE_ADDRESSABLE
10589 (OMP_CLAUSE_DECL (to_group->grp_end)));
10590 OMP_CLAUSE_SET_MAP_KIND (to_group->grp_end,
10591 GOMP_MAP_ATTACH_DETACH);
10593 location_t loc = OMP_CLAUSE_LOCATION (to_group->grp_end);
10594 tree alloc
10595 = build_omp_clause (loc, OMP_CLAUSE_MAP);
10596 OMP_CLAUSE_SET_MAP_KIND (alloc, GOMP_MAP_ALLOC);
10597 tree tmp = build_fold_addr_expr (OMP_CLAUSE_DECL
10598 (to_group->grp_end));
10599 tree char_ptr_type = build_pointer_type (char_type_node);
10600 OMP_CLAUSE_DECL (alloc)
10601 = build2 (MEM_REF, char_type_node,
10602 tmp,
10603 build_int_cst (char_ptr_type, 0));
10604 OMP_CLAUSE_SIZE (alloc) = TYPE_SIZE_UNIT (TREE_TYPE (tmp));
10606 OMP_CLAUSE_CHAIN (alloc)
10607 = OMP_CLAUSE_CHAIN (*to_group->grp_start);
10608 OMP_CLAUSE_CHAIN (*to_group->grp_start) = alloc;
10612 break;
10614 case GOMP_MAP_ATTACH_DETACH:
10615 case GOMP_MAP_ATTACH_ZERO_LENGTH_ARRAY_SECTION:
10617 tree base_ptr, referenced_ptr_node = NULL_TREE;
10619 while (TREE_CODE (decl) == ARRAY_REF)
10620 decl = TREE_OPERAND (decl, 0);
10622 if (TREE_CODE (decl) == INDIRECT_REF)
10623 decl = TREE_OPERAND (decl, 0);
10625 /* Only component accesses. */
10626 if (DECL_P (decl))
10627 continue;
10629 /* We want the pointer itself when checking if the base pointer is
10630 mapped elsewhere in the same directive -- if we have a
10631 reference to the pointer, don't use that. */
10633 if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
10634 && TREE_CODE (TREE_TYPE (TREE_TYPE (decl))) == POINTER_TYPE)
10636 referenced_ptr_node = OMP_CLAUSE_CHAIN (*grp->grp_start);
10637 base_ptr = OMP_CLAUSE_DECL (referenced_ptr_node);
10639 else
10640 base_ptr = decl;
10642 gomp_map_kind zlas_kind
10643 = (code == OACC_EXIT_DATA || code == OMP_TARGET_EXIT_DATA)
10644 ? GOMP_MAP_DETACH : GOMP_MAP_ATTACH_ZERO_LENGTH_ARRAY_SECTION;
10646 if (TREE_CODE (TREE_TYPE (base_ptr)) == POINTER_TYPE)
10648 /* If we map the base TO, and we're doing an attachment, we can
10649 skip the TO mapping altogether and create an ALLOC mapping
10650 instead, since the attachment will overwrite the device
10651 pointer in that location immediately anyway. Otherwise,
10652 change our mapping to
10653 GOMP_MAP_ATTACH_ZERO_LENGTH_ARRAY_SECTION in case the
10654 attachment target has not been copied to the device already
10655 by some earlier directive. */
10657 bool base_mapped_to = false;
10659 omp_mapping_group *base_group;
10661 if (omp_directive_maps_explicitly (grpmap, base_ptr,
10662 &base_group, false, true,
10663 false))
10665 if (referenced_ptr_node)
10667 base_mapped_to = true;
10668 if ((OMP_CLAUSE_MAP_KIND (base_group->grp_end)
10669 == GOMP_MAP_ATTACH_DETACH)
10670 && (OMP_CLAUSE_CHAIN (*base_group->grp_start)
10671 == base_group->grp_end))
10673 OMP_CLAUSE_CHAIN (*base_group->grp_start)
10674 = OMP_CLAUSE_CHAIN (base_group->grp_end);
10675 base_group->grp_end = *base_group->grp_start;
10676 repair_chain = true;
10679 else
10681 base_group->deleted = true;
10682 OMP_CLAUSE_ATTACHMENT_MAPPING_ERASED (grp_end) = 1;
10686 /* We're dealing with a reference to a pointer, and we are
10687 attaching both the reference and the pointer. We know the
10688 reference itself is on the target, because we are going to
10689 create an ALLOC node for it in accumulate_sibling_list. The
10690 pointer might be on the target already or it might not, but
10691 if it isn't then it's not an error, so use
10692 GOMP_MAP_ATTACH_ZLAS for it. */
10693 if (!base_mapped_to && referenced_ptr_node)
10694 OMP_CLAUSE_SET_MAP_KIND (referenced_ptr_node, zlas_kind);
10696 omp_mapping_group *struct_group;
10697 tree desc;
10698 if ((desc = OMP_CLAUSE_CHAIN (*grp->grp_start))
10699 && omp_map_clause_descriptor_p (desc)
10700 && omp_mapped_by_containing_struct (grpmap, decl,
10701 &struct_group))
10702 /* If we have a pointer set but we're mapping (or unmapping)
10703 the whole of the containing struct, we can remove the
10704 pointer set mapping. */
10705 OMP_CLAUSE_CHAIN (*grp->grp_start) = OMP_CLAUSE_CHAIN (desc);
10707 else if (TREE_CODE (TREE_TYPE (base_ptr)) == REFERENCE_TYPE
10708 && (TREE_CODE (TREE_TYPE (TREE_TYPE (base_ptr)))
10709 == ARRAY_TYPE)
10710 && OMP_CLAUSE_MAP_MAYBE_ZERO_LENGTH_ARRAY_SECTION
10711 (*grp->grp_start))
10712 OMP_CLAUSE_SET_MAP_KIND (grp->grp_end, zlas_kind);
10714 break;
10716 case GOMP_MAP_ATTACH:
10717 /* Ignore standalone attach here. */
10718 break;
10720 default:
10722 omp_mapping_group *struct_group;
10723 if (omp_mapped_by_containing_struct (grpmap, decl, &struct_group)
10724 && *grp->grp_start == grp_end)
10726 omp_check_mapping_compatibility (OMP_CLAUSE_LOCATION (grp_end),
10727 struct_group, grp);
10728 /* Remove the whole of this mapping -- redundant. */
10729 grp->deleted = true;
10732 tree base = decl;
10733 while ((base = omp_get_base_pointer (base)))
10735 omp_mapping_group *base_group;
10737 if (omp_directive_maps_explicitly (grpmap, base, &base_group,
10738 true, true, false))
10740 tree grp_first = *base_group->grp_start;
10741 OMP_CLAUSE_SET_MAP_KIND (grp_first, GOMP_MAP_ALLOC);
10748 if (repair_chain)
10750 /* Group start pointers may have become detached from the
10751 OMP_CLAUSE_CHAIN of previous groups if elements were removed from the
10752 end of those groups. Fix that now. */
10753 tree *new_next = NULL;
10754 FOR_EACH_VEC_ELT (*groups, i, grp)
10756 if (new_next)
10757 grp->grp_start = new_next;
10759 new_next = &OMP_CLAUSE_CHAIN (grp->grp_end);
10764 /* Similar to omp_resolve_clause_dependencies, but for OpenACC. The only
10765 clause dependencies we handle for now are struct element mappings and
10766 whole-struct mappings on the same directive, and duplicate clause
10767 detection. */
10769 void
10770 oacc_resolve_clause_dependencies (vec<omp_mapping_group> *groups,
10771 hash_map<tree_operand_hash_no_se,
10772 omp_mapping_group *> *grpmap)
10774 int i;
10775 omp_mapping_group *grp;
10776 hash_set<tree_operand_hash> *seen_components = NULL;
10777 hash_set<tree_operand_hash> *shown_error = NULL;
10779 FOR_EACH_VEC_ELT (*groups, i, grp)
10781 tree grp_end = grp->grp_end;
10782 tree decl = OMP_CLAUSE_DECL (grp_end);
10784 gcc_assert (OMP_CLAUSE_CODE (grp_end) == OMP_CLAUSE_MAP);
10786 if (DECL_P (grp_end))
10787 continue;
10789 tree c = OMP_CLAUSE_DECL (*grp->grp_start);
10790 while (TREE_CODE (c) == ARRAY_REF)
10791 c = TREE_OPERAND (c, 0);
10792 if (TREE_CODE (c) != COMPONENT_REF)
10793 continue;
10794 if (!seen_components)
10795 seen_components = new hash_set<tree_operand_hash> ();
10796 if (!shown_error)
10797 shown_error = new hash_set<tree_operand_hash> ();
10798 if (seen_components->contains (c)
10799 && !shown_error->contains (c))
10801 error_at (OMP_CLAUSE_LOCATION (grp_end),
10802 "%qE appears more than once in map clauses",
10803 OMP_CLAUSE_DECL (grp_end));
10804 shown_error->add (c);
10806 else
10807 seen_components->add (c);
10809 omp_mapping_group *struct_group;
10810 if (omp_mapped_by_containing_struct (grpmap, decl, &struct_group)
10811 && *grp->grp_start == grp_end)
10813 omp_check_mapping_compatibility (OMP_CLAUSE_LOCATION (grp_end),
10814 struct_group, grp);
10815 /* Remove the whole of this mapping -- redundant. */
10816 grp->deleted = true;
10820 if (seen_components)
10821 delete seen_components;
10822 if (shown_error)
10823 delete shown_error;
10826 /* Link node NEWNODE so it is pointed to by chain INSERT_AT. NEWNODE's chain
10827 is linked to the previous node pointed to by INSERT_AT. */
10829 static tree *
10830 omp_siblist_insert_node_after (tree newnode, tree *insert_at)
10832 OMP_CLAUSE_CHAIN (newnode) = *insert_at;
10833 *insert_at = newnode;
10834 return &OMP_CLAUSE_CHAIN (newnode);
10837 /* Move NODE (which is currently pointed to by the chain OLD_POS) so it is
10838 pointed to by chain MOVE_AFTER instead. */
10840 static void
10841 omp_siblist_move_node_after (tree node, tree *old_pos, tree *move_after)
10843 gcc_assert (node == *old_pos);
10844 *old_pos = OMP_CLAUSE_CHAIN (node);
10845 OMP_CLAUSE_CHAIN (node) = *move_after;
10846 *move_after = node;
10849 /* Move nodes from FIRST_PTR (pointed to by previous node's chain) to
10850 LAST_NODE to after MOVE_AFTER chain. Similar to below function, but no
10851 new nodes are prepended to the list before splicing into the new position.
10852 Return the position we should continue scanning the list at, or NULL to
10853 stay where we were. */
10855 static tree *
10856 omp_siblist_move_nodes_after (tree *first_ptr, tree last_node,
10857 tree *move_after)
10859 if (first_ptr == move_after)
10860 return NULL;
10862 tree tmp = *first_ptr;
10863 *first_ptr = OMP_CLAUSE_CHAIN (last_node);
10864 OMP_CLAUSE_CHAIN (last_node) = *move_after;
10865 *move_after = tmp;
10867 return first_ptr;
10870 /* Concatenate two lists described by [FIRST_NEW, LAST_NEW_TAIL] and
10871 [FIRST_PTR, LAST_NODE], and insert them in the OMP clause list after chain
10872 pointer MOVE_AFTER.
10874 The latter list was previously part of the OMP clause list, and the former
10875 (prepended) part is comprised of new nodes.
10877 We start with a list of nodes starting with a struct mapping node. We
10878 rearrange the list so that new nodes starting from FIRST_NEW and whose last
10879 node's chain is LAST_NEW_TAIL comes directly after MOVE_AFTER, followed by
10880 the group of mapping nodes we are currently processing (from the chain
10881 FIRST_PTR to LAST_NODE). The return value is the pointer to the next chain
10882 we should continue processing from, or NULL to stay where we were.
10884 The transformation (in the case where MOVE_AFTER and FIRST_PTR are
10885 different) is worked through below. Here we are processing LAST_NODE, and
10886 FIRST_PTR points at the preceding mapping clause:
10888 #. mapping node chain
10889 ---------------------------------------------------
10890 A. struct_node [->B]
10891 B. comp_1 [->C]
10892 C. comp_2 [->D (move_after)]
10893 D. map_to_3 [->E]
10894 E. attach_3 [->F (first_ptr)]
10895 F. map_to_4 [->G (continue_at)]
10896 G. attach_4 (last_node) [->H]
10897 H. ...
10899 *last_new_tail = *first_ptr;
10901 I. new_node (first_new) [->F (last_new_tail)]
10903 *first_ptr = OMP_CLAUSE_CHAIN (last_node)
10905 #. mapping node chain
10906 ----------------------------------------------------
10907 A. struct_node [->B]
10908 B. comp_1 [->C]
10909 C. comp_2 [->D (move_after)]
10910 D. map_to_3 [->E]
10911 E. attach_3 [->H (first_ptr)]
10912 F. map_to_4 [->G (continue_at)]
10913 G. attach_4 (last_node) [->H]
10914 H. ...
10916 I. new_node (first_new) [->F (last_new_tail)]
10918 OMP_CLAUSE_CHAIN (last_node) = *move_after;
10920 #. mapping node chain
10921 ---------------------------------------------------
10922 A. struct_node [->B]
10923 B. comp_1 [->C]
10924 C. comp_2 [->D (move_after)]
10925 D. map_to_3 [->E]
10926 E. attach_3 [->H (continue_at)]
10927 F. map_to_4 [->G]
10928 G. attach_4 (last_node) [->D]
10929 H. ...
10931 I. new_node (first_new) [->F (last_new_tail)]
10933 *move_after = first_new;
10935 #. mapping node chain
10936 ---------------------------------------------------
10937 A. struct_node [->B]
10938 B. comp_1 [->C]
10939 C. comp_2 [->I (move_after)]
10940 D. map_to_3 [->E]
10941 E. attach_3 [->H (continue_at)]
10942 F. map_to_4 [->G]
10943 G. attach_4 (last_node) [->D]
10944 H. ...
10945 I. new_node (first_new) [->F (last_new_tail)]
10947 or, in order:
10949 #. mapping node chain
10950 ---------------------------------------------------
10951 A. struct_node [->B]
10952 B. comp_1 [->C]
10953 C. comp_2 [->I (move_after)]
10954 I. new_node (first_new) [->F (last_new_tail)]
10955 F. map_to_4 [->G]
10956 G. attach_4 (last_node) [->D]
10957 D. map_to_3 [->E]
10958 E. attach_3 [->H (continue_at)]
10959 H. ...
10962 static tree *
10963 omp_siblist_move_concat_nodes_after (tree first_new, tree *last_new_tail,
10964 tree *first_ptr, tree last_node,
10965 tree *move_after)
10967 tree *continue_at = NULL;
10968 *last_new_tail = *first_ptr;
10969 if (first_ptr == move_after)
10970 *move_after = first_new;
10971 else
10973 *first_ptr = OMP_CLAUSE_CHAIN (last_node);
10974 continue_at = first_ptr;
10975 OMP_CLAUSE_CHAIN (last_node) = *move_after;
10976 *move_after = first_new;
10978 return continue_at;
10981 static omp_addr_token *
10982 omp_first_chained_access_token (vec<omp_addr_token *> &addr_tokens)
10984 using namespace omp_addr_tokenizer;
10985 int idx = addr_tokens.length () - 1;
10986 gcc_assert (idx >= 0);
10987 if (addr_tokens[idx]->type != ACCESS_METHOD)
10988 return addr_tokens[idx];
10989 while (idx > 0 && addr_tokens[idx - 1]->type == ACCESS_METHOD)
10990 idx--;
10991 return addr_tokens[idx];
10994 /* Mapping struct members causes an additional set of nodes to be created,
10995 starting with GOMP_MAP_STRUCT followed by a number of mappings equal to the
10996 number of members being mapped, in order of ascending position (address or
10997 bitwise).
10999 We scan through the list of mapping clauses, calling this function for each
11000 struct member mapping we find, and build up the list of mappings after the
11001 initial GOMP_MAP_STRUCT node. For pointer members, these will be
11002 newly-created ALLOC nodes. For non-pointer members, the existing mapping is
11003 moved into place in the sorted list.
11005 struct {
11006 int *a;
11007 int *b;
11008 int c;
11009 int *d;
11012 #pragma (acc|omp directive) copy(struct.a[0:n], struct.b[0:n], struct.c,
11013 struct.d[0:n])
11015 GOMP_MAP_STRUCT (4)
11016 [GOMP_MAP_FIRSTPRIVATE_REFERENCE -- for refs to structs]
11017 GOMP_MAP_ALLOC (struct.a)
11018 GOMP_MAP_ALLOC (struct.b)
11019 GOMP_MAP_TO (struct.c)
11020 GOMP_MAP_ALLOC (struct.d)
11023 In the case where we are mapping references to pointers, or in Fortran if
11024 we are mapping an array with a descriptor, additional nodes may be created
11025 after the struct node list also.
11027 The return code is either a pointer to the next node to process (if the
11028 list has been rearranged), else NULL to continue with the next node in the
11029 original list. */
11031 static tree *
11032 omp_accumulate_sibling_list (enum omp_region_type region_type,
11033 enum tree_code code,
11034 hash_map<tree_operand_hash, tree>
11035 *&struct_map_to_clause,
11036 hash_map<tree_operand_hash_no_se,
11037 omp_mapping_group *> *group_map,
11038 tree *grp_start_p, tree grp_end,
11039 vec<omp_addr_token *> &addr_tokens, tree **inner,
11040 bool *fragile_p, bool reprocessing_struct,
11041 tree **added_tail)
11043 using namespace omp_addr_tokenizer;
11044 poly_offset_int coffset;
11045 poly_int64 cbitpos;
11046 tree ocd = OMP_CLAUSE_DECL (grp_end);
11047 bool openmp = !(region_type & ORT_ACC);
11048 bool target = (region_type & ORT_TARGET) != 0;
11049 tree *continue_at = NULL;
11051 while (TREE_CODE (ocd) == ARRAY_REF)
11052 ocd = TREE_OPERAND (ocd, 0);
11054 if (*fragile_p)
11056 omp_mapping_group *to_group
11057 = omp_get_nonfirstprivate_group (group_map, ocd, true);
11059 if (to_group)
11060 return NULL;
11063 omp_addr_token *last_token = omp_first_chained_access_token (addr_tokens);
11064 if (last_token->type == ACCESS_METHOD)
11066 switch (last_token->u.access_kind)
11068 case ACCESS_REF:
11069 case ACCESS_REF_TO_POINTER:
11070 case ACCESS_REF_TO_POINTER_OFFSET:
11071 case ACCESS_INDEXED_REF_TO_ARRAY:
11072 /* We may see either a bare reference or a dereferenced
11073 "convert_from_reference"-like one here. Handle either way. */
11074 if (TREE_CODE (ocd) == INDIRECT_REF)
11075 ocd = TREE_OPERAND (ocd, 0);
11076 gcc_assert (TREE_CODE (TREE_TYPE (ocd)) == REFERENCE_TYPE);
11077 break;
11079 default:
11084 bool variable_offset;
11085 tree base
11086 = extract_base_bit_offset (ocd, &cbitpos, &coffset, &variable_offset);
11088 int base_token;
11089 for (base_token = addr_tokens.length () - 1; base_token >= 0; base_token--)
11091 if (addr_tokens[base_token]->type == ARRAY_BASE
11092 || addr_tokens[base_token]->type == STRUCTURE_BASE)
11093 break;
11096 /* The two expressions in the assertion below aren't quite the same: if we
11097 have 'struct_base_decl access_indexed_array' for something like
11098 "myvar[2].x" then base will be "myvar" and addr_tokens[base_token]->expr
11099 will be "myvar[2]" -- the actual base of the structure.
11100 The former interpretation leads to a strange situation where we get
11101 struct(myvar) alloc(myvar[2].ptr1)
11102 That is, the array of structures is kind of treated as one big structure
11103 for the purposes of gathering sibling lists, etc. */
11104 /* gcc_assert (base == addr_tokens[base_token]->expr); */
11106 bool attach_detach = ((OMP_CLAUSE_MAP_KIND (grp_end)
11107 == GOMP_MAP_ATTACH_DETACH)
11108 || (OMP_CLAUSE_MAP_KIND (grp_end)
11109 == GOMP_MAP_ATTACH_ZERO_LENGTH_ARRAY_SECTION));
11110 bool has_descriptor = false;
11111 if (OMP_CLAUSE_CHAIN (*grp_start_p) != grp_end)
11113 tree grp_mid = OMP_CLAUSE_CHAIN (*grp_start_p);
11114 if (grp_mid && omp_map_clause_descriptor_p (grp_mid))
11115 has_descriptor = true;
11118 if (!struct_map_to_clause || struct_map_to_clause->get (base) == NULL)
11120 enum gomp_map_kind str_kind = GOMP_MAP_STRUCT;
11122 if (struct_map_to_clause == NULL)
11123 struct_map_to_clause = new hash_map<tree_operand_hash, tree>;
11125 if (variable_offset)
11126 str_kind = GOMP_MAP_STRUCT_UNORD;
11128 tree l = build_omp_clause (OMP_CLAUSE_LOCATION (grp_end), OMP_CLAUSE_MAP);
11130 OMP_CLAUSE_SET_MAP_KIND (l, str_kind);
11131 OMP_CLAUSE_DECL (l) = unshare_expr (base);
11132 OMP_CLAUSE_SIZE (l) = size_int (1);
11134 struct_map_to_clause->put (base, l);
11136 /* On first iterating through the clause list, we insert the struct node
11137 just before the component access node that triggers the initial
11138 omp_accumulate_sibling_list call for a particular sibling list (and
11139 it then forms the first entry in that list). When reprocessing
11140 struct bases that are themselves component accesses, we insert the
11141 struct node on an off-side list to avoid inserting the new
11142 GOMP_MAP_STRUCT into the middle of the old one. */
11143 tree *insert_node_pos = reprocessing_struct ? *added_tail : grp_start_p;
11145 if (has_descriptor)
11147 tree desc = OMP_CLAUSE_CHAIN (*grp_start_p);
11148 if (code == OMP_TARGET_EXIT_DATA || code == OACC_EXIT_DATA)
11149 OMP_CLAUSE_SET_MAP_KIND (desc, GOMP_MAP_RELEASE);
11150 tree sc = *insert_node_pos;
11151 OMP_CLAUSE_CHAIN (l) = desc;
11152 OMP_CLAUSE_CHAIN (*grp_start_p) = OMP_CLAUSE_CHAIN (desc);
11153 OMP_CLAUSE_CHAIN (desc) = sc;
11154 *insert_node_pos = l;
11156 else if (attach_detach)
11158 tree extra_node;
11159 tree alloc_node
11160 = build_omp_struct_comp_nodes (code, *grp_start_p, grp_end,
11161 &extra_node);
11162 tree *tail;
11163 OMP_CLAUSE_CHAIN (l) = alloc_node;
11165 if (extra_node)
11167 OMP_CLAUSE_CHAIN (extra_node) = *insert_node_pos;
11168 OMP_CLAUSE_CHAIN (alloc_node) = extra_node;
11169 tail = &OMP_CLAUSE_CHAIN (extra_node);
11171 else
11173 OMP_CLAUSE_CHAIN (alloc_node) = *insert_node_pos;
11174 tail = &OMP_CLAUSE_CHAIN (alloc_node);
11177 /* For OpenMP semantics, we don't want to implicitly allocate
11178 space for the pointer here for non-compute regions (e.g. "enter
11179 data"). A FRAGILE_P node is only being created so that
11180 omp-low.cc is able to rewrite the struct properly.
11181 For references (to pointers), we want to actually allocate the
11182 space for the reference itself in the sorted list following the
11183 struct node.
11184 For pointers, we want to allocate space if we had an explicit
11185 mapping of the attachment point, but not otherwise. */
11186 if (*fragile_p
11187 || (openmp
11188 && !target
11189 && attach_detach
11190 && TREE_CODE (TREE_TYPE (ocd)) == POINTER_TYPE
11191 && !OMP_CLAUSE_ATTACHMENT_MAPPING_ERASED (grp_end)))
11193 if (!lang_GNU_Fortran ())
11194 /* In Fortran, pointers are dereferenced automatically, but may
11195 be unassociated. So we still want to allocate space for the
11196 pointer (as the base for an attach operation that should be
11197 present in the same directive's clause list also). */
11198 OMP_CLAUSE_SIZE (alloc_node) = size_zero_node;
11199 OMP_CLAUSE_MAP_MAYBE_ZERO_LENGTH_ARRAY_SECTION (alloc_node) = 1;
11202 *insert_node_pos = l;
11204 if (reprocessing_struct)
11206 /* When reprocessing a struct node group used as the base of a
11207 subcomponent access, if we have a reference-to-pointer base,
11208 we will see:
11209 struct(**ptr) attach(*ptr)
11210 whereas for a non-reprocess-struct group, we see, e.g.:
11211 tofrom(**ptr) attach(*ptr) attach(ptr)
11212 and we create the "alloc" for the second "attach", i.e.
11213 for the reference itself. When reprocessing a struct group we
11214 thus change the pointer attachment into a reference attachment
11215 by stripping the indirection. (The attachment of the
11216 referenced pointer must happen elsewhere, either on the same
11217 directive, or otherwise.) */
11218 tree adecl = OMP_CLAUSE_DECL (alloc_node);
11220 if ((TREE_CODE (adecl) == INDIRECT_REF
11221 || (TREE_CODE (adecl) == MEM_REF
11222 && integer_zerop (TREE_OPERAND (adecl, 1))))
11223 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (adecl, 0)))
11224 == REFERENCE_TYPE)
11225 && (TREE_CODE (TREE_TYPE (TREE_TYPE
11226 (TREE_OPERAND (adecl, 0)))) == POINTER_TYPE))
11227 OMP_CLAUSE_DECL (alloc_node) = TREE_OPERAND (adecl, 0);
11229 *added_tail = tail;
11232 else
11234 gcc_assert (*grp_start_p == grp_end);
11235 if (reprocessing_struct)
11237 /* If we don't have an attach/detach node, this is a
11238 "target data" directive or similar, not an offload region.
11239 Synthesize an "alloc" node using just the initiating
11240 GOMP_MAP_STRUCT decl. */
11241 gomp_map_kind k = (code == OMP_TARGET_EXIT_DATA
11242 || code == OACC_EXIT_DATA)
11243 ? GOMP_MAP_RELEASE : GOMP_MAP_ALLOC;
11244 tree alloc_node
11245 = build_omp_clause (OMP_CLAUSE_LOCATION (grp_end),
11246 OMP_CLAUSE_MAP);
11247 OMP_CLAUSE_SET_MAP_KIND (alloc_node, k);
11248 OMP_CLAUSE_DECL (alloc_node) = unshare_expr (last_token->expr);
11249 OMP_CLAUSE_SIZE (alloc_node)
11250 = TYPE_SIZE_UNIT (TREE_TYPE (OMP_CLAUSE_DECL (alloc_node)));
11252 OMP_CLAUSE_CHAIN (alloc_node) = OMP_CLAUSE_CHAIN (l);
11253 OMP_CLAUSE_CHAIN (l) = alloc_node;
11254 *insert_node_pos = l;
11255 *added_tail = &OMP_CLAUSE_CHAIN (alloc_node);
11257 else
11258 grp_start_p = omp_siblist_insert_node_after (l, insert_node_pos);
11261 unsigned last_access = base_token + 1;
11263 while (last_access + 1 < addr_tokens.length ()
11264 && addr_tokens[last_access + 1]->type == ACCESS_METHOD)
11265 last_access++;
11267 if ((region_type & ORT_TARGET)
11268 && addr_tokens[base_token + 1]->type == ACCESS_METHOD)
11270 bool base_ref = false;
11271 access_method_kinds access_kind
11272 = addr_tokens[last_access]->u.access_kind;
11274 switch (access_kind)
11276 case ACCESS_DIRECT:
11277 case ACCESS_INDEXED_ARRAY:
11278 return NULL;
11280 case ACCESS_REF:
11281 case ACCESS_REF_TO_POINTER:
11282 case ACCESS_REF_TO_POINTER_OFFSET:
11283 case ACCESS_INDEXED_REF_TO_ARRAY:
11284 base_ref = true;
11285 break;
11287 default:
11290 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (grp_end),
11291 OMP_CLAUSE_MAP);
11292 enum gomp_map_kind mkind;
11293 omp_mapping_group *decl_group;
11294 tree use_base;
11295 switch (access_kind)
11297 case ACCESS_POINTER:
11298 case ACCESS_POINTER_OFFSET:
11299 use_base = addr_tokens[last_access]->expr;
11300 break;
11301 case ACCESS_REF_TO_POINTER:
11302 case ACCESS_REF_TO_POINTER_OFFSET:
11303 use_base
11304 = build_fold_indirect_ref (addr_tokens[last_access]->expr);
11305 break;
11306 default:
11307 use_base = addr_tokens[base_token]->expr;
11309 bool mapped_to_p
11310 = omp_directive_maps_explicitly (group_map, use_base, &decl_group,
11311 true, false, true);
11312 if (addr_tokens[base_token]->type == STRUCTURE_BASE
11313 && DECL_P (addr_tokens[last_access]->expr)
11314 && !mapped_to_p)
11315 mkind = base_ref ? GOMP_MAP_FIRSTPRIVATE_REFERENCE
11316 : GOMP_MAP_FIRSTPRIVATE_POINTER;
11317 else
11318 mkind = GOMP_MAP_ATTACH_DETACH;
11320 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
11321 /* If we have a reference to pointer base, we want to attach the
11322 pointer here, not the reference. The reference attachment happens
11323 elsewhere. */
11324 bool ref_to_ptr
11325 = (access_kind == ACCESS_REF_TO_POINTER
11326 || access_kind == ACCESS_REF_TO_POINTER_OFFSET);
11327 tree sdecl = addr_tokens[last_access]->expr;
11328 tree sdecl_ptr = ref_to_ptr ? build_fold_indirect_ref (sdecl)
11329 : sdecl;
11330 /* For the FIRSTPRIVATE_REFERENCE after the struct node, we
11331 want to use the reference itself for the decl, but we
11332 still want to use the pointer to calculate the bias. */
11333 OMP_CLAUSE_DECL (c2) = (mkind == GOMP_MAP_ATTACH_DETACH)
11334 ? sdecl_ptr : sdecl;
11335 sdecl = sdecl_ptr;
11336 tree baddr = build_fold_addr_expr (base);
11337 baddr = fold_convert_loc (OMP_CLAUSE_LOCATION (grp_end),
11338 ptrdiff_type_node, baddr);
11339 tree decladdr = fold_convert_loc (OMP_CLAUSE_LOCATION (grp_end),
11340 ptrdiff_type_node, sdecl);
11341 OMP_CLAUSE_SIZE (c2)
11342 = fold_build2_loc (OMP_CLAUSE_LOCATION (grp_end), MINUS_EXPR,
11343 ptrdiff_type_node, baddr, decladdr);
11344 /* Insert after struct node. */
11345 OMP_CLAUSE_CHAIN (c2) = OMP_CLAUSE_CHAIN (l);
11346 OMP_CLAUSE_CHAIN (l) = c2;
11348 if (addr_tokens[base_token]->type == STRUCTURE_BASE
11349 && (addr_tokens[base_token]->u.structure_base_kind
11350 == BASE_COMPONENT_EXPR)
11351 && mkind == GOMP_MAP_ATTACH_DETACH
11352 && addr_tokens[last_access]->u.access_kind != ACCESS_REF)
11354 *inner = insert_node_pos;
11355 if (openmp)
11356 *fragile_p = true;
11357 return NULL;
11361 if (addr_tokens[base_token]->type == STRUCTURE_BASE
11362 && (addr_tokens[base_token]->u.structure_base_kind
11363 == BASE_COMPONENT_EXPR)
11364 && addr_tokens[last_access]->u.access_kind == ACCESS_REF)
11365 *inner = insert_node_pos;
11367 return NULL;
11369 else if (struct_map_to_clause)
11371 tree *osc = struct_map_to_clause->get (base);
11372 tree *sc = NULL, *scp = NULL;
11373 bool unordered = false;
11375 if (osc && OMP_CLAUSE_MAP_KIND (*osc) == GOMP_MAP_STRUCT_UNORD)
11376 unordered = true;
11378 unsigned HOST_WIDE_INT i, elems = tree_to_uhwi (OMP_CLAUSE_SIZE (*osc));
11379 sc = &OMP_CLAUSE_CHAIN (*osc);
11380 /* The struct mapping might be immediately followed by a
11381 FIRSTPRIVATE_POINTER, FIRSTPRIVATE_REFERENCE or an ATTACH_DETACH --
11382 if it's an indirect access or a reference, or if the structure base
11383 is not a decl. The FIRSTPRIVATE_* nodes are removed in omp-low.cc
11384 after they have been processed there, and ATTACH_DETACH nodes are
11385 recomputed and moved out of the GOMP_MAP_STRUCT construct once
11386 sibling list building is complete. */
11387 if (OMP_CLAUSE_MAP_KIND (*sc) == GOMP_MAP_FIRSTPRIVATE_POINTER
11388 || OMP_CLAUSE_MAP_KIND (*sc) == GOMP_MAP_FIRSTPRIVATE_REFERENCE
11389 || OMP_CLAUSE_MAP_KIND (*sc) == GOMP_MAP_ATTACH_DETACH)
11390 sc = &OMP_CLAUSE_CHAIN (*sc);
11391 for (i = 0; i < elems; i++, sc = &OMP_CLAUSE_CHAIN (*sc))
11392 if (attach_detach && sc == grp_start_p)
11393 break;
11394 else if (TREE_CODE (OMP_CLAUSE_DECL (*sc)) != COMPONENT_REF
11395 && TREE_CODE (OMP_CLAUSE_DECL (*sc)) != INDIRECT_REF
11396 && TREE_CODE (OMP_CLAUSE_DECL (*sc)) != ARRAY_REF)
11397 break;
11398 else
11400 tree sc_decl = OMP_CLAUSE_DECL (*sc);
11401 poly_offset_int offset;
11402 poly_int64 bitpos;
11404 if (TREE_CODE (sc_decl) == ARRAY_REF)
11406 while (TREE_CODE (sc_decl) == ARRAY_REF)
11407 sc_decl = TREE_OPERAND (sc_decl, 0);
11408 if (TREE_CODE (sc_decl) != COMPONENT_REF
11409 || TREE_CODE (TREE_TYPE (sc_decl)) != ARRAY_TYPE)
11410 break;
11412 else if (INDIRECT_REF_P (sc_decl)
11413 && TREE_CODE (TREE_OPERAND (sc_decl, 0)) == COMPONENT_REF
11414 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (sc_decl, 0)))
11415 == REFERENCE_TYPE))
11416 sc_decl = TREE_OPERAND (sc_decl, 0);
11418 bool variable_offset2;
11419 tree base2 = extract_base_bit_offset (sc_decl, &bitpos, &offset,
11420 &variable_offset2);
11421 if (!base2 || !operand_equal_p (base2, base, 0))
11422 break;
11423 if (scp)
11424 continue;
11425 if (variable_offset2)
11427 OMP_CLAUSE_SET_MAP_KIND (*osc, GOMP_MAP_STRUCT_UNORD);
11428 unordered = true;
11429 break;
11431 else if ((region_type & ORT_ACC) != 0)
11433 /* For OpenACC, allow (ignore) duplicate struct accesses in
11434 the middle of a mapping clause, e.g. "mystruct->foo" in:
11435 copy(mystruct->foo->bar) copy(mystruct->foo->qux). */
11436 if (reprocessing_struct
11437 && known_eq (coffset, offset)
11438 && known_eq (cbitpos, bitpos))
11439 return NULL;
11441 else if (known_eq (coffset, offset)
11442 && known_eq (cbitpos, bitpos))
11444 /* Having two struct members at the same offset doesn't work,
11445 so make sure we don't. (We're allowed to ignore this.
11446 Should we report the error?) */
11447 /*error_at (OMP_CLAUSE_LOCATION (grp_end),
11448 "duplicate struct member %qE in map clauses",
11449 OMP_CLAUSE_DECL (grp_end));*/
11450 return NULL;
11452 if (maybe_lt (coffset, offset)
11453 || (known_eq (coffset, offset)
11454 && maybe_lt (cbitpos, bitpos)))
11456 if (attach_detach)
11457 scp = sc;
11458 else
11459 break;
11463 /* If this is an unordered struct, just insert the new element at the
11464 end of the list. */
11465 if (unordered)
11467 for (; i < elems; i++)
11468 sc = &OMP_CLAUSE_CHAIN (*sc);
11469 scp = NULL;
11472 OMP_CLAUSE_SIZE (*osc)
11473 = size_binop (PLUS_EXPR, OMP_CLAUSE_SIZE (*osc), size_one_node);
11475 if (reprocessing_struct)
11477 /* If we're reprocessing a struct node, we don't want to do most of
11478 the list manipulation below. We only need to handle the (pointer
11479 or reference) attach/detach case. */
11480 tree extra_node, alloc_node;
11481 if (has_descriptor)
11482 gcc_unreachable ();
11483 else if (attach_detach)
11484 alloc_node = build_omp_struct_comp_nodes (code, *grp_start_p,
11485 grp_end, &extra_node);
11486 else
11488 /* If we don't have an attach/detach node, this is a
11489 "target data" directive or similar, not an offload region.
11490 Synthesize an "alloc" node using just the initiating
11491 GOMP_MAP_STRUCT decl. */
11492 gomp_map_kind k = (code == OMP_TARGET_EXIT_DATA
11493 || code == OACC_EXIT_DATA)
11494 ? GOMP_MAP_RELEASE : GOMP_MAP_ALLOC;
11495 alloc_node
11496 = build_omp_clause (OMP_CLAUSE_LOCATION (grp_end),
11497 OMP_CLAUSE_MAP);
11498 OMP_CLAUSE_SET_MAP_KIND (alloc_node, k);
11499 OMP_CLAUSE_DECL (alloc_node) = unshare_expr (last_token->expr);
11500 OMP_CLAUSE_SIZE (alloc_node)
11501 = TYPE_SIZE_UNIT (TREE_TYPE (OMP_CLAUSE_DECL (alloc_node)));
11504 if (scp)
11505 omp_siblist_insert_node_after (alloc_node, scp);
11506 else
11508 tree *new_end = omp_siblist_insert_node_after (alloc_node, sc);
11509 if (sc == *added_tail)
11510 *added_tail = new_end;
11513 return NULL;
11516 if (has_descriptor)
11518 tree desc = OMP_CLAUSE_CHAIN (*grp_start_p);
11519 if (code == OMP_TARGET_EXIT_DATA
11520 || code == OACC_EXIT_DATA)
11521 OMP_CLAUSE_SET_MAP_KIND (desc, GOMP_MAP_RELEASE);
11522 omp_siblist_move_node_after (desc,
11523 &OMP_CLAUSE_CHAIN (*grp_start_p),
11524 scp ? scp : sc);
11526 else if (attach_detach)
11528 tree cl = NULL_TREE, extra_node;
11529 tree alloc_node = build_omp_struct_comp_nodes (code, *grp_start_p,
11530 grp_end, &extra_node);
11531 tree *tail_chain = NULL;
11533 if (*fragile_p
11534 || (openmp
11535 && !target
11536 && attach_detach
11537 && TREE_CODE (TREE_TYPE (ocd)) == POINTER_TYPE
11538 && !OMP_CLAUSE_ATTACHMENT_MAPPING_ERASED (grp_end)))
11540 if (!lang_GNU_Fortran ())
11541 OMP_CLAUSE_SIZE (alloc_node) = size_zero_node;
11542 OMP_CLAUSE_MAP_MAYBE_ZERO_LENGTH_ARRAY_SECTION (alloc_node) = 1;
11545 /* Here, we have:
11547 grp_end : the last (or only) node in this group.
11548 grp_start_p : pointer to the first node in a pointer mapping group
11549 up to and including GRP_END.
11550 sc : pointer to the chain for the end of the struct component
11551 list.
11552 scp : pointer to the chain for the sorted position at which we
11553 should insert in the middle of the struct component list
11554 (else NULL to insert at end).
11555 alloc_node : the "alloc" node for the structure (pointer-type)
11556 component. We insert at SCP (if present), else SC
11557 (the end of the struct component list).
11558 extra_node : a newly-synthesized node for an additional indirect
11559 pointer mapping or a Fortran pointer set, if needed.
11560 cl : first node to prepend before grp_start_p.
11561 tail_chain : pointer to chain of last prepended node.
11563 The general idea is we move the nodes for this struct mapping
11564 together: the alloc node goes into the sorted list directly after
11565 the struct mapping, and any extra nodes (together with the nodes
11566 mapping arrays pointed to by struct components) get moved after
11567 that list. When SCP is NULL, we insert the nodes at SC, i.e. at
11568 the end of the struct component mapping list. It's important that
11569 the alloc_node comes first in that case because it's part of the
11570 sorted component mapping list (but subsequent nodes are not!). */
11572 if (scp)
11573 omp_siblist_insert_node_after (alloc_node, scp);
11575 /* Make [cl,tail_chain] a list of the alloc node (if we haven't
11576 already inserted it) and the extra_node (if it is present). The
11577 list can be empty if we added alloc_node above and there is no
11578 extra node. */
11579 if (scp && extra_node)
11581 cl = extra_node;
11582 tail_chain = &OMP_CLAUSE_CHAIN (extra_node);
11584 else if (extra_node)
11586 OMP_CLAUSE_CHAIN (alloc_node) = extra_node;
11587 cl = alloc_node;
11588 tail_chain = &OMP_CLAUSE_CHAIN (extra_node);
11590 else if (!scp)
11592 cl = alloc_node;
11593 tail_chain = &OMP_CLAUSE_CHAIN (alloc_node);
11596 continue_at
11597 = cl ? omp_siblist_move_concat_nodes_after (cl, tail_chain,
11598 grp_start_p, grp_end,
11600 : omp_siblist_move_nodes_after (grp_start_p, grp_end, sc);
11602 else if (*sc != grp_end)
11604 gcc_assert (*grp_start_p == grp_end);
11606 /* We are moving the current node back to a previous struct node:
11607 the node that used to point to the current node will now point to
11608 the next node. */
11609 continue_at = grp_start_p;
11610 /* In the non-pointer case, the mapping clause itself is moved into
11611 the correct position in the struct component list, which in this
11612 case is just SC. */
11613 omp_siblist_move_node_after (*grp_start_p, grp_start_p, sc);
11616 return continue_at;
11619 /* Scan through GROUPS, and create sorted structure sibling lists without
11620 gimplifying. */
11622 static bool
11623 omp_build_struct_sibling_lists (enum tree_code code,
11624 enum omp_region_type region_type,
11625 vec<omp_mapping_group> *groups,
11626 hash_map<tree_operand_hash_no_se,
11627 omp_mapping_group *> **grpmap,
11628 tree *list_p)
11630 using namespace omp_addr_tokenizer;
11631 unsigned i;
11632 omp_mapping_group *grp;
11633 hash_map<tree_operand_hash, tree> *struct_map_to_clause = NULL;
11634 bool success = true;
11635 tree *new_next = NULL;
11636 tree *tail = &OMP_CLAUSE_CHAIN ((*groups)[groups->length () - 1].grp_end);
11637 tree added_nodes = NULL_TREE;
11638 tree *added_tail = &added_nodes;
11639 auto_vec<omp_mapping_group> pre_hwm_groups;
11641 FOR_EACH_VEC_ELT (*groups, i, grp)
11643 tree c = grp->grp_end;
11644 tree decl = OMP_CLAUSE_DECL (c);
11645 tree grp_end = grp->grp_end;
11646 auto_vec<omp_addr_token *> addr_tokens;
11647 tree sentinel = OMP_CLAUSE_CHAIN (grp_end);
11649 if (new_next && !grp->reprocess_struct)
11650 grp->grp_start = new_next;
11652 new_next = NULL;
11654 tree *grp_start_p = grp->grp_start;
11656 if (DECL_P (decl))
11657 continue;
11659 /* Skip groups we marked for deletion in
11660 {omp,oacc}_resolve_clause_dependencies. */
11661 if (grp->deleted)
11662 continue;
11664 if (OMP_CLAUSE_CHAIN (*grp_start_p)
11665 && OMP_CLAUSE_CHAIN (*grp_start_p) != grp_end)
11667 /* Don't process an array descriptor that isn't inside a derived type
11668 as a struct (the GOMP_MAP_POINTER following will have the form
11669 "var.data", but such mappings are handled specially). */
11670 tree grpmid = OMP_CLAUSE_CHAIN (*grp_start_p);
11671 if (omp_map_clause_descriptor_p (grpmid)
11672 && DECL_P (OMP_CLAUSE_DECL (grpmid)))
11673 continue;
11676 tree expr = decl;
11678 while (TREE_CODE (expr) == ARRAY_REF)
11679 expr = TREE_OPERAND (expr, 0);
11681 if (!omp_parse_expr (addr_tokens, expr))
11682 continue;
11684 omp_addr_token *last_token
11685 = omp_first_chained_access_token (addr_tokens);
11687 /* A mapping of a reference to a pointer member that doesn't specify an
11688 array section, etc., like this:
11689 *mystruct.ref_to_ptr
11690 should not be processed by the struct sibling-list handling code --
11691 it just transfers the referenced pointer.
11693 In contrast, the quite similar-looking construct:
11694 *mystruct.ptr
11695 which is equivalent to e.g.
11696 mystruct.ptr[0]
11697 *does* trigger sibling-list processing.
11699 An exception for the former case is for "fragile" groups where the
11700 reference itself is not handled otherwise; this is subject to special
11701 handling in omp_accumulate_sibling_list also. */
11703 if (TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE
11704 && last_token->type == ACCESS_METHOD
11705 && last_token->u.access_kind == ACCESS_REF
11706 && !grp->fragile)
11707 continue;
11709 tree d = decl;
11710 if (TREE_CODE (d) == ARRAY_REF)
11712 while (TREE_CODE (d) == ARRAY_REF)
11713 d = TREE_OPERAND (d, 0);
11714 if (TREE_CODE (d) == COMPONENT_REF
11715 && TREE_CODE (TREE_TYPE (d)) == ARRAY_TYPE)
11716 decl = d;
11718 if (d == decl
11719 && INDIRECT_REF_P (decl)
11720 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
11721 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
11722 == REFERENCE_TYPE)
11723 && (OMP_CLAUSE_MAP_KIND (c)
11724 != GOMP_MAP_POINTER_TO_ZERO_LENGTH_ARRAY_SECTION))
11725 decl = TREE_OPERAND (decl, 0);
11727 STRIP_NOPS (decl);
11729 if (TREE_CODE (decl) != COMPONENT_REF)
11730 continue;
11732 /* If we're mapping the whole struct in another node, skip adding this
11733 node to a sibling list. */
11734 omp_mapping_group *wholestruct;
11735 if (omp_mapped_by_containing_struct (*grpmap, OMP_CLAUSE_DECL (c),
11736 &wholestruct))
11737 continue;
11739 if (OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_TO_PSET
11740 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ATTACH
11741 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_DETACH
11742 && code != OACC_UPDATE
11743 && code != OMP_TARGET_UPDATE)
11745 if (error_operand_p (decl))
11747 success = false;
11748 goto error_out;
11751 tree stype = TREE_TYPE (decl);
11752 if (TREE_CODE (stype) == REFERENCE_TYPE)
11753 stype = TREE_TYPE (stype);
11754 if (TYPE_SIZE_UNIT (stype) == NULL
11755 || TREE_CODE (TYPE_SIZE_UNIT (stype)) != INTEGER_CST)
11757 error_at (OMP_CLAUSE_LOCATION (c),
11758 "mapping field %qE of variable length "
11759 "structure", OMP_CLAUSE_DECL (c));
11760 success = false;
11761 goto error_out;
11764 tree *inner = NULL;
11765 bool fragile_p = grp->fragile;
11767 new_next
11768 = omp_accumulate_sibling_list (region_type, code,
11769 struct_map_to_clause, *grpmap,
11770 grp_start_p, grp_end, addr_tokens,
11771 &inner, &fragile_p,
11772 grp->reprocess_struct, &added_tail);
11774 if (inner)
11776 omp_mapping_group newgrp;
11777 newgrp.grp_start = inner;
11778 if (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (*inner))
11779 == GOMP_MAP_ATTACH_DETACH)
11780 newgrp.grp_end = OMP_CLAUSE_CHAIN (*inner);
11781 else
11782 newgrp.grp_end = *inner;
11783 newgrp.mark = UNVISITED;
11784 newgrp.sibling = NULL;
11785 newgrp.deleted = false;
11786 newgrp.reprocess_struct = true;
11787 newgrp.fragile = fragile_p;
11788 newgrp.next = NULL;
11789 groups->safe_push (newgrp);
11791 /* !!! Growing GROUPS might invalidate the pointers in the group
11792 map. Rebuild it here. This is a bit inefficient, but
11793 shouldn't happen very often. */
11794 delete (*grpmap);
11795 *grpmap
11796 = omp_reindex_mapping_groups (list_p, groups, &pre_hwm_groups,
11797 sentinel);
11802 /* Delete groups marked for deletion above. At this point the order of the
11803 groups may no longer correspond to the order of the underlying list,
11804 which complicates this a little. First clear out OMP_CLAUSE_DECL for
11805 deleted nodes... */
11807 FOR_EACH_VEC_ELT (*groups, i, grp)
11808 if (grp->deleted)
11809 for (tree d = *grp->grp_start;
11810 d != OMP_CLAUSE_CHAIN (grp->grp_end);
11811 d = OMP_CLAUSE_CHAIN (d))
11812 OMP_CLAUSE_DECL (d) = NULL_TREE;
11814 /* ...then sweep through the list removing the now-empty nodes. */
11816 tail = list_p;
11817 while (*tail)
11819 if (OMP_CLAUSE_CODE (*tail) == OMP_CLAUSE_MAP
11820 && OMP_CLAUSE_DECL (*tail) == NULL_TREE)
11821 *tail = OMP_CLAUSE_CHAIN (*tail);
11822 else
11823 tail = &OMP_CLAUSE_CHAIN (*tail);
11826 /* Tack on the struct nodes added during nested struct reprocessing. */
11827 if (added_nodes)
11829 *tail = added_nodes;
11830 tail = added_tail;
11833 /* Now we have finished building the struct sibling lists, reprocess
11834 newly-added "attach" nodes: we need the address of the first
11835 mapped element of each struct sibling list for the bias of the attach
11836 operation -- not necessarily the base address of the whole struct. */
11837 if (struct_map_to_clause)
11838 for (hash_map<tree_operand_hash, tree>::iterator iter
11839 = struct_map_to_clause->begin ();
11840 iter != struct_map_to_clause->end ();
11841 ++iter)
11843 tree struct_node = (*iter).second;
11844 gcc_assert (OMP_CLAUSE_CODE (struct_node) == OMP_CLAUSE_MAP);
11845 tree attach = OMP_CLAUSE_CHAIN (struct_node);
11847 if (OMP_CLAUSE_CODE (attach) != OMP_CLAUSE_MAP
11848 || OMP_CLAUSE_MAP_KIND (attach) != GOMP_MAP_ATTACH_DETACH)
11849 continue;
11851 OMP_CLAUSE_SET_MAP_KIND (attach, GOMP_MAP_ATTACH);
11853 /* Sanity check: the standalone attach node will not work if we have
11854 an "enter data" operation (because for those, variables need to be
11855 mapped separately and attach nodes must be grouped together with the
11856 base they attach to). We should only have created the
11857 ATTACH_DETACH node after GOMP_MAP_STRUCT for a target region, so
11858 this should never be true. */
11859 gcc_assert ((region_type & ORT_TARGET) != 0);
11861 /* This is the first sorted node in the struct sibling list. Use it
11862 to recalculate the correct bias to use.
11863 (&first_node - attach_decl).
11864 For GOMP_MAP_STRUCT_UNORD, we need e.g. the
11865 min(min(min(first,second),third),fourth) element, because the
11866 elements aren't in any particular order. */
11867 tree lowest_addr;
11868 if (OMP_CLAUSE_MAP_KIND (struct_node) == GOMP_MAP_STRUCT_UNORD)
11870 tree first_node = OMP_CLAUSE_CHAIN (attach);
11871 unsigned HOST_WIDE_INT num_mappings
11872 = tree_to_uhwi (OMP_CLAUSE_SIZE (struct_node));
11873 lowest_addr = OMP_CLAUSE_DECL (first_node);
11874 lowest_addr = build_fold_addr_expr (lowest_addr);
11875 lowest_addr = fold_convert (pointer_sized_int_node, lowest_addr);
11876 tree next_node = OMP_CLAUSE_CHAIN (first_node);
11877 while (num_mappings > 1)
11879 tree tmp = OMP_CLAUSE_DECL (next_node);
11880 tmp = build_fold_addr_expr (tmp);
11881 tmp = fold_convert (pointer_sized_int_node, tmp);
11882 lowest_addr = fold_build2 (MIN_EXPR, pointer_sized_int_node,
11883 lowest_addr, tmp);
11884 next_node = OMP_CLAUSE_CHAIN (next_node);
11885 num_mappings--;
11887 lowest_addr = fold_convert (ptrdiff_type_node, lowest_addr);
11889 else
11891 tree first_node = OMP_CLAUSE_DECL (OMP_CLAUSE_CHAIN (attach));
11892 first_node = build_fold_addr_expr (first_node);
11893 lowest_addr = fold_convert (ptrdiff_type_node, first_node);
11895 tree attach_decl = OMP_CLAUSE_DECL (attach);
11896 attach_decl = fold_convert (ptrdiff_type_node, attach_decl);
11897 OMP_CLAUSE_SIZE (attach)
11898 = fold_build2 (MINUS_EXPR, ptrdiff_type_node, lowest_addr,
11899 attach_decl);
11901 /* Remove GOMP_MAP_ATTACH node from after struct node. */
11902 OMP_CLAUSE_CHAIN (struct_node) = OMP_CLAUSE_CHAIN (attach);
11903 /* ...and re-insert it at the end of our clause list. */
11904 *tail = attach;
11905 OMP_CLAUSE_CHAIN (attach) = NULL_TREE;
11906 tail = &OMP_CLAUSE_CHAIN (attach);
11909 error_out:
11910 if (struct_map_to_clause)
11911 delete struct_map_to_clause;
11913 return success;
11916 /* Scan the OMP clauses in *LIST_P, installing mappings into a new
11917 and previous omp contexts. */
11919 static void
11920 gimplify_scan_omp_clauses (tree *list_p, gimple_seq *pre_p,
11921 enum omp_region_type region_type,
11922 enum tree_code code)
11924 using namespace omp_addr_tokenizer;
11925 struct gimplify_omp_ctx *ctx, *outer_ctx;
11926 tree c;
11927 tree *orig_list_p = list_p;
11928 int handled_depend_iterators = -1;
11929 int nowait = -1;
11931 ctx = new_omp_context (region_type);
11932 ctx->code = code;
11933 outer_ctx = ctx->outer_context;
11934 if (code == OMP_TARGET)
11936 if (!lang_GNU_Fortran ())
11937 ctx->defaultmap[GDMK_POINTER] = GOVD_MAP | GOVD_MAP_0LEN_ARRAY;
11938 ctx->defaultmap[GDMK_SCALAR] = GOVD_FIRSTPRIVATE;
11939 ctx->defaultmap[GDMK_SCALAR_TARGET] = (lang_GNU_Fortran ()
11940 ? GOVD_MAP : GOVD_FIRSTPRIVATE);
11942 if (!lang_GNU_Fortran ())
11943 switch (code)
11945 case OMP_TARGET:
11946 case OMP_TARGET_DATA:
11947 case OMP_TARGET_ENTER_DATA:
11948 case OMP_TARGET_EXIT_DATA:
11949 case OACC_DECLARE:
11950 case OACC_HOST_DATA:
11951 case OACC_PARALLEL:
11952 case OACC_KERNELS:
11953 ctx->target_firstprivatize_array_bases = true;
11954 default:
11955 break;
11958 vec<omp_mapping_group> *groups = NULL;
11959 hash_map<tree_operand_hash_no_se, omp_mapping_group *> *grpmap = NULL;
11960 unsigned grpnum = 0;
11961 tree *grp_start_p = NULL, grp_end = NULL_TREE;
11963 if (code == OMP_TARGET
11964 || code == OMP_TARGET_DATA
11965 || code == OMP_TARGET_ENTER_DATA
11966 || code == OMP_TARGET_EXIT_DATA
11967 || code == OACC_DATA
11968 || code == OACC_KERNELS
11969 || code == OACC_PARALLEL
11970 || code == OACC_SERIAL
11971 || code == OACC_ENTER_DATA
11972 || code == OACC_EXIT_DATA
11973 || code == OACC_UPDATE
11974 || code == OACC_DECLARE)
11976 groups = omp_gather_mapping_groups (list_p);
11978 if (groups)
11979 grpmap = omp_index_mapping_groups (groups);
11982 while ((c = *list_p) != NULL)
11984 bool remove = false;
11985 bool notice_outer = true;
11986 bool map_descriptor;
11987 const char *check_non_private = NULL;
11988 unsigned int flags;
11989 tree decl;
11990 auto_vec<omp_addr_token *, 10> addr_tokens;
11992 if (grp_end && c == OMP_CLAUSE_CHAIN (grp_end))
11994 grp_start_p = NULL;
11995 grp_end = NULL_TREE;
11998 switch (OMP_CLAUSE_CODE (c))
12000 case OMP_CLAUSE_PRIVATE:
12001 flags = GOVD_PRIVATE | GOVD_EXPLICIT;
12002 if (lang_hooks.decls.omp_private_outer_ref (OMP_CLAUSE_DECL (c)))
12004 flags |= GOVD_PRIVATE_OUTER_REF;
12005 OMP_CLAUSE_PRIVATE_OUTER_REF (c) = 1;
12007 else
12008 notice_outer = false;
12009 goto do_add;
12010 case OMP_CLAUSE_SHARED:
12011 flags = GOVD_SHARED | GOVD_EXPLICIT;
12012 goto do_add;
12013 case OMP_CLAUSE_FIRSTPRIVATE:
12014 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
12015 check_non_private = "firstprivate";
12016 if (OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (c))
12018 gcc_assert (code == OMP_TARGET);
12019 flags |= GOVD_FIRSTPRIVATE_IMPLICIT;
12021 goto do_add;
12022 case OMP_CLAUSE_LASTPRIVATE:
12023 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
12024 switch (code)
12026 case OMP_DISTRIBUTE:
12027 error_at (OMP_CLAUSE_LOCATION (c),
12028 "conditional %<lastprivate%> clause on "
12029 "%qs construct", "distribute");
12030 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
12031 break;
12032 case OMP_TASKLOOP:
12033 error_at (OMP_CLAUSE_LOCATION (c),
12034 "conditional %<lastprivate%> clause on "
12035 "%qs construct", "taskloop");
12036 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
12037 break;
12038 default:
12039 break;
12041 flags = GOVD_LASTPRIVATE | GOVD_SEEN | GOVD_EXPLICIT;
12042 if (code != OMP_LOOP)
12043 check_non_private = "lastprivate";
12044 decl = OMP_CLAUSE_DECL (c);
12045 if (error_operand_p (decl))
12046 goto do_add;
12047 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c)
12048 && !lang_hooks.decls.omp_scalar_p (decl, true))
12050 error_at (OMP_CLAUSE_LOCATION (c),
12051 "non-scalar variable %qD in conditional "
12052 "%<lastprivate%> clause", decl);
12053 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
12055 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
12056 flags |= GOVD_LASTPRIVATE_CONDITIONAL;
12057 omp_lastprivate_for_combined_outer_constructs (outer_ctx, decl,
12058 false);
12059 goto do_add;
12060 case OMP_CLAUSE_REDUCTION:
12061 if (OMP_CLAUSE_REDUCTION_TASK (c))
12063 if (region_type == ORT_WORKSHARE || code == OMP_SCOPE)
12065 if (nowait == -1)
12066 nowait = omp_find_clause (*list_p,
12067 OMP_CLAUSE_NOWAIT) != NULL_TREE;
12068 if (nowait
12069 && (outer_ctx == NULL
12070 || outer_ctx->region_type != ORT_COMBINED_PARALLEL))
12072 error_at (OMP_CLAUSE_LOCATION (c),
12073 "%<task%> reduction modifier on a construct "
12074 "with a %<nowait%> clause");
12075 OMP_CLAUSE_REDUCTION_TASK (c) = 0;
12078 else if ((region_type & ORT_PARALLEL) != ORT_PARALLEL)
12080 error_at (OMP_CLAUSE_LOCATION (c),
12081 "invalid %<task%> reduction modifier on construct "
12082 "other than %<parallel%>, %qs, %<sections%> or "
12083 "%<scope%>", lang_GNU_Fortran () ? "do" : "for");
12084 OMP_CLAUSE_REDUCTION_TASK (c) = 0;
12087 if (OMP_CLAUSE_REDUCTION_INSCAN (c))
12088 switch (code)
12090 case OMP_SECTIONS:
12091 error_at (OMP_CLAUSE_LOCATION (c),
12092 "%<inscan%> %<reduction%> clause on "
12093 "%qs construct", "sections");
12094 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
12095 break;
12096 case OMP_PARALLEL:
12097 error_at (OMP_CLAUSE_LOCATION (c),
12098 "%<inscan%> %<reduction%> clause on "
12099 "%qs construct", "parallel");
12100 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
12101 break;
12102 case OMP_TEAMS:
12103 error_at (OMP_CLAUSE_LOCATION (c),
12104 "%<inscan%> %<reduction%> clause on "
12105 "%qs construct", "teams");
12106 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
12107 break;
12108 case OMP_TASKLOOP:
12109 error_at (OMP_CLAUSE_LOCATION (c),
12110 "%<inscan%> %<reduction%> clause on "
12111 "%qs construct", "taskloop");
12112 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
12113 break;
12114 case OMP_SCOPE:
12115 error_at (OMP_CLAUSE_LOCATION (c),
12116 "%<inscan%> %<reduction%> clause on "
12117 "%qs construct", "scope");
12118 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
12119 break;
12120 default:
12121 break;
12123 /* FALLTHRU */
12124 case OMP_CLAUSE_IN_REDUCTION:
12125 case OMP_CLAUSE_TASK_REDUCTION:
12126 flags = GOVD_REDUCTION | GOVD_SEEN | GOVD_EXPLICIT;
12127 /* OpenACC permits reductions on private variables. */
12128 if (!(region_type & ORT_ACC)
12129 /* taskgroup is actually not a worksharing region. */
12130 && code != OMP_TASKGROUP)
12131 check_non_private = omp_clause_code_name[OMP_CLAUSE_CODE (c)];
12132 decl = OMP_CLAUSE_DECL (c);
12133 if (TREE_CODE (decl) == MEM_REF)
12135 tree type = TREE_TYPE (decl);
12136 bool saved_into_ssa = gimplify_ctxp->into_ssa;
12137 gimplify_ctxp->into_ssa = false;
12138 if (gimplify_expr (&TYPE_MAX_VALUE (TYPE_DOMAIN (type)), pre_p,
12139 NULL, is_gimple_val, fb_rvalue, false)
12140 == GS_ERROR)
12142 gimplify_ctxp->into_ssa = saved_into_ssa;
12143 remove = true;
12144 break;
12146 gimplify_ctxp->into_ssa = saved_into_ssa;
12147 tree v = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
12148 if (DECL_P (v))
12150 omp_firstprivatize_variable (ctx, v);
12151 omp_notice_variable (ctx, v, true);
12153 decl = TREE_OPERAND (decl, 0);
12154 if (TREE_CODE (decl) == POINTER_PLUS_EXPR)
12156 gimplify_ctxp->into_ssa = false;
12157 if (gimplify_expr (&TREE_OPERAND (decl, 1), pre_p,
12158 NULL, is_gimple_val, fb_rvalue, false)
12159 == GS_ERROR)
12161 gimplify_ctxp->into_ssa = saved_into_ssa;
12162 remove = true;
12163 break;
12165 gimplify_ctxp->into_ssa = saved_into_ssa;
12166 v = TREE_OPERAND (decl, 1);
12167 if (DECL_P (v))
12169 omp_firstprivatize_variable (ctx, v);
12170 omp_notice_variable (ctx, v, true);
12172 decl = TREE_OPERAND (decl, 0);
12174 if (TREE_CODE (decl) == ADDR_EXPR
12175 || TREE_CODE (decl) == INDIRECT_REF)
12176 decl = TREE_OPERAND (decl, 0);
12178 goto do_add_decl;
12179 case OMP_CLAUSE_LINEAR:
12180 if (gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c), pre_p, NULL,
12181 is_gimple_val, fb_rvalue) == GS_ERROR)
12183 remove = true;
12184 break;
12186 else
12188 if (code == OMP_SIMD
12189 && !OMP_CLAUSE_LINEAR_NO_COPYIN (c))
12191 struct gimplify_omp_ctx *octx = outer_ctx;
12192 if (octx
12193 && octx->region_type == ORT_WORKSHARE
12194 && octx->combined_loop
12195 && !octx->distribute)
12197 if (octx->outer_context
12198 && (octx->outer_context->region_type
12199 == ORT_COMBINED_PARALLEL))
12200 octx = octx->outer_context->outer_context;
12201 else
12202 octx = octx->outer_context;
12204 if (octx
12205 && octx->region_type == ORT_WORKSHARE
12206 && octx->combined_loop
12207 && octx->distribute)
12209 error_at (OMP_CLAUSE_LOCATION (c),
12210 "%<linear%> clause for variable other than "
12211 "loop iterator specified on construct "
12212 "combined with %<distribute%>");
12213 remove = true;
12214 break;
12217 /* For combined #pragma omp parallel for simd, need to put
12218 lastprivate and perhaps firstprivate too on the
12219 parallel. Similarly for #pragma omp for simd. */
12220 struct gimplify_omp_ctx *octx = outer_ctx;
12221 bool taskloop_seen = false;
12222 decl = NULL_TREE;
12225 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
12226 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
12227 break;
12228 decl = OMP_CLAUSE_DECL (c);
12229 if (error_operand_p (decl))
12231 decl = NULL_TREE;
12232 break;
12234 flags = GOVD_SEEN;
12235 if (!OMP_CLAUSE_LINEAR_NO_COPYIN (c))
12236 flags |= GOVD_FIRSTPRIVATE;
12237 if (!OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
12238 flags |= GOVD_LASTPRIVATE;
12239 if (octx
12240 && octx->region_type == ORT_WORKSHARE
12241 && octx->combined_loop)
12243 if (octx->outer_context
12244 && (octx->outer_context->region_type
12245 == ORT_COMBINED_PARALLEL))
12246 octx = octx->outer_context;
12247 else if (omp_check_private (octx, decl, false))
12248 break;
12250 else if (octx
12251 && (octx->region_type & ORT_TASK) != 0
12252 && octx->combined_loop)
12253 taskloop_seen = true;
12254 else if (octx
12255 && octx->region_type == ORT_COMBINED_PARALLEL
12256 && ((ctx->region_type == ORT_WORKSHARE
12257 && octx == outer_ctx)
12258 || taskloop_seen))
12259 flags = GOVD_SEEN | GOVD_SHARED;
12260 else if (octx
12261 && ((octx->region_type & ORT_COMBINED_TEAMS)
12262 == ORT_COMBINED_TEAMS))
12263 flags = GOVD_SEEN | GOVD_SHARED;
12264 else if (octx
12265 && octx->region_type == ORT_COMBINED_TARGET)
12267 if (flags & GOVD_LASTPRIVATE)
12268 flags = GOVD_SEEN | GOVD_MAP;
12270 else
12271 break;
12272 splay_tree_node on
12273 = splay_tree_lookup (octx->variables,
12274 (splay_tree_key) decl);
12275 if (on && (on->value & GOVD_DATA_SHARE_CLASS) != 0)
12277 octx = NULL;
12278 break;
12280 omp_add_variable (octx, decl, flags);
12281 if (octx->outer_context == NULL)
12282 break;
12283 octx = octx->outer_context;
12285 while (1);
12286 if (octx
12287 && decl
12288 && (!OMP_CLAUSE_LINEAR_NO_COPYIN (c)
12289 || !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
12290 omp_notice_variable (octx, decl, true);
12292 flags = GOVD_LINEAR | GOVD_EXPLICIT;
12293 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
12294 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
12296 notice_outer = false;
12297 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
12299 goto do_add;
12301 case OMP_CLAUSE_MAP:
12302 if (!grp_start_p)
12304 grp_start_p = list_p;
12305 grp_end = (*groups)[grpnum].grp_end;
12306 grpnum++;
12308 decl = OMP_CLAUSE_DECL (c);
12310 if (error_operand_p (decl))
12312 remove = true;
12313 break;
12316 if (!omp_parse_expr (addr_tokens, decl))
12318 remove = true;
12319 break;
12322 if (remove)
12323 break;
12324 if (DECL_P (decl) && outer_ctx && (region_type & ORT_ACC))
12326 struct gimplify_omp_ctx *octx;
12327 for (octx = outer_ctx; octx; octx = octx->outer_context)
12329 if (octx->region_type != ORT_ACC_HOST_DATA)
12330 break;
12331 splay_tree_node n2
12332 = splay_tree_lookup (octx->variables,
12333 (splay_tree_key) decl);
12334 if (n2)
12335 error_at (OMP_CLAUSE_LOCATION (c), "variable %qE "
12336 "declared in enclosing %<host_data%> region",
12337 DECL_NAME (decl));
12341 map_descriptor = false;
12343 /* This condition checks if we're mapping an array descriptor that
12344 isn't inside a derived type -- these have special handling, and
12345 are not handled as structs in omp_build_struct_sibling_lists.
12346 See that function for further details. */
12347 if (*grp_start_p != grp_end
12348 && OMP_CLAUSE_CHAIN (*grp_start_p)
12349 && OMP_CLAUSE_CHAIN (*grp_start_p) != grp_end)
12351 tree grp_mid = OMP_CLAUSE_CHAIN (*grp_start_p);
12352 if (omp_map_clause_descriptor_p (grp_mid)
12353 && DECL_P (OMP_CLAUSE_DECL (grp_mid)))
12354 map_descriptor = true;
12356 else if (OMP_CLAUSE_CODE (grp_end) == OMP_CLAUSE_MAP
12357 && (OMP_CLAUSE_MAP_KIND (grp_end) == GOMP_MAP_RELEASE
12358 || OMP_CLAUSE_MAP_KIND (grp_end) == GOMP_MAP_DELETE)
12359 && OMP_CLAUSE_RELEASE_DESCRIPTOR (grp_end))
12360 map_descriptor = true;
12362 /* Adding the decl for a struct access: we haven't created
12363 GOMP_MAP_STRUCT nodes yet, so this statement needs to predict
12364 whether they will be created in gimplify_adjust_omp_clauses.
12365 NOTE: Technically we should probably look through DECL_VALUE_EXPR
12366 here because something that looks like a DECL_P may actually be a
12367 struct access, e.g. variables in a lambda closure
12368 (__closure->__foo) or class members (this->foo). Currently in both
12369 those cases we map the whole of the containing object (directly in
12370 the C++ FE) though, so struct nodes are not created. */
12371 if (c == grp_end
12372 && addr_tokens[0]->type == STRUCTURE_BASE
12373 && addr_tokens[0]->u.structure_base_kind == BASE_DECL
12374 && !map_descriptor)
12376 gcc_assert (addr_tokens[1]->type == ACCESS_METHOD);
12377 /* If we got to this struct via a chain of pointers, maybe we
12378 want to map it implicitly instead. */
12379 if (omp_access_chain_p (addr_tokens, 1))
12380 break;
12381 omp_mapping_group *wholestruct;
12382 if (!(region_type & ORT_ACC)
12383 && omp_mapped_by_containing_struct (grpmap,
12384 OMP_CLAUSE_DECL (c),
12385 &wholestruct))
12386 break;
12387 decl = addr_tokens[1]->expr;
12388 if (splay_tree_lookup (ctx->variables, (splay_tree_key) decl))
12389 break;
12390 /* Standalone attach or detach clauses for a struct element
12391 should not inhibit implicit mapping of the whole struct. */
12392 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH
12393 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_DETACH)
12394 break;
12395 flags = GOVD_MAP | GOVD_EXPLICIT;
12397 gcc_assert (addr_tokens[1]->u.access_kind != ACCESS_DIRECT
12398 || TREE_ADDRESSABLE (decl));
12399 goto do_add_decl;
12402 if (!DECL_P (decl))
12404 tree d = decl, *pd;
12405 if (TREE_CODE (d) == ARRAY_REF)
12407 while (TREE_CODE (d) == ARRAY_REF)
12408 d = TREE_OPERAND (d, 0);
12409 if (TREE_CODE (d) == COMPONENT_REF
12410 && TREE_CODE (TREE_TYPE (d)) == ARRAY_TYPE)
12411 decl = d;
12413 pd = &OMP_CLAUSE_DECL (c);
12414 if (d == decl
12415 && TREE_CODE (decl) == INDIRECT_REF
12416 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
12417 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
12418 == REFERENCE_TYPE)
12419 && (OMP_CLAUSE_MAP_KIND (c)
12420 != GOMP_MAP_POINTER_TO_ZERO_LENGTH_ARRAY_SECTION))
12422 pd = &TREE_OPERAND (decl, 0);
12423 decl = TREE_OPERAND (decl, 0);
12426 if (addr_tokens[0]->type == STRUCTURE_BASE
12427 && addr_tokens[0]->u.structure_base_kind == BASE_DECL
12428 && addr_tokens[1]->type == ACCESS_METHOD
12429 && (addr_tokens[1]->u.access_kind == ACCESS_POINTER
12430 || (addr_tokens[1]->u.access_kind
12431 == ACCESS_POINTER_OFFSET))
12432 && GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c)))
12434 tree base = addr_tokens[1]->expr;
12435 splay_tree_node n
12436 = splay_tree_lookup (ctx->variables,
12437 (splay_tree_key) base);
12438 n->value |= GOVD_SEEN;
12441 if (code == OMP_TARGET && OMP_CLAUSE_MAP_IN_REDUCTION (c))
12443 /* Don't gimplify *pd fully at this point, as the base
12444 will need to be adjusted during omp lowering. */
12445 auto_vec<tree, 10> expr_stack;
12446 tree *p = pd;
12447 while (handled_component_p (*p)
12448 || TREE_CODE (*p) == INDIRECT_REF
12449 || TREE_CODE (*p) == ADDR_EXPR
12450 || TREE_CODE (*p) == MEM_REF
12451 || TREE_CODE (*p) == NON_LVALUE_EXPR)
12453 expr_stack.safe_push (*p);
12454 p = &TREE_OPERAND (*p, 0);
12456 for (int i = expr_stack.length () - 1; i >= 0; i--)
12458 tree t = expr_stack[i];
12459 if (TREE_CODE (t) == ARRAY_REF
12460 || TREE_CODE (t) == ARRAY_RANGE_REF)
12462 if (TREE_OPERAND (t, 2) == NULL_TREE)
12464 tree low = unshare_expr (array_ref_low_bound (t));
12465 if (!is_gimple_min_invariant (low))
12467 TREE_OPERAND (t, 2) = low;
12468 if (gimplify_expr (&TREE_OPERAND (t, 2),
12469 pre_p, NULL,
12470 is_gimple_reg,
12471 fb_rvalue) == GS_ERROR)
12472 remove = true;
12475 else if (gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
12476 NULL, is_gimple_reg,
12477 fb_rvalue) == GS_ERROR)
12478 remove = true;
12479 if (TREE_OPERAND (t, 3) == NULL_TREE)
12481 tree elmt_size = array_ref_element_size (t);
12482 if (!is_gimple_min_invariant (elmt_size))
12484 elmt_size = unshare_expr (elmt_size);
12485 tree elmt_type
12486 = TREE_TYPE (TREE_TYPE (TREE_OPERAND (t,
12487 0)));
12488 tree factor
12489 = size_int (TYPE_ALIGN_UNIT (elmt_type));
12490 elmt_size
12491 = size_binop (EXACT_DIV_EXPR, elmt_size,
12492 factor);
12493 TREE_OPERAND (t, 3) = elmt_size;
12494 if (gimplify_expr (&TREE_OPERAND (t, 3),
12495 pre_p, NULL,
12496 is_gimple_reg,
12497 fb_rvalue) == GS_ERROR)
12498 remove = true;
12501 else if (gimplify_expr (&TREE_OPERAND (t, 3), pre_p,
12502 NULL, is_gimple_reg,
12503 fb_rvalue) == GS_ERROR)
12504 remove = true;
12506 else if (TREE_CODE (t) == COMPONENT_REF)
12508 if (TREE_OPERAND (t, 2) == NULL_TREE)
12510 tree offset = component_ref_field_offset (t);
12511 if (!is_gimple_min_invariant (offset))
12513 offset = unshare_expr (offset);
12514 tree field = TREE_OPERAND (t, 1);
12515 tree factor
12516 = size_int (DECL_OFFSET_ALIGN (field)
12517 / BITS_PER_UNIT);
12518 offset = size_binop (EXACT_DIV_EXPR, offset,
12519 factor);
12520 TREE_OPERAND (t, 2) = offset;
12521 if (gimplify_expr (&TREE_OPERAND (t, 2),
12522 pre_p, NULL,
12523 is_gimple_reg,
12524 fb_rvalue) == GS_ERROR)
12525 remove = true;
12528 else if (gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
12529 NULL, is_gimple_reg,
12530 fb_rvalue) == GS_ERROR)
12531 remove = true;
12534 for (; expr_stack.length () > 0; )
12536 tree t = expr_stack.pop ();
12538 if (TREE_CODE (t) == ARRAY_REF
12539 || TREE_CODE (t) == ARRAY_RANGE_REF)
12541 if (!is_gimple_min_invariant (TREE_OPERAND (t, 1))
12542 && gimplify_expr (&TREE_OPERAND (t, 1), pre_p,
12543 NULL, is_gimple_val,
12544 fb_rvalue) == GS_ERROR)
12545 remove = true;
12549 break;
12552 if ((code == OMP_TARGET
12553 || code == OMP_TARGET_DATA
12554 || code == OMP_TARGET_ENTER_DATA
12555 || code == OMP_TARGET_EXIT_DATA)
12556 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
12558 /* If we have attach/detach but the decl we have is a pointer to
12559 pointer, we're probably mapping the "base level" array
12560 implicitly. Make sure we don't add the decl as if we mapped
12561 it explicitly. That is,
12563 int **arr;
12564 [...]
12565 #pragma omp target map(arr[a][b:c])
12567 should *not* map "arr" explicitly. That way we get a
12568 zero-length "alloc" mapping for it, and assuming it's been
12569 mapped by some previous directive, etc., things work as they
12570 should. */
12572 tree basetype = TREE_TYPE (addr_tokens[0]->expr);
12574 if (TREE_CODE (basetype) == REFERENCE_TYPE)
12575 basetype = TREE_TYPE (basetype);
12577 if (code == OMP_TARGET
12578 && addr_tokens[0]->type == ARRAY_BASE
12579 && addr_tokens[0]->u.structure_base_kind == BASE_DECL
12580 && TREE_CODE (basetype) == POINTER_TYPE
12581 && TREE_CODE (TREE_TYPE (basetype)) == POINTER_TYPE)
12582 break;
12585 flags = GOVD_MAP | GOVD_EXPLICIT;
12586 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_TO
12587 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_TOFROM
12588 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_PRESENT_TO
12589 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_PRESENT_TOFROM)
12590 flags |= GOVD_MAP_ALWAYS_TO;
12592 goto do_add;
12594 case OMP_CLAUSE_AFFINITY:
12595 gimplify_omp_affinity (list_p, pre_p);
12596 remove = true;
12597 break;
12598 case OMP_CLAUSE_DOACROSS:
12599 if (OMP_CLAUSE_DOACROSS_KIND (c) == OMP_CLAUSE_DOACROSS_SINK)
12601 tree deps = OMP_CLAUSE_DECL (c);
12602 while (deps && TREE_CODE (deps) == TREE_LIST)
12604 if (TREE_CODE (TREE_PURPOSE (deps)) == TRUNC_DIV_EXPR
12605 && DECL_P (TREE_OPERAND (TREE_PURPOSE (deps), 1)))
12606 gimplify_expr (&TREE_OPERAND (TREE_PURPOSE (deps), 1),
12607 pre_p, NULL, is_gimple_val, fb_rvalue);
12608 deps = TREE_CHAIN (deps);
12611 else
12612 gcc_assert (OMP_CLAUSE_DOACROSS_KIND (c)
12613 == OMP_CLAUSE_DOACROSS_SOURCE);
12614 break;
12615 case OMP_CLAUSE_DEPEND:
12616 if (handled_depend_iterators == -1)
12617 handled_depend_iterators = gimplify_omp_depend (list_p, pre_p);
12618 if (handled_depend_iterators)
12620 if (handled_depend_iterators == 2)
12621 remove = true;
12622 break;
12624 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
12626 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
12627 NULL, is_gimple_val, fb_rvalue);
12628 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
12630 if (error_operand_p (OMP_CLAUSE_DECL (c)))
12632 remove = true;
12633 break;
12635 if (OMP_CLAUSE_DECL (c) != null_pointer_node)
12637 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (OMP_CLAUSE_DECL (c));
12638 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
12639 is_gimple_val, fb_rvalue) == GS_ERROR)
12641 remove = true;
12642 break;
12645 if (code == OMP_TASK)
12646 ctx->has_depend = true;
12647 break;
12649 case OMP_CLAUSE_TO:
12650 case OMP_CLAUSE_FROM:
12651 case OMP_CLAUSE__CACHE_:
12652 decl = OMP_CLAUSE_DECL (c);
12653 if (error_operand_p (decl))
12655 remove = true;
12656 break;
12658 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
12659 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
12660 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
12661 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
12662 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
12664 remove = true;
12665 break;
12667 if (!DECL_P (decl))
12669 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p,
12670 NULL, is_gimple_lvalue, fb_lvalue)
12671 == GS_ERROR)
12673 remove = true;
12674 break;
12676 break;
12678 goto do_notice;
12680 case OMP_CLAUSE_USE_DEVICE_PTR:
12681 case OMP_CLAUSE_USE_DEVICE_ADDR:
12682 flags = GOVD_EXPLICIT;
12683 goto do_add;
12685 case OMP_CLAUSE_HAS_DEVICE_ADDR:
12686 decl = OMP_CLAUSE_DECL (c);
12687 while (TREE_CODE (decl) == INDIRECT_REF
12688 || TREE_CODE (decl) == ARRAY_REF)
12689 decl = TREE_OPERAND (decl, 0);
12690 flags = GOVD_EXPLICIT;
12691 goto do_add_decl;
12693 case OMP_CLAUSE_IS_DEVICE_PTR:
12694 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
12695 goto do_add;
12697 do_add:
12698 decl = OMP_CLAUSE_DECL (c);
12699 do_add_decl:
12700 if (error_operand_p (decl))
12702 remove = true;
12703 break;
12705 if (DECL_NAME (decl) == NULL_TREE && (flags & GOVD_SHARED) == 0)
12707 tree t = omp_member_access_dummy_var (decl);
12708 if (t)
12710 tree v = DECL_VALUE_EXPR (decl);
12711 DECL_NAME (decl) = DECL_NAME (TREE_OPERAND (v, 1));
12712 if (outer_ctx)
12713 omp_notice_variable (outer_ctx, t, true);
12716 if (code == OACC_DATA
12717 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP
12718 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
12719 flags |= GOVD_MAP_0LEN_ARRAY;
12720 omp_add_variable (ctx, decl, flags);
12721 if ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
12722 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_IN_REDUCTION
12723 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_TASK_REDUCTION)
12724 && OMP_CLAUSE_REDUCTION_PLACEHOLDER (c))
12726 struct gimplify_omp_ctx *pctx
12727 = code == OMP_TARGET ? outer_ctx : ctx;
12728 if (pctx)
12729 omp_add_variable (pctx, OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
12730 GOVD_LOCAL | GOVD_SEEN);
12731 if (pctx
12732 && OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c)
12733 && walk_tree (&OMP_CLAUSE_REDUCTION_INIT (c),
12734 find_decl_expr,
12735 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
12736 NULL) == NULL_TREE)
12737 omp_add_variable (pctx,
12738 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
12739 GOVD_LOCAL | GOVD_SEEN);
12740 gimplify_omp_ctxp = pctx;
12741 push_gimplify_context ();
12743 OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c) = NULL;
12744 OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c) = NULL;
12746 gimplify_and_add (OMP_CLAUSE_REDUCTION_INIT (c),
12747 &OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c));
12748 pop_gimplify_context
12749 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c)));
12750 push_gimplify_context ();
12751 gimplify_and_add (OMP_CLAUSE_REDUCTION_MERGE (c),
12752 &OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c));
12753 pop_gimplify_context
12754 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c)));
12755 OMP_CLAUSE_REDUCTION_INIT (c) = NULL_TREE;
12756 OMP_CLAUSE_REDUCTION_MERGE (c) = NULL_TREE;
12758 gimplify_omp_ctxp = outer_ctx;
12760 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
12761 && OMP_CLAUSE_LASTPRIVATE_STMT (c))
12763 gimplify_omp_ctxp = ctx;
12764 push_gimplify_context ();
12765 if (TREE_CODE (OMP_CLAUSE_LASTPRIVATE_STMT (c)) != BIND_EXPR)
12767 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
12768 NULL, NULL);
12769 TREE_SIDE_EFFECTS (bind) = 1;
12770 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LASTPRIVATE_STMT (c);
12771 OMP_CLAUSE_LASTPRIVATE_STMT (c) = bind;
12773 gimplify_and_add (OMP_CLAUSE_LASTPRIVATE_STMT (c),
12774 &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c));
12775 pop_gimplify_context
12776 (gimple_seq_first_stmt (OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c)));
12777 OMP_CLAUSE_LASTPRIVATE_STMT (c) = NULL_TREE;
12779 gimplify_omp_ctxp = outer_ctx;
12781 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
12782 && OMP_CLAUSE_LINEAR_STMT (c))
12784 gimplify_omp_ctxp = ctx;
12785 push_gimplify_context ();
12786 if (TREE_CODE (OMP_CLAUSE_LINEAR_STMT (c)) != BIND_EXPR)
12788 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
12789 NULL, NULL);
12790 TREE_SIDE_EFFECTS (bind) = 1;
12791 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LINEAR_STMT (c);
12792 OMP_CLAUSE_LINEAR_STMT (c) = bind;
12794 gimplify_and_add (OMP_CLAUSE_LINEAR_STMT (c),
12795 &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c));
12796 pop_gimplify_context
12797 (gimple_seq_first_stmt (OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c)));
12798 OMP_CLAUSE_LINEAR_STMT (c) = NULL_TREE;
12800 gimplify_omp_ctxp = outer_ctx;
12802 if (notice_outer)
12803 goto do_notice;
12804 break;
12806 case OMP_CLAUSE_COPYIN:
12807 case OMP_CLAUSE_COPYPRIVATE:
12808 decl = OMP_CLAUSE_DECL (c);
12809 if (error_operand_p (decl))
12811 remove = true;
12812 break;
12814 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_COPYPRIVATE
12815 && !remove
12816 && !omp_check_private (ctx, decl, true))
12818 remove = true;
12819 if (is_global_var (decl))
12821 if (DECL_THREAD_LOCAL_P (decl))
12822 remove = false;
12823 else if (DECL_HAS_VALUE_EXPR_P (decl))
12825 tree value = get_base_address (DECL_VALUE_EXPR (decl));
12827 if (value
12828 && DECL_P (value)
12829 && DECL_THREAD_LOCAL_P (value))
12830 remove = false;
12833 if (remove)
12834 error_at (OMP_CLAUSE_LOCATION (c),
12835 "copyprivate variable %qE is not threadprivate"
12836 " or private in outer context", DECL_NAME (decl));
12838 do_notice:
12839 if ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
12840 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_FIRSTPRIVATE
12841 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE)
12842 && outer_ctx
12843 && ((region_type & ORT_TASKLOOP) == ORT_TASKLOOP
12844 || (region_type == ORT_WORKSHARE
12845 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
12846 && (OMP_CLAUSE_REDUCTION_INSCAN (c)
12847 || code == OMP_LOOP)))
12848 && (outer_ctx->region_type == ORT_COMBINED_PARALLEL
12849 || (code == OMP_LOOP
12850 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
12851 && ((outer_ctx->region_type & ORT_COMBINED_TEAMS)
12852 == ORT_COMBINED_TEAMS))))
12854 splay_tree_node on
12855 = splay_tree_lookup (outer_ctx->variables,
12856 (splay_tree_key)decl);
12857 if (on == NULL || (on->value & GOVD_DATA_SHARE_CLASS) == 0)
12859 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
12860 && TREE_CODE (OMP_CLAUSE_DECL (c)) == MEM_REF
12861 && (TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE
12862 || (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
12863 && (TREE_CODE (TREE_TYPE (TREE_TYPE (decl)))
12864 == POINTER_TYPE))))
12865 omp_firstprivatize_variable (outer_ctx, decl);
12866 else
12868 omp_add_variable (outer_ctx, decl,
12869 GOVD_SEEN | GOVD_SHARED);
12870 if (outer_ctx->outer_context)
12871 omp_notice_variable (outer_ctx->outer_context, decl,
12872 true);
12876 if (outer_ctx)
12877 omp_notice_variable (outer_ctx, decl, true);
12878 if (check_non_private
12879 && (region_type == ORT_WORKSHARE || code == OMP_SCOPE)
12880 && (OMP_CLAUSE_CODE (c) != OMP_CLAUSE_REDUCTION
12881 || decl == OMP_CLAUSE_DECL (c)
12882 || (TREE_CODE (OMP_CLAUSE_DECL (c)) == MEM_REF
12883 && (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c), 0))
12884 == ADDR_EXPR
12885 || (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c), 0))
12886 == POINTER_PLUS_EXPR
12887 && (TREE_CODE (TREE_OPERAND (TREE_OPERAND
12888 (OMP_CLAUSE_DECL (c), 0), 0))
12889 == ADDR_EXPR)))))
12890 && omp_check_private (ctx, decl, false))
12892 error ("%s variable %qE is private in outer context",
12893 check_non_private, DECL_NAME (decl));
12894 remove = true;
12896 break;
12898 case OMP_CLAUSE_DETACH:
12899 flags = GOVD_FIRSTPRIVATE | GOVD_SEEN;
12900 goto do_add;
12902 case OMP_CLAUSE_IF:
12903 if (OMP_CLAUSE_IF_MODIFIER (c) != ERROR_MARK
12904 && OMP_CLAUSE_IF_MODIFIER (c) != code)
12906 const char *p[2];
12907 for (int i = 0; i < 2; i++)
12908 switch (i ? OMP_CLAUSE_IF_MODIFIER (c) : code)
12910 case VOID_CST: p[i] = "cancel"; break;
12911 case OMP_PARALLEL: p[i] = "parallel"; break;
12912 case OMP_SIMD: p[i] = "simd"; break;
12913 case OMP_TASK: p[i] = "task"; break;
12914 case OMP_TASKLOOP: p[i] = "taskloop"; break;
12915 case OMP_TARGET_DATA: p[i] = "target data"; break;
12916 case OMP_TARGET: p[i] = "target"; break;
12917 case OMP_TARGET_UPDATE: p[i] = "target update"; break;
12918 case OMP_TARGET_ENTER_DATA:
12919 p[i] = "target enter data"; break;
12920 case OMP_TARGET_EXIT_DATA: p[i] = "target exit data"; break;
12921 default: gcc_unreachable ();
12923 error_at (OMP_CLAUSE_LOCATION (c),
12924 "expected %qs %<if%> clause modifier rather than %qs",
12925 p[0], p[1]);
12926 remove = true;
12928 /* Fall through. */
12930 case OMP_CLAUSE_SELF:
12931 case OMP_CLAUSE_FINAL:
12932 OMP_CLAUSE_OPERAND (c, 0)
12933 = gimple_boolify (OMP_CLAUSE_OPERAND (c, 0));
12934 /* Fall through. */
12936 case OMP_CLAUSE_NUM_TEAMS:
12937 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_NUM_TEAMS
12938 && OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c)
12939 && !is_gimple_min_invariant (OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c)))
12941 if (error_operand_p (OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c)))
12943 remove = true;
12944 break;
12946 OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c)
12947 = get_initialized_tmp_var (OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c),
12948 pre_p, NULL, true);
12950 /* Fall through. */
12952 case OMP_CLAUSE_SCHEDULE:
12953 case OMP_CLAUSE_NUM_THREADS:
12954 case OMP_CLAUSE_THREAD_LIMIT:
12955 case OMP_CLAUSE_DIST_SCHEDULE:
12956 case OMP_CLAUSE_DEVICE:
12957 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEVICE
12958 && OMP_CLAUSE_DEVICE_ANCESTOR (c))
12960 if (code != OMP_TARGET)
12962 error_at (OMP_CLAUSE_LOCATION (c),
12963 "%<device%> clause with %<ancestor%> is only "
12964 "allowed on %<target%> construct");
12965 remove = true;
12966 break;
12969 tree clauses = *orig_list_p;
12970 for (; clauses ; clauses = OMP_CLAUSE_CHAIN (clauses))
12971 if (OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_DEVICE
12972 && OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_FIRSTPRIVATE
12973 && OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_PRIVATE
12974 && OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_DEFAULTMAP
12975 && OMP_CLAUSE_CODE (clauses) != OMP_CLAUSE_MAP
12978 error_at (OMP_CLAUSE_LOCATION (c),
12979 "with %<ancestor%>, only the %<device%>, "
12980 "%<firstprivate%>, %<private%>, %<defaultmap%>, "
12981 "and %<map%> clauses may appear on the "
12982 "construct");
12983 remove = true;
12984 break;
12987 /* Fall through. */
12989 case OMP_CLAUSE_PRIORITY:
12990 case OMP_CLAUSE_GRAINSIZE:
12991 case OMP_CLAUSE_NUM_TASKS:
12992 case OMP_CLAUSE_FILTER:
12993 case OMP_CLAUSE_HINT:
12994 case OMP_CLAUSE_ASYNC:
12995 case OMP_CLAUSE_WAIT:
12996 case OMP_CLAUSE_NUM_GANGS:
12997 case OMP_CLAUSE_NUM_WORKERS:
12998 case OMP_CLAUSE_VECTOR_LENGTH:
12999 case OMP_CLAUSE_WORKER:
13000 case OMP_CLAUSE_VECTOR:
13001 if (OMP_CLAUSE_OPERAND (c, 0)
13002 && !is_gimple_min_invariant (OMP_CLAUSE_OPERAND (c, 0)))
13004 if (error_operand_p (OMP_CLAUSE_OPERAND (c, 0)))
13006 remove = true;
13007 break;
13009 /* All these clauses care about value, not a particular decl,
13010 so try to force it into a SSA_NAME or fresh temporary. */
13011 OMP_CLAUSE_OPERAND (c, 0)
13012 = get_initialized_tmp_var (OMP_CLAUSE_OPERAND (c, 0),
13013 pre_p, NULL, true);
13015 break;
13017 case OMP_CLAUSE_GANG:
13018 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 0), pre_p, NULL,
13019 is_gimple_val, fb_rvalue) == GS_ERROR)
13020 remove = true;
13021 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 1), pre_p, NULL,
13022 is_gimple_val, fb_rvalue) == GS_ERROR)
13023 remove = true;
13024 break;
13026 case OMP_CLAUSE_NOWAIT:
13027 nowait = 1;
13028 break;
13030 case OMP_CLAUSE_ORDERED:
13031 case OMP_CLAUSE_UNTIED:
13032 case OMP_CLAUSE_COLLAPSE:
13033 case OMP_CLAUSE_TILE:
13034 case OMP_CLAUSE_AUTO:
13035 case OMP_CLAUSE_SEQ:
13036 case OMP_CLAUSE_INDEPENDENT:
13037 case OMP_CLAUSE_MERGEABLE:
13038 case OMP_CLAUSE_PROC_BIND:
13039 case OMP_CLAUSE_SAFELEN:
13040 case OMP_CLAUSE_SIMDLEN:
13041 case OMP_CLAUSE_NOGROUP:
13042 case OMP_CLAUSE_THREADS:
13043 case OMP_CLAUSE_SIMD:
13044 case OMP_CLAUSE_BIND:
13045 case OMP_CLAUSE_IF_PRESENT:
13046 case OMP_CLAUSE_FINALIZE:
13047 break;
13049 case OMP_CLAUSE_ORDER:
13050 ctx->order_concurrent = true;
13051 break;
13053 case OMP_CLAUSE_DEFAULTMAP:
13054 enum gimplify_defaultmap_kind gdmkmin, gdmkmax;
13055 switch (OMP_CLAUSE_DEFAULTMAP_CATEGORY (c))
13057 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_UNSPECIFIED:
13058 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_ALL:
13059 gdmkmin = GDMK_SCALAR;
13060 gdmkmax = GDMK_POINTER;
13061 break;
13062 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_SCALAR:
13063 gdmkmin = GDMK_SCALAR;
13064 gdmkmax = GDMK_SCALAR_TARGET;
13065 break;
13066 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_AGGREGATE:
13067 gdmkmin = gdmkmax = GDMK_AGGREGATE;
13068 break;
13069 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_ALLOCATABLE:
13070 gdmkmin = gdmkmax = GDMK_ALLOCATABLE;
13071 break;
13072 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_POINTER:
13073 gdmkmin = gdmkmax = GDMK_POINTER;
13074 break;
13075 default:
13076 gcc_unreachable ();
13078 for (int gdmk = gdmkmin; gdmk <= gdmkmax; gdmk++)
13079 switch (OMP_CLAUSE_DEFAULTMAP_BEHAVIOR (c))
13081 case OMP_CLAUSE_DEFAULTMAP_ALLOC:
13082 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_ALLOC_ONLY;
13083 break;
13084 case OMP_CLAUSE_DEFAULTMAP_TO:
13085 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_TO_ONLY;
13086 break;
13087 case OMP_CLAUSE_DEFAULTMAP_FROM:
13088 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_FROM_ONLY;
13089 break;
13090 case OMP_CLAUSE_DEFAULTMAP_TOFROM:
13091 ctx->defaultmap[gdmk] = GOVD_MAP;
13092 break;
13093 case OMP_CLAUSE_DEFAULTMAP_FIRSTPRIVATE:
13094 ctx->defaultmap[gdmk] = GOVD_FIRSTPRIVATE;
13095 break;
13096 case OMP_CLAUSE_DEFAULTMAP_NONE:
13097 ctx->defaultmap[gdmk] = 0;
13098 break;
13099 case OMP_CLAUSE_DEFAULTMAP_PRESENT:
13100 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_FORCE_PRESENT;
13101 break;
13102 case OMP_CLAUSE_DEFAULTMAP_DEFAULT:
13103 switch (gdmk)
13105 case GDMK_SCALAR:
13106 ctx->defaultmap[gdmk] = GOVD_FIRSTPRIVATE;
13107 break;
13108 case GDMK_SCALAR_TARGET:
13109 ctx->defaultmap[gdmk] = (lang_GNU_Fortran ()
13110 ? GOVD_MAP : GOVD_FIRSTPRIVATE);
13111 break;
13112 case GDMK_AGGREGATE:
13113 case GDMK_ALLOCATABLE:
13114 ctx->defaultmap[gdmk] = GOVD_MAP;
13115 break;
13116 case GDMK_POINTER:
13117 ctx->defaultmap[gdmk] = GOVD_MAP;
13118 if (!lang_GNU_Fortran ())
13119 ctx->defaultmap[gdmk] |= GOVD_MAP_0LEN_ARRAY;
13120 break;
13121 default:
13122 gcc_unreachable ();
13124 break;
13125 default:
13126 gcc_unreachable ();
13128 break;
13130 case OMP_CLAUSE_ALIGNED:
13131 decl = OMP_CLAUSE_DECL (c);
13132 if (error_operand_p (decl))
13134 remove = true;
13135 break;
13137 if (gimplify_expr (&OMP_CLAUSE_ALIGNED_ALIGNMENT (c), pre_p, NULL,
13138 is_gimple_val, fb_rvalue) == GS_ERROR)
13140 remove = true;
13141 break;
13143 if (!is_global_var (decl)
13144 && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
13145 omp_add_variable (ctx, decl, GOVD_ALIGNED);
13146 break;
13148 case OMP_CLAUSE_NONTEMPORAL:
13149 decl = OMP_CLAUSE_DECL (c);
13150 if (error_operand_p (decl))
13152 remove = true;
13153 break;
13155 omp_add_variable (ctx, decl, GOVD_NONTEMPORAL);
13156 break;
13158 case OMP_CLAUSE_ALLOCATE:
13159 decl = OMP_CLAUSE_DECL (c);
13160 if (error_operand_p (decl))
13162 remove = true;
13163 break;
13165 if (gimplify_expr (&OMP_CLAUSE_ALLOCATE_ALLOCATOR (c), pre_p, NULL,
13166 is_gimple_val, fb_rvalue) == GS_ERROR)
13168 remove = true;
13169 break;
13171 else if (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c) == NULL_TREE
13172 || (TREE_CODE (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c))
13173 == INTEGER_CST))
13175 else if (code == OMP_TASKLOOP
13176 || !DECL_P (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)))
13177 OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
13178 = get_initialized_tmp_var (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
13179 pre_p, NULL, false);
13180 break;
13182 case OMP_CLAUSE_DEFAULT:
13183 ctx->default_kind = OMP_CLAUSE_DEFAULT_KIND (c);
13184 break;
13186 case OMP_CLAUSE_INCLUSIVE:
13187 case OMP_CLAUSE_EXCLUSIVE:
13188 decl = OMP_CLAUSE_DECL (c);
13190 splay_tree_node n = splay_tree_lookup (outer_ctx->variables,
13191 (splay_tree_key) decl);
13192 if (n == NULL || (n->value & GOVD_REDUCTION) == 0)
13194 error_at (OMP_CLAUSE_LOCATION (c),
13195 "%qD specified in %qs clause but not in %<inscan%> "
13196 "%<reduction%> clause on the containing construct",
13197 decl, omp_clause_code_name[OMP_CLAUSE_CODE (c)]);
13198 remove = true;
13200 else
13202 n->value |= GOVD_REDUCTION_INSCAN;
13203 if (outer_ctx->region_type == ORT_SIMD
13204 && outer_ctx->outer_context
13205 && outer_ctx->outer_context->region_type == ORT_WORKSHARE)
13207 n = splay_tree_lookup (outer_ctx->outer_context->variables,
13208 (splay_tree_key) decl);
13209 if (n && (n->value & GOVD_REDUCTION) != 0)
13210 n->value |= GOVD_REDUCTION_INSCAN;
13214 break;
13216 case OMP_CLAUSE_NOHOST:
13217 default:
13218 gcc_unreachable ();
13221 if (code == OACC_DATA
13222 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP
13223 && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
13224 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
13225 remove = true;
13226 if (remove)
13227 *list_p = OMP_CLAUSE_CHAIN (c);
13228 else
13229 list_p = &OMP_CLAUSE_CHAIN (c);
13232 if (groups)
13234 delete grpmap;
13235 delete groups;
13238 ctx->clauses = *orig_list_p;
13239 gimplify_omp_ctxp = ctx;
13242 /* Return true if DECL is a candidate for shared to firstprivate
13243 optimization. We only consider non-addressable scalars, not
13244 too big, and not references. */
13246 static bool
13247 omp_shared_to_firstprivate_optimizable_decl_p (tree decl)
13249 if (TREE_ADDRESSABLE (decl))
13250 return false;
13251 tree type = TREE_TYPE (decl);
13252 if (!is_gimple_reg_type (type)
13253 || TREE_CODE (type) == REFERENCE_TYPE
13254 || TREE_ADDRESSABLE (type))
13255 return false;
13256 /* Don't optimize too large decls, as each thread/task will have
13257 its own. */
13258 HOST_WIDE_INT len = int_size_in_bytes (type);
13259 if (len == -1 || len > 4 * POINTER_SIZE / BITS_PER_UNIT)
13260 return false;
13261 if (omp_privatize_by_reference (decl))
13262 return false;
13263 return true;
13266 /* Helper function of omp_find_stores_op and gimplify_adjust_omp_clauses*.
13267 For omp_shared_to_firstprivate_optimizable_decl_p decl mark it as
13268 GOVD_WRITTEN in outer contexts. */
13270 static void
13271 omp_mark_stores (struct gimplify_omp_ctx *ctx, tree decl)
13273 for (; ctx; ctx = ctx->outer_context)
13275 splay_tree_node n = splay_tree_lookup (ctx->variables,
13276 (splay_tree_key) decl);
13277 if (n == NULL)
13278 continue;
13279 else if (n->value & GOVD_SHARED)
13281 n->value |= GOVD_WRITTEN;
13282 return;
13284 else if (n->value & GOVD_DATA_SHARE_CLASS)
13285 return;
13289 /* Helper callback for walk_gimple_seq to discover possible stores
13290 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
13291 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
13292 for those. */
13294 static tree
13295 omp_find_stores_op (tree *tp, int *walk_subtrees, void *data)
13297 struct walk_stmt_info *wi = (struct walk_stmt_info *) data;
13299 *walk_subtrees = 0;
13300 if (!wi->is_lhs)
13301 return NULL_TREE;
13303 tree op = *tp;
13306 if (handled_component_p (op))
13307 op = TREE_OPERAND (op, 0);
13308 else if ((TREE_CODE (op) == MEM_REF || TREE_CODE (op) == TARGET_MEM_REF)
13309 && TREE_CODE (TREE_OPERAND (op, 0)) == ADDR_EXPR)
13310 op = TREE_OPERAND (TREE_OPERAND (op, 0), 0);
13311 else
13312 break;
13314 while (1);
13315 if (!DECL_P (op) || !omp_shared_to_firstprivate_optimizable_decl_p (op))
13316 return NULL_TREE;
13318 omp_mark_stores (gimplify_omp_ctxp, op);
13319 return NULL_TREE;
13322 /* Helper callback for walk_gimple_seq to discover possible stores
13323 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
13324 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
13325 for those. */
13327 static tree
13328 omp_find_stores_stmt (gimple_stmt_iterator *gsi_p,
13329 bool *handled_ops_p,
13330 struct walk_stmt_info *wi)
13332 gimple *stmt = gsi_stmt (*gsi_p);
13333 switch (gimple_code (stmt))
13335 /* Don't recurse on OpenMP constructs for which
13336 gimplify_adjust_omp_clauses already handled the bodies,
13337 except handle gimple_omp_for_pre_body. */
13338 case GIMPLE_OMP_FOR:
13339 *handled_ops_p = true;
13340 if (gimple_omp_for_pre_body (stmt))
13341 walk_gimple_seq (gimple_omp_for_pre_body (stmt),
13342 omp_find_stores_stmt, omp_find_stores_op, wi);
13343 break;
13344 case GIMPLE_OMP_PARALLEL:
13345 case GIMPLE_OMP_TASK:
13346 case GIMPLE_OMP_SECTIONS:
13347 case GIMPLE_OMP_SINGLE:
13348 case GIMPLE_OMP_SCOPE:
13349 case GIMPLE_OMP_TARGET:
13350 case GIMPLE_OMP_TEAMS:
13351 case GIMPLE_OMP_CRITICAL:
13352 *handled_ops_p = true;
13353 break;
13354 default:
13355 break;
13357 return NULL_TREE;
13360 struct gimplify_adjust_omp_clauses_data
13362 tree *list_p;
13363 gimple_seq *pre_p;
13366 /* For all variables that were not actually used within the context,
13367 remove PRIVATE, SHARED, and FIRSTPRIVATE clauses. */
13369 static int
13370 gimplify_adjust_omp_clauses_1 (splay_tree_node n, void *data)
13372 tree *list_p = ((struct gimplify_adjust_omp_clauses_data *) data)->list_p;
13373 gimple_seq *pre_p
13374 = ((struct gimplify_adjust_omp_clauses_data *) data)->pre_p;
13375 tree decl = (tree) n->key;
13376 unsigned flags = n->value;
13377 enum omp_clause_code code;
13378 tree clause;
13379 bool private_debug;
13381 if (gimplify_omp_ctxp->region_type == ORT_COMBINED_PARALLEL
13382 && (flags & GOVD_LASTPRIVATE_CONDITIONAL) != 0)
13383 flags = GOVD_SHARED | GOVD_SEEN | GOVD_WRITTEN;
13384 if (flags & (GOVD_EXPLICIT | GOVD_LOCAL))
13385 return 0;
13386 if ((flags & GOVD_SEEN) == 0)
13387 return 0;
13388 if (flags & GOVD_DEBUG_PRIVATE)
13390 gcc_assert ((flags & GOVD_DATA_SHARE_CLASS) == GOVD_SHARED);
13391 private_debug = true;
13393 else if (flags & GOVD_MAP)
13394 private_debug = false;
13395 else
13396 private_debug
13397 = lang_hooks.decls.omp_private_debug_clause (decl,
13398 !!(flags & GOVD_SHARED));
13399 if (private_debug)
13400 code = OMP_CLAUSE_PRIVATE;
13401 else if (flags & GOVD_MAP)
13403 code = OMP_CLAUSE_MAP;
13404 if ((gimplify_omp_ctxp->region_type & ORT_ACC) == 0
13405 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl))))
13407 error ("%<_Atomic%> %qD in implicit %<map%> clause", decl);
13408 return 0;
13410 if (VAR_P (decl)
13411 && DECL_IN_CONSTANT_POOL (decl)
13412 && !lookup_attribute ("omp declare target",
13413 DECL_ATTRIBUTES (decl)))
13415 tree id = get_identifier ("omp declare target");
13416 DECL_ATTRIBUTES (decl)
13417 = tree_cons (id, NULL_TREE, DECL_ATTRIBUTES (decl));
13418 varpool_node *node = varpool_node::get (decl);
13419 if (node)
13421 node->offloadable = 1;
13422 if (ENABLE_OFFLOADING)
13423 g->have_offload = true;
13427 else if (flags & GOVD_SHARED)
13429 if (is_global_var (decl))
13431 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
13432 while (ctx != NULL)
13434 splay_tree_node on
13435 = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
13436 if (on && (on->value & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
13437 | GOVD_PRIVATE | GOVD_REDUCTION
13438 | GOVD_LINEAR | GOVD_MAP)) != 0)
13439 break;
13440 ctx = ctx->outer_context;
13442 if (ctx == NULL)
13443 return 0;
13445 code = OMP_CLAUSE_SHARED;
13446 /* Don't optimize shared into firstprivate for read-only vars
13447 on tasks with depend clause, we shouldn't try to copy them
13448 until the dependencies are satisfied. */
13449 if (gimplify_omp_ctxp->has_depend)
13450 flags |= GOVD_WRITTEN;
13452 else if (flags & GOVD_PRIVATE)
13453 code = OMP_CLAUSE_PRIVATE;
13454 else if (flags & GOVD_FIRSTPRIVATE)
13456 code = OMP_CLAUSE_FIRSTPRIVATE;
13457 if ((gimplify_omp_ctxp->region_type & ORT_TARGET)
13458 && (gimplify_omp_ctxp->region_type & ORT_ACC) == 0
13459 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl))))
13461 error ("%<_Atomic%> %qD in implicit %<firstprivate%> clause on "
13462 "%<target%> construct", decl);
13463 return 0;
13466 else if (flags & GOVD_LASTPRIVATE)
13467 code = OMP_CLAUSE_LASTPRIVATE;
13468 else if (flags & (GOVD_ALIGNED | GOVD_NONTEMPORAL))
13469 return 0;
13470 else if (flags & GOVD_CONDTEMP)
13472 code = OMP_CLAUSE__CONDTEMP_;
13473 gimple_add_tmp_var (decl);
13475 else
13476 gcc_unreachable ();
13478 if (((flags & GOVD_LASTPRIVATE)
13479 || (code == OMP_CLAUSE_SHARED && (flags & GOVD_WRITTEN)))
13480 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
13481 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
13483 tree chain = *list_p;
13484 clause = build_omp_clause (input_location, code);
13485 OMP_CLAUSE_DECL (clause) = decl;
13486 OMP_CLAUSE_CHAIN (clause) = chain;
13487 if (private_debug)
13488 OMP_CLAUSE_PRIVATE_DEBUG (clause) = 1;
13489 else if (code == OMP_CLAUSE_PRIVATE && (flags & GOVD_PRIVATE_OUTER_REF))
13490 OMP_CLAUSE_PRIVATE_OUTER_REF (clause) = 1;
13491 else if (code == OMP_CLAUSE_SHARED
13492 && (flags & GOVD_WRITTEN) == 0
13493 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
13494 OMP_CLAUSE_SHARED_READONLY (clause) = 1;
13495 else if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_EXPLICIT) == 0)
13496 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (clause) = 1;
13497 else if (code == OMP_CLAUSE_MAP && (flags & GOVD_MAP_0LEN_ARRAY) != 0)
13499 tree nc = build_omp_clause (input_location, OMP_CLAUSE_MAP);
13500 OMP_CLAUSE_DECL (nc) = decl;
13501 if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
13502 && TREE_CODE (TREE_TYPE (TREE_TYPE (decl))) == POINTER_TYPE)
13503 OMP_CLAUSE_DECL (clause)
13504 = build_fold_indirect_ref_loc (input_location, decl);
13505 OMP_CLAUSE_DECL (clause)
13506 = build2 (MEM_REF, char_type_node, OMP_CLAUSE_DECL (clause),
13507 build_int_cst (build_pointer_type (char_type_node), 0));
13508 OMP_CLAUSE_SIZE (clause) = size_zero_node;
13509 OMP_CLAUSE_SIZE (nc) = size_zero_node;
13510 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_ALLOC);
13511 OMP_CLAUSE_MAP_MAYBE_ZERO_LENGTH_ARRAY_SECTION (clause) = 1;
13512 tree dtype = TREE_TYPE (decl);
13513 if (TREE_CODE (dtype) == REFERENCE_TYPE)
13514 dtype = TREE_TYPE (dtype);
13515 /* FIRSTPRIVATE_POINTER doesn't work well if we have a
13516 multiply-indirected pointer. If we have a reference to a pointer to
13517 a pointer, it's possible that this should really be
13518 GOMP_MAP_FIRSTPRIVATE_REFERENCE -- but that also doesn't work at the
13519 moment, so stick with this. (See PR113279 and testcases
13520 baseptrs-{4,6}.C:ref2ptrptr_offset_decl_member_slice). */
13521 if (TREE_CODE (dtype) == POINTER_TYPE
13522 && TREE_CODE (TREE_TYPE (dtype)) == POINTER_TYPE)
13523 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
13524 else
13525 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_POINTER);
13526 OMP_CLAUSE_CHAIN (nc) = chain;
13527 OMP_CLAUSE_CHAIN (clause) = nc;
13528 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
13529 gimplify_omp_ctxp = ctx->outer_context;
13530 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (clause), 0),
13531 pre_p, NULL, is_gimple_val, fb_rvalue);
13532 gimplify_omp_ctxp = ctx;
13534 else if (code == OMP_CLAUSE_MAP)
13536 int kind;
13537 /* Not all combinations of these GOVD_MAP flags are actually valid. */
13538 switch (flags & (GOVD_MAP_TO_ONLY
13539 | GOVD_MAP_FORCE
13540 | GOVD_MAP_FORCE_PRESENT
13541 | GOVD_MAP_ALLOC_ONLY
13542 | GOVD_MAP_FROM_ONLY))
13544 case 0:
13545 kind = GOMP_MAP_TOFROM;
13546 break;
13547 case GOVD_MAP_FORCE:
13548 kind = GOMP_MAP_TOFROM | GOMP_MAP_FLAG_FORCE;
13549 break;
13550 case GOVD_MAP_TO_ONLY:
13551 kind = GOMP_MAP_TO;
13552 break;
13553 case GOVD_MAP_FROM_ONLY:
13554 kind = GOMP_MAP_FROM;
13555 break;
13556 case GOVD_MAP_ALLOC_ONLY:
13557 kind = GOMP_MAP_ALLOC;
13558 break;
13559 case GOVD_MAP_TO_ONLY | GOVD_MAP_FORCE:
13560 kind = GOMP_MAP_TO | GOMP_MAP_FLAG_FORCE;
13561 break;
13562 case GOVD_MAP_FORCE_PRESENT:
13563 kind = GOMP_MAP_FORCE_PRESENT;
13564 break;
13565 case GOVD_MAP_FORCE_PRESENT | GOVD_MAP_ALLOC_ONLY:
13566 kind = GOMP_MAP_FORCE_PRESENT;
13567 break;
13568 default:
13569 gcc_unreachable ();
13571 OMP_CLAUSE_SET_MAP_KIND (clause, kind);
13572 /* Setting of the implicit flag for the runtime is currently disabled for
13573 OpenACC. */
13574 if ((gimplify_omp_ctxp->region_type & ORT_ACC) == 0)
13575 OMP_CLAUSE_MAP_RUNTIME_IMPLICIT_P (clause) = 1;
13576 if (DECL_SIZE (decl)
13577 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
13579 tree decl2 = DECL_VALUE_EXPR (decl);
13580 gcc_assert (INDIRECT_REF_P (decl2));
13581 decl2 = TREE_OPERAND (decl2, 0);
13582 gcc_assert (DECL_P (decl2));
13583 tree mem = build_simple_mem_ref (decl2);
13584 OMP_CLAUSE_DECL (clause) = mem;
13585 OMP_CLAUSE_SIZE (clause) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
13586 if (gimplify_omp_ctxp->outer_context)
13588 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
13589 omp_notice_variable (ctx, decl2, true);
13590 omp_notice_variable (ctx, OMP_CLAUSE_SIZE (clause), true);
13592 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
13593 OMP_CLAUSE_MAP);
13594 OMP_CLAUSE_DECL (nc) = decl;
13595 OMP_CLAUSE_SIZE (nc) = size_zero_node;
13596 if (gimplify_omp_ctxp->target_firstprivatize_array_bases)
13597 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_POINTER);
13598 else
13599 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
13600 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
13601 OMP_CLAUSE_CHAIN (clause) = nc;
13603 else if (gimplify_omp_ctxp->target_firstprivatize_array_bases
13604 && omp_privatize_by_reference (decl))
13606 OMP_CLAUSE_DECL (clause) = build_simple_mem_ref (decl);
13607 OMP_CLAUSE_SIZE (clause)
13608 = unshare_expr (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl))));
13609 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
13610 gimplify_omp_ctxp = ctx->outer_context;
13611 gimplify_expr (&OMP_CLAUSE_SIZE (clause),
13612 pre_p, NULL, is_gimple_val, fb_rvalue);
13613 gimplify_omp_ctxp = ctx;
13614 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
13615 OMP_CLAUSE_MAP);
13616 OMP_CLAUSE_DECL (nc) = decl;
13617 OMP_CLAUSE_SIZE (nc) = size_zero_node;
13618 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_REFERENCE);
13619 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
13620 OMP_CLAUSE_CHAIN (clause) = nc;
13622 else
13623 OMP_CLAUSE_SIZE (clause) = DECL_SIZE_UNIT (decl);
13625 if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_LASTPRIVATE) != 0)
13627 tree nc = build_omp_clause (input_location, OMP_CLAUSE_LASTPRIVATE);
13628 OMP_CLAUSE_DECL (nc) = decl;
13629 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (nc) = 1;
13630 OMP_CLAUSE_CHAIN (nc) = chain;
13631 OMP_CLAUSE_CHAIN (clause) = nc;
13632 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
13633 gimplify_omp_ctxp = ctx->outer_context;
13634 lang_hooks.decls.omp_finish_clause (nc, pre_p,
13635 (ctx->region_type & ORT_ACC) != 0);
13636 gimplify_omp_ctxp = ctx;
13638 *list_p = clause;
13639 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
13640 gimplify_omp_ctxp = ctx->outer_context;
13641 /* Don't call omp_finish_clause on implicitly added OMP_CLAUSE_PRIVATE
13642 in simd. Those are only added for the local vars inside of simd body
13643 and they don't need to be e.g. default constructible. */
13644 if (code != OMP_CLAUSE_PRIVATE || ctx->region_type != ORT_SIMD)
13645 lang_hooks.decls.omp_finish_clause (clause, pre_p,
13646 (ctx->region_type & ORT_ACC) != 0);
13647 if (gimplify_omp_ctxp)
13648 for (; clause != chain; clause = OMP_CLAUSE_CHAIN (clause))
13649 if (OMP_CLAUSE_CODE (clause) == OMP_CLAUSE_MAP
13650 && DECL_P (OMP_CLAUSE_SIZE (clause)))
13651 omp_notice_variable (gimplify_omp_ctxp, OMP_CLAUSE_SIZE (clause),
13652 true);
13653 gimplify_omp_ctxp = ctx;
13654 return 0;
13657 static void
13658 gimplify_adjust_omp_clauses (gimple_seq *pre_p, gimple_seq body, tree *list_p,
13659 enum tree_code code)
13661 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
13662 tree *orig_list_p = list_p;
13663 tree c, decl;
13664 bool has_inscan_reductions = false;
13666 if (body)
13668 struct gimplify_omp_ctx *octx;
13669 for (octx = ctx; octx; octx = octx->outer_context)
13670 if ((octx->region_type & (ORT_PARALLEL | ORT_TASK | ORT_TEAMS)) != 0)
13671 break;
13672 if (octx)
13674 struct walk_stmt_info wi;
13675 memset (&wi, 0, sizeof (wi));
13676 walk_gimple_seq (body, omp_find_stores_stmt,
13677 omp_find_stores_op, &wi);
13681 if (ctx->add_safelen1)
13683 /* If there are VLAs in the body of simd loop, prevent
13684 vectorization. */
13685 gcc_assert (ctx->region_type == ORT_SIMD);
13686 c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_SAFELEN);
13687 OMP_CLAUSE_SAFELEN_EXPR (c) = integer_one_node;
13688 OMP_CLAUSE_CHAIN (c) = *list_p;
13689 *list_p = c;
13690 list_p = &OMP_CLAUSE_CHAIN (c);
13693 if (ctx->region_type == ORT_WORKSHARE
13694 && ctx->outer_context
13695 && ctx->outer_context->region_type == ORT_COMBINED_PARALLEL)
13697 for (c = ctx->outer_context->clauses; c; c = OMP_CLAUSE_CHAIN (c))
13698 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
13699 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
13701 decl = OMP_CLAUSE_DECL (c);
13702 splay_tree_node n
13703 = splay_tree_lookup (ctx->outer_context->variables,
13704 (splay_tree_key) decl);
13705 gcc_checking_assert (!splay_tree_lookup (ctx->variables,
13706 (splay_tree_key) decl));
13707 omp_add_variable (ctx, decl, n->value);
13708 tree c2 = copy_node (c);
13709 OMP_CLAUSE_CHAIN (c2) = *list_p;
13710 *list_p = c2;
13711 if ((n->value & GOVD_FIRSTPRIVATE) == 0)
13712 continue;
13713 c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
13714 OMP_CLAUSE_FIRSTPRIVATE);
13715 OMP_CLAUSE_DECL (c2) = decl;
13716 OMP_CLAUSE_CHAIN (c2) = *list_p;
13717 *list_p = c2;
13721 if (code == OMP_TARGET
13722 || code == OMP_TARGET_DATA
13723 || code == OMP_TARGET_ENTER_DATA
13724 || code == OMP_TARGET_EXIT_DATA)
13726 vec<omp_mapping_group> *groups;
13727 groups = omp_gather_mapping_groups (list_p);
13728 hash_map<tree_operand_hash_no_se, omp_mapping_group *> *grpmap = NULL;
13730 if (groups)
13732 grpmap = omp_index_mapping_groups (groups);
13734 omp_resolve_clause_dependencies (code, groups, grpmap);
13735 omp_build_struct_sibling_lists (code, ctx->region_type, groups,
13736 &grpmap, list_p);
13738 omp_mapping_group *outlist = NULL;
13740 delete grpmap;
13741 delete groups;
13743 /* Rebuild now we have struct sibling lists. */
13744 groups = omp_gather_mapping_groups (list_p);
13745 grpmap = omp_index_mapping_groups (groups);
13747 bool enter_exit = (code == OMP_TARGET_ENTER_DATA
13748 || code == OMP_TARGET_EXIT_DATA);
13750 outlist = omp_tsort_mapping_groups (groups, grpmap, enter_exit);
13751 outlist = omp_segregate_mapping_groups (outlist);
13752 list_p = omp_reorder_mapping_groups (groups, outlist, list_p);
13754 delete grpmap;
13755 delete groups;
13758 else if (ctx->region_type & ORT_ACC)
13760 vec<omp_mapping_group> *groups;
13761 groups = omp_gather_mapping_groups (list_p);
13762 if (groups)
13764 hash_map<tree_operand_hash_no_se, omp_mapping_group *> *grpmap;
13765 grpmap = omp_index_mapping_groups (groups);
13767 oacc_resolve_clause_dependencies (groups, grpmap);
13768 omp_build_struct_sibling_lists (code, ctx->region_type, groups,
13769 &grpmap, list_p);
13771 delete groups;
13772 delete grpmap;
13776 tree attach_list = NULL_TREE;
13777 tree *attach_tail = &attach_list;
13779 tree *grp_start_p = NULL, grp_end = NULL_TREE;
13781 while ((c = *list_p) != NULL)
13783 splay_tree_node n;
13784 bool remove = false;
13785 bool move_attach = false;
13787 if (grp_end && c == OMP_CLAUSE_CHAIN (grp_end))
13788 grp_end = NULL_TREE;
13790 switch (OMP_CLAUSE_CODE (c))
13792 case OMP_CLAUSE_FIRSTPRIVATE:
13793 if ((ctx->region_type & ORT_TARGET)
13794 && (ctx->region_type & ORT_ACC) == 0
13795 && TYPE_ATOMIC (strip_array_types
13796 (TREE_TYPE (OMP_CLAUSE_DECL (c)))))
13798 error_at (OMP_CLAUSE_LOCATION (c),
13799 "%<_Atomic%> %qD in %<firstprivate%> clause on "
13800 "%<target%> construct", OMP_CLAUSE_DECL (c));
13801 remove = true;
13802 break;
13804 if (OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (c))
13806 decl = OMP_CLAUSE_DECL (c);
13807 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
13808 if ((n->value & GOVD_MAP) != 0)
13810 remove = true;
13811 break;
13813 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT_TARGET (c) = 0;
13814 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (c) = 0;
13816 /* FALLTHRU */
13817 case OMP_CLAUSE_PRIVATE:
13818 case OMP_CLAUSE_SHARED:
13819 case OMP_CLAUSE_LINEAR:
13820 decl = OMP_CLAUSE_DECL (c);
13821 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
13822 remove = !(n->value & GOVD_SEEN);
13823 if ((n->value & GOVD_LASTPRIVATE_CONDITIONAL) != 0
13824 && code == OMP_PARALLEL
13825 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_FIRSTPRIVATE)
13826 remove = true;
13827 if (! remove)
13829 bool shared = OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED;
13830 if ((n->value & GOVD_DEBUG_PRIVATE)
13831 || lang_hooks.decls.omp_private_debug_clause (decl, shared))
13833 gcc_assert ((n->value & GOVD_DEBUG_PRIVATE) == 0
13834 || ((n->value & GOVD_DATA_SHARE_CLASS)
13835 == GOVD_SHARED));
13836 OMP_CLAUSE_SET_CODE (c, OMP_CLAUSE_PRIVATE);
13837 OMP_CLAUSE_PRIVATE_DEBUG (c) = 1;
13839 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
13840 && ctx->has_depend
13841 && DECL_P (decl))
13842 n->value |= GOVD_WRITTEN;
13843 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
13844 && (n->value & GOVD_WRITTEN) == 0
13845 && DECL_P (decl)
13846 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
13847 OMP_CLAUSE_SHARED_READONLY (c) = 1;
13848 else if (DECL_P (decl)
13849 && ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
13850 && (n->value & GOVD_WRITTEN) != 0)
13851 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
13852 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
13853 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
13854 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
13856 else
13857 n->value &= ~GOVD_EXPLICIT;
13858 break;
13860 case OMP_CLAUSE_LASTPRIVATE:
13861 /* Make sure OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE is set to
13862 accurately reflect the presence of a FIRSTPRIVATE clause. */
13863 decl = OMP_CLAUSE_DECL (c);
13864 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
13865 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c)
13866 = (n->value & GOVD_FIRSTPRIVATE) != 0;
13867 if (code == OMP_DISTRIBUTE
13868 && OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
13870 remove = true;
13871 error_at (OMP_CLAUSE_LOCATION (c),
13872 "same variable used in %<firstprivate%> and "
13873 "%<lastprivate%> clauses on %<distribute%> "
13874 "construct");
13876 if (!remove
13877 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
13878 && DECL_P (decl)
13879 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
13880 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
13881 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) && code == OMP_PARALLEL)
13882 remove = true;
13883 break;
13885 case OMP_CLAUSE_ALIGNED:
13886 decl = OMP_CLAUSE_DECL (c);
13887 if (!is_global_var (decl))
13889 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
13890 remove = n == NULL || !(n->value & GOVD_SEEN);
13891 if (!remove && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
13893 struct gimplify_omp_ctx *octx;
13894 if (n != NULL
13895 && (n->value & (GOVD_DATA_SHARE_CLASS
13896 & ~GOVD_FIRSTPRIVATE)))
13897 remove = true;
13898 else
13899 for (octx = ctx->outer_context; octx;
13900 octx = octx->outer_context)
13902 n = splay_tree_lookup (octx->variables,
13903 (splay_tree_key) decl);
13904 if (n == NULL)
13905 continue;
13906 if (n->value & GOVD_LOCAL)
13907 break;
13908 /* We have to avoid assigning a shared variable
13909 to itself when trying to add
13910 __builtin_assume_aligned. */
13911 if (n->value & GOVD_SHARED)
13913 remove = true;
13914 break;
13919 else if (TREE_CODE (TREE_TYPE (decl)) == ARRAY_TYPE)
13921 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
13922 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
13923 remove = true;
13925 break;
13927 case OMP_CLAUSE_HAS_DEVICE_ADDR:
13928 decl = OMP_CLAUSE_DECL (c);
13929 while (INDIRECT_REF_P (decl)
13930 || TREE_CODE (decl) == ARRAY_REF)
13931 decl = TREE_OPERAND (decl, 0);
13932 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
13933 remove = n == NULL || !(n->value & GOVD_SEEN);
13934 break;
13936 case OMP_CLAUSE_IS_DEVICE_PTR:
13937 case OMP_CLAUSE_NONTEMPORAL:
13938 decl = OMP_CLAUSE_DECL (c);
13939 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
13940 remove = n == NULL || !(n->value & GOVD_SEEN);
13941 break;
13943 case OMP_CLAUSE_MAP:
13944 decl = OMP_CLAUSE_DECL (c);
13945 if (!grp_end)
13947 grp_start_p = list_p;
13948 grp_end = *omp_group_last (grp_start_p);
13950 switch (OMP_CLAUSE_MAP_KIND (c))
13952 case GOMP_MAP_PRESENT_ALLOC:
13953 case GOMP_MAP_PRESENT_TO:
13954 case GOMP_MAP_PRESENT_FROM:
13955 case GOMP_MAP_PRESENT_TOFROM:
13956 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FORCE_PRESENT);
13957 break;
13958 default:
13959 break;
13961 switch (code)
13963 case OACC_DATA:
13964 if (TREE_CODE (TREE_TYPE (decl)) != ARRAY_TYPE)
13965 break;
13966 /* Fallthrough. */
13967 case OACC_HOST_DATA:
13968 case OACC_ENTER_DATA:
13969 case OACC_EXIT_DATA:
13970 case OMP_TARGET_DATA:
13971 case OMP_TARGET_ENTER_DATA:
13972 case OMP_TARGET_EXIT_DATA:
13973 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
13974 || (OMP_CLAUSE_MAP_KIND (c)
13975 == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
13976 /* For target {,enter ,exit }data only the array slice is
13977 mapped, but not the pointer to it. */
13978 remove = true;
13979 if (code == OMP_TARGET_EXIT_DATA
13980 && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_POINTER
13981 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_POINTER))
13982 remove = true;
13983 break;
13984 case OMP_TARGET:
13985 break;
13986 default:
13987 break;
13989 if (remove)
13990 break;
13991 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
13993 /* Sanity check: attach/detach map kinds use the size as a bias,
13994 and it's never right to use the decl size for such
13995 mappings. */
13996 gcc_assert (OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ATTACH
13997 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_DETACH
13998 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FORCE_DETACH
13999 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ATTACH_DETACH
14000 && (OMP_CLAUSE_MAP_KIND (c)
14001 != GOMP_MAP_ATTACH_ZERO_LENGTH_ARRAY_SECTION));
14002 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
14003 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
14005 gimplify_omp_ctxp = ctx->outer_context;
14006 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p, NULL,
14007 is_gimple_val, fb_rvalue) == GS_ERROR)
14009 gimplify_omp_ctxp = ctx;
14010 remove = true;
14011 break;
14013 else if ((OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
14014 || (OMP_CLAUSE_MAP_KIND (c)
14015 == GOMP_MAP_FIRSTPRIVATE_REFERENCE)
14016 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
14017 && TREE_CODE (OMP_CLAUSE_SIZE (c)) != INTEGER_CST)
14019 OMP_CLAUSE_SIZE (c)
14020 = get_initialized_tmp_var (OMP_CLAUSE_SIZE (c), pre_p, NULL,
14021 false);
14022 if ((ctx->region_type & ORT_TARGET) != 0)
14023 omp_add_variable (ctx, OMP_CLAUSE_SIZE (c),
14024 GOVD_FIRSTPRIVATE | GOVD_SEEN);
14026 gimplify_omp_ctxp = ctx;
14027 /* Data clauses associated with reductions must be
14028 compatible with present_or_copy. Warn and adjust the clause
14029 if that is not the case. */
14030 if (ctx->region_type == ORT_ACC_PARALLEL
14031 || ctx->region_type == ORT_ACC_SERIAL)
14033 tree t = DECL_P (decl) ? decl : TREE_OPERAND (decl, 0);
14034 n = NULL;
14036 if (DECL_P (t))
14037 n = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
14039 if (n && (n->value & GOVD_REDUCTION))
14041 enum gomp_map_kind kind = OMP_CLAUSE_MAP_KIND (c);
14043 OMP_CLAUSE_MAP_IN_REDUCTION (c) = 1;
14044 if ((kind & GOMP_MAP_TOFROM) != GOMP_MAP_TOFROM
14045 && kind != GOMP_MAP_FORCE_PRESENT
14046 && kind != GOMP_MAP_POINTER)
14048 warning_at (OMP_CLAUSE_LOCATION (c), 0,
14049 "incompatible data clause with reduction "
14050 "on %qE; promoting to %<present_or_copy%>",
14051 DECL_NAME (t));
14052 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_TOFROM);
14056 if ((OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT
14057 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT_UNORD)
14058 && (code == OMP_TARGET_EXIT_DATA || code == OACC_EXIT_DATA))
14060 remove = true;
14061 break;
14063 /* If we have a DECL_VALUE_EXPR (e.g. this is a class member and/or
14064 a variable captured in a lambda closure), look through that now
14065 before the DECL_P check below. (A code other than COMPONENT_REF,
14066 i.e. INDIRECT_REF, will be a VLA/variable-length array
14067 section. A global var may be a variable in a common block. We
14068 don't want to do this here for either of those.) */
14069 if ((ctx->region_type & ORT_ACC) == 0
14070 && DECL_P (decl)
14071 && !is_global_var (decl)
14072 && DECL_HAS_VALUE_EXPR_P (decl)
14073 && TREE_CODE (DECL_VALUE_EXPR (decl)) == COMPONENT_REF)
14074 decl = OMP_CLAUSE_DECL (c) = DECL_VALUE_EXPR (decl);
14075 if (TREE_CODE (decl) == TARGET_EXPR)
14077 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
14078 is_gimple_lvalue, fb_lvalue) == GS_ERROR)
14079 remove = true;
14081 else if (!DECL_P (decl))
14083 if ((ctx->region_type & ORT_TARGET) != 0
14084 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
14086 if (INDIRECT_REF_P (decl)
14087 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
14088 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
14089 == REFERENCE_TYPE))
14090 decl = TREE_OPERAND (decl, 0);
14091 if (TREE_CODE (decl) == COMPONENT_REF)
14093 while (TREE_CODE (decl) == COMPONENT_REF)
14094 decl = TREE_OPERAND (decl, 0);
14095 if (DECL_P (decl))
14097 n = splay_tree_lookup (ctx->variables,
14098 (splay_tree_key) decl);
14099 if (!(n->value & GOVD_SEEN))
14100 remove = true;
14105 tree d = decl, *pd;
14106 if (TREE_CODE (d) == ARRAY_REF)
14108 while (TREE_CODE (d) == ARRAY_REF)
14109 d = TREE_OPERAND (d, 0);
14110 if (TREE_CODE (d) == COMPONENT_REF
14111 && TREE_CODE (TREE_TYPE (d)) == ARRAY_TYPE)
14112 decl = d;
14114 pd = &OMP_CLAUSE_DECL (c);
14115 if (d == decl
14116 && TREE_CODE (decl) == INDIRECT_REF
14117 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
14118 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
14119 == REFERENCE_TYPE)
14120 && (OMP_CLAUSE_MAP_KIND (c)
14121 != GOMP_MAP_POINTER_TO_ZERO_LENGTH_ARRAY_SECTION))
14123 pd = &TREE_OPERAND (decl, 0);
14124 decl = TREE_OPERAND (decl, 0);
14127 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
14128 switch (code)
14130 case OACC_ENTER_DATA:
14131 case OACC_EXIT_DATA:
14132 if (TREE_CODE (TREE_TYPE (OMP_CLAUSE_DECL (c)))
14133 == ARRAY_TYPE)
14134 remove = true;
14135 else if (code == OACC_ENTER_DATA)
14136 goto change_to_attach;
14137 /* Fallthrough. */
14138 case OMP_TARGET_EXIT_DATA:
14139 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_DETACH);
14140 break;
14141 case OACC_UPDATE:
14142 /* An "attach/detach" operation on an update directive
14143 should behave as a GOMP_MAP_ALWAYS_POINTER. Note that
14144 both GOMP_MAP_ATTACH_DETACH and GOMP_MAP_ALWAYS_POINTER
14145 kinds depend on the previous mapping (for non-TARGET
14146 regions). */
14147 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_ALWAYS_POINTER);
14148 break;
14149 default:
14150 change_to_attach:
14151 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_ATTACH);
14152 if ((ctx->region_type & ORT_TARGET) != 0)
14153 move_attach = true;
14155 else if ((ctx->region_type & ORT_TARGET) != 0
14156 && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH
14157 || (OMP_CLAUSE_MAP_KIND (c)
14158 == GOMP_MAP_ATTACH_ZERO_LENGTH_ARRAY_SECTION)))
14159 move_attach = true;
14161 /* If we have e.g. map(struct: *var), don't gimplify the
14162 argument since omp-low.cc wants to see the decl itself. */
14163 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT)
14164 break;
14166 /* We've already partly gimplified this in
14167 gimplify_scan_omp_clauses. Don't do any more. */
14168 if (code == OMP_TARGET && OMP_CLAUSE_MAP_IN_REDUCTION (c))
14169 break;
14171 gimplify_omp_ctxp = ctx->outer_context;
14172 if (gimplify_expr (pd, pre_p, NULL, is_gimple_lvalue,
14173 fb_lvalue) == GS_ERROR)
14174 remove = true;
14175 gimplify_omp_ctxp = ctx;
14176 break;
14179 if ((code == OMP_TARGET
14180 || code == OMP_TARGET_DATA
14181 || code == OMP_TARGET_ENTER_DATA
14182 || code == OMP_TARGET_EXIT_DATA)
14183 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
14185 bool firstprivatize = false;
14187 for (struct gimplify_omp_ctx *octx = ctx->outer_context; octx;
14188 octx = octx->outer_context)
14190 splay_tree_node n
14191 = splay_tree_lookup (octx->variables,
14192 (splay_tree_key) OMP_CLAUSE_DECL (c));
14193 /* If this is contained in an outer OpenMP region as a
14194 firstprivate value, remove the attach/detach. */
14195 if (n && (n->value & GOVD_FIRSTPRIVATE))
14197 firstprivatize = true;
14198 break;
14202 enum gomp_map_kind map_kind;
14203 if (firstprivatize)
14204 map_kind = GOMP_MAP_FIRSTPRIVATE_POINTER;
14205 else if (code == OMP_TARGET_EXIT_DATA)
14206 map_kind = GOMP_MAP_DETACH;
14207 else
14208 map_kind = GOMP_MAP_ATTACH;
14209 OMP_CLAUSE_SET_MAP_KIND (c, map_kind);
14211 else if ((ctx->region_type & ORT_ACC) != 0
14212 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
14214 enum gomp_map_kind map_kind = (code == OACC_EXIT_DATA
14215 ? GOMP_MAP_DETACH
14216 : GOMP_MAP_ATTACH);
14217 OMP_CLAUSE_SET_MAP_KIND (c, map_kind);
14220 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
14221 if ((ctx->region_type & ORT_TARGET) != 0
14222 && !(n->value & GOVD_SEEN)
14223 && GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c)) == 0
14224 && (!is_global_var (decl)
14225 || !lookup_attribute ("omp declare target link",
14226 DECL_ATTRIBUTES (decl))))
14228 remove = true;
14229 /* For struct element mapping, if struct is never referenced
14230 in target block and none of the mapping has always modifier,
14231 remove all the struct element mappings, which immediately
14232 follow the GOMP_MAP_STRUCT map clause. */
14233 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT
14234 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT_UNORD)
14236 HOST_WIDE_INT cnt = tree_to_shwi (OMP_CLAUSE_SIZE (c));
14237 while (cnt--)
14238 OMP_CLAUSE_CHAIN (c)
14239 = OMP_CLAUSE_CHAIN (OMP_CLAUSE_CHAIN (c));
14242 else if (DECL_SIZE (decl)
14243 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST
14244 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_POINTER
14245 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FIRSTPRIVATE_POINTER
14246 && (OMP_CLAUSE_MAP_KIND (c)
14247 != GOMP_MAP_FIRSTPRIVATE_REFERENCE))
14249 /* For GOMP_MAP_FORCE_DEVICEPTR, we'll never enter here, because
14250 for these, TREE_CODE (DECL_SIZE (decl)) will always be
14251 INTEGER_CST. */
14252 gcc_assert (OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FORCE_DEVICEPTR);
14254 tree decl2 = DECL_VALUE_EXPR (decl);
14255 gcc_assert (INDIRECT_REF_P (decl2));
14256 decl2 = TREE_OPERAND (decl2, 0);
14257 gcc_assert (DECL_P (decl2));
14258 tree mem = build_simple_mem_ref (decl2);
14259 OMP_CLAUSE_DECL (c) = mem;
14260 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
14261 if (ctx->outer_context)
14263 omp_notice_variable (ctx->outer_context, decl2, true);
14264 omp_notice_variable (ctx->outer_context,
14265 OMP_CLAUSE_SIZE (c), true);
14267 if (((ctx->region_type & ORT_TARGET) != 0
14268 || !ctx->target_firstprivatize_array_bases)
14269 && ((n->value & GOVD_SEEN) == 0
14270 || (n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE)) == 0))
14272 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (c),
14273 OMP_CLAUSE_MAP);
14274 OMP_CLAUSE_DECL (nc) = decl;
14275 OMP_CLAUSE_SIZE (nc) = size_zero_node;
14276 if (ctx->target_firstprivatize_array_bases)
14277 OMP_CLAUSE_SET_MAP_KIND (nc,
14278 GOMP_MAP_FIRSTPRIVATE_POINTER);
14279 else
14280 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
14281 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (c);
14282 OMP_CLAUSE_CHAIN (c) = nc;
14283 c = nc;
14286 else
14288 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
14289 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
14290 gcc_assert ((n->value & GOVD_SEEN) == 0
14291 || ((n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE))
14292 == 0));
14295 /* If we have a target region, we can push all the attaches to the
14296 end of the list (we may have standalone "attach" operations
14297 synthesized for GOMP_MAP_STRUCT nodes that must be processed after
14298 the attachment point AND the pointed-to block have been mapped).
14299 If we have something else, e.g. "enter data", we need to keep
14300 "attach" nodes together with the previous node they attach to so
14301 that separate "exit data" operations work properly (see
14302 libgomp/target.c). */
14303 if ((ctx->region_type & ORT_TARGET) != 0
14304 && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH
14305 || (OMP_CLAUSE_MAP_KIND (c)
14306 == GOMP_MAP_ATTACH_ZERO_LENGTH_ARRAY_SECTION)))
14307 move_attach = true;
14309 break;
14311 case OMP_CLAUSE_TO:
14312 case OMP_CLAUSE_FROM:
14313 case OMP_CLAUSE__CACHE_:
14314 decl = OMP_CLAUSE_DECL (c);
14315 if (!DECL_P (decl))
14316 break;
14317 if (DECL_SIZE (decl)
14318 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
14320 tree decl2 = DECL_VALUE_EXPR (decl);
14321 gcc_assert (INDIRECT_REF_P (decl2));
14322 decl2 = TREE_OPERAND (decl2, 0);
14323 gcc_assert (DECL_P (decl2));
14324 tree mem = build_simple_mem_ref (decl2);
14325 OMP_CLAUSE_DECL (c) = mem;
14326 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
14327 if (ctx->outer_context)
14329 omp_notice_variable (ctx->outer_context, decl2, true);
14330 omp_notice_variable (ctx->outer_context,
14331 OMP_CLAUSE_SIZE (c), true);
14334 else if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
14335 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
14336 break;
14338 case OMP_CLAUSE_REDUCTION:
14339 if (OMP_CLAUSE_REDUCTION_INSCAN (c))
14341 decl = OMP_CLAUSE_DECL (c);
14342 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
14343 if ((n->value & GOVD_REDUCTION_INSCAN) == 0)
14345 remove = true;
14346 error_at (OMP_CLAUSE_LOCATION (c),
14347 "%qD specified in %<inscan%> %<reduction%> clause "
14348 "but not in %<scan%> directive clause", decl);
14349 break;
14351 has_inscan_reductions = true;
14353 /* FALLTHRU */
14354 case OMP_CLAUSE_IN_REDUCTION:
14355 case OMP_CLAUSE_TASK_REDUCTION:
14356 decl = OMP_CLAUSE_DECL (c);
14357 /* OpenACC reductions need a present_or_copy data clause.
14358 Add one if necessary. Emit error when the reduction is private. */
14359 if (ctx->region_type == ORT_ACC_PARALLEL
14360 || ctx->region_type == ORT_ACC_SERIAL)
14362 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
14363 if (n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE))
14365 remove = true;
14366 error_at (OMP_CLAUSE_LOCATION (c), "invalid private "
14367 "reduction on %qE", DECL_NAME (decl));
14369 else if ((n->value & GOVD_MAP) == 0)
14371 tree next = OMP_CLAUSE_CHAIN (c);
14372 tree nc = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_MAP);
14373 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_TOFROM);
14374 OMP_CLAUSE_DECL (nc) = decl;
14375 OMP_CLAUSE_CHAIN (c) = nc;
14376 lang_hooks.decls.omp_finish_clause (nc, pre_p,
14377 (ctx->region_type
14378 & ORT_ACC) != 0);
14379 while (1)
14381 OMP_CLAUSE_MAP_IN_REDUCTION (nc) = 1;
14382 if (OMP_CLAUSE_CHAIN (nc) == NULL)
14383 break;
14384 nc = OMP_CLAUSE_CHAIN (nc);
14386 OMP_CLAUSE_CHAIN (nc) = next;
14387 n->value |= GOVD_MAP;
14390 if (DECL_P (decl)
14391 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
14392 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
14393 break;
14395 case OMP_CLAUSE_ALLOCATE:
14396 decl = OMP_CLAUSE_DECL (c);
14397 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
14398 if (n != NULL && !(n->value & GOVD_SEEN))
14400 if ((n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE | GOVD_LINEAR))
14401 != 0
14402 && (n->value & (GOVD_REDUCTION | GOVD_LASTPRIVATE)) == 0)
14403 remove = true;
14405 if (!remove
14406 && OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
14407 && TREE_CODE (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)) != INTEGER_CST
14408 && ((ctx->region_type & (ORT_PARALLEL | ORT_TARGET)) != 0
14409 || (ctx->region_type & ORT_TASKLOOP) == ORT_TASK
14410 || (ctx->region_type & ORT_HOST_TEAMS) == ORT_HOST_TEAMS))
14412 tree allocator = OMP_CLAUSE_ALLOCATE_ALLOCATOR (c);
14413 n = splay_tree_lookup (ctx->variables, (splay_tree_key) allocator);
14414 if (n == NULL)
14416 enum omp_clause_default_kind default_kind
14417 = ctx->default_kind;
14418 ctx->default_kind = OMP_CLAUSE_DEFAULT_FIRSTPRIVATE;
14419 omp_notice_variable (ctx, OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
14420 true);
14421 ctx->default_kind = default_kind;
14423 else
14424 omp_notice_variable (ctx, OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
14425 true);
14427 break;
14429 case OMP_CLAUSE_COPYIN:
14430 case OMP_CLAUSE_COPYPRIVATE:
14431 case OMP_CLAUSE_IF:
14432 case OMP_CLAUSE_SELF:
14433 case OMP_CLAUSE_NUM_THREADS:
14434 case OMP_CLAUSE_NUM_TEAMS:
14435 case OMP_CLAUSE_THREAD_LIMIT:
14436 case OMP_CLAUSE_DIST_SCHEDULE:
14437 case OMP_CLAUSE_DEVICE:
14438 case OMP_CLAUSE_SCHEDULE:
14439 case OMP_CLAUSE_NOWAIT:
14440 case OMP_CLAUSE_ORDERED:
14441 case OMP_CLAUSE_DEFAULT:
14442 case OMP_CLAUSE_UNTIED:
14443 case OMP_CLAUSE_COLLAPSE:
14444 case OMP_CLAUSE_FINAL:
14445 case OMP_CLAUSE_MERGEABLE:
14446 case OMP_CLAUSE_PROC_BIND:
14447 case OMP_CLAUSE_SAFELEN:
14448 case OMP_CLAUSE_SIMDLEN:
14449 case OMP_CLAUSE_DEPEND:
14450 case OMP_CLAUSE_DOACROSS:
14451 case OMP_CLAUSE_PRIORITY:
14452 case OMP_CLAUSE_GRAINSIZE:
14453 case OMP_CLAUSE_NUM_TASKS:
14454 case OMP_CLAUSE_NOGROUP:
14455 case OMP_CLAUSE_THREADS:
14456 case OMP_CLAUSE_SIMD:
14457 case OMP_CLAUSE_FILTER:
14458 case OMP_CLAUSE_HINT:
14459 case OMP_CLAUSE_DEFAULTMAP:
14460 case OMP_CLAUSE_ORDER:
14461 case OMP_CLAUSE_BIND:
14462 case OMP_CLAUSE_DETACH:
14463 case OMP_CLAUSE_USE_DEVICE_PTR:
14464 case OMP_CLAUSE_USE_DEVICE_ADDR:
14465 case OMP_CLAUSE_ASYNC:
14466 case OMP_CLAUSE_WAIT:
14467 case OMP_CLAUSE_INDEPENDENT:
14468 case OMP_CLAUSE_NUM_GANGS:
14469 case OMP_CLAUSE_NUM_WORKERS:
14470 case OMP_CLAUSE_VECTOR_LENGTH:
14471 case OMP_CLAUSE_GANG:
14472 case OMP_CLAUSE_WORKER:
14473 case OMP_CLAUSE_VECTOR:
14474 case OMP_CLAUSE_AUTO:
14475 case OMP_CLAUSE_SEQ:
14476 case OMP_CLAUSE_TILE:
14477 case OMP_CLAUSE_IF_PRESENT:
14478 case OMP_CLAUSE_FINALIZE:
14479 case OMP_CLAUSE_INCLUSIVE:
14480 case OMP_CLAUSE_EXCLUSIVE:
14481 break;
14483 case OMP_CLAUSE_NOHOST:
14484 default:
14485 gcc_unreachable ();
14488 if (remove)
14489 *list_p = OMP_CLAUSE_CHAIN (c);
14490 else if (move_attach)
14492 /* Remove attach node from here, separate out into its own list. */
14493 *attach_tail = c;
14494 *list_p = OMP_CLAUSE_CHAIN (c);
14495 OMP_CLAUSE_CHAIN (c) = NULL_TREE;
14496 attach_tail = &OMP_CLAUSE_CHAIN (c);
14498 else
14499 list_p = &OMP_CLAUSE_CHAIN (c);
14502 /* Splice attach nodes at the end of the list. */
14503 if (attach_list)
14505 *list_p = attach_list;
14506 list_p = attach_tail;
14509 /* Add in any implicit data sharing. */
14510 struct gimplify_adjust_omp_clauses_data data;
14511 if ((gimplify_omp_ctxp->region_type & ORT_ACC) == 0)
14513 /* OpenMP. Implicit clauses are added at the start of the clause list,
14514 but after any non-map clauses. */
14515 tree *implicit_add_list_p = orig_list_p;
14516 while (*implicit_add_list_p
14517 && OMP_CLAUSE_CODE (*implicit_add_list_p) != OMP_CLAUSE_MAP)
14518 implicit_add_list_p = &OMP_CLAUSE_CHAIN (*implicit_add_list_p);
14519 data.list_p = implicit_add_list_p;
14521 else
14522 /* OpenACC. */
14523 data.list_p = list_p;
14524 data.pre_p = pre_p;
14525 splay_tree_foreach (ctx->variables, gimplify_adjust_omp_clauses_1, &data);
14527 if (has_inscan_reductions)
14528 for (c = *orig_list_p; c; c = OMP_CLAUSE_CHAIN (c))
14529 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
14530 && !OMP_CLAUSE_LINEAR_NO_COPYIN (c))
14532 error_at (OMP_CLAUSE_LOCATION (c),
14533 "%<inscan%> %<reduction%> clause used together with "
14534 "%<linear%> clause for a variable other than loop "
14535 "iterator");
14536 break;
14539 gimplify_omp_ctxp = ctx->outer_context;
14540 delete_omp_context (ctx);
14543 /* Return 0 if CONSTRUCTS selectors don't match the OpenMP context,
14544 -1 if unknown yet (simd is involved, won't be known until vectorization)
14545 and 1 if they do. If SCORES is non-NULL, it should point to an array
14546 of at least 2*NCONSTRUCTS+2 ints, and will be filled with the positions
14547 of the CONSTRUCTS (position -1 if it will never match) followed by
14548 number of constructs in the OpenMP context construct trait. If the
14549 score depends on whether it will be in a declare simd clone or not,
14550 the function returns 2 and there will be two sets of the scores, the first
14551 one for the case that it is not in a declare simd clone, the other
14552 that it is in a declare simd clone. */
14555 omp_construct_selector_matches (enum tree_code *constructs, int nconstructs,
14556 int *scores)
14558 int matched = 0, cnt = 0;
14559 bool simd_seen = false;
14560 bool target_seen = false;
14561 int declare_simd_cnt = -1;
14562 auto_vec<enum tree_code, 16> codes;
14563 for (struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp; ctx;)
14565 if (((ctx->region_type & ORT_PARALLEL) && ctx->code == OMP_PARALLEL)
14566 || ((ctx->region_type & (ORT_TARGET | ORT_IMPLICIT_TARGET | ORT_ACC))
14567 == ORT_TARGET && ctx->code == OMP_TARGET)
14568 || ((ctx->region_type & ORT_TEAMS) && ctx->code == OMP_TEAMS)
14569 || (ctx->region_type == ORT_WORKSHARE && ctx->code == OMP_FOR)
14570 || (ctx->region_type == ORT_SIMD
14571 && ctx->code == OMP_SIMD
14572 && !omp_find_clause (ctx->clauses, OMP_CLAUSE_BIND)))
14574 ++cnt;
14575 if (scores)
14576 codes.safe_push (ctx->code);
14577 else if (matched < nconstructs && ctx->code == constructs[matched])
14579 if (ctx->code == OMP_SIMD)
14581 if (matched)
14582 return 0;
14583 simd_seen = true;
14585 ++matched;
14587 if (ctx->code == OMP_TARGET)
14589 if (scores == NULL)
14590 return matched < nconstructs ? 0 : simd_seen ? -1 : 1;
14591 target_seen = true;
14592 break;
14595 else if (ctx->region_type == ORT_WORKSHARE
14596 && ctx->code == OMP_LOOP
14597 && ctx->outer_context
14598 && ctx->outer_context->region_type == ORT_COMBINED_PARALLEL
14599 && ctx->outer_context->outer_context
14600 && ctx->outer_context->outer_context->code == OMP_LOOP
14601 && ctx->outer_context->outer_context->distribute)
14602 ctx = ctx->outer_context->outer_context;
14603 ctx = ctx->outer_context;
14605 if (!target_seen
14606 && lookup_attribute ("omp declare simd",
14607 DECL_ATTRIBUTES (current_function_decl)))
14609 /* Declare simd is a maybe case, it is supposed to be added only to the
14610 omp-simd-clone.cc added clones and not to the base function. */
14611 declare_simd_cnt = cnt++;
14612 if (scores)
14613 codes.safe_push (OMP_SIMD);
14614 else if (cnt == 0
14615 && constructs[0] == OMP_SIMD)
14617 gcc_assert (matched == 0);
14618 simd_seen = true;
14619 if (++matched == nconstructs)
14620 return -1;
14623 if (tree attr = lookup_attribute ("omp declare variant variant",
14624 DECL_ATTRIBUTES (current_function_decl)))
14626 tree selectors = TREE_VALUE (attr);
14627 int variant_nconstructs = list_length (selectors);
14628 enum tree_code *variant_constructs = NULL;
14629 if (!target_seen && variant_nconstructs)
14631 variant_constructs
14632 = (enum tree_code *) alloca (variant_nconstructs
14633 * sizeof (enum tree_code));
14634 omp_construct_traits_to_codes (selectors, variant_nconstructs,
14635 variant_constructs);
14637 for (int i = 0; i < variant_nconstructs; i++)
14639 ++cnt;
14640 if (scores)
14641 codes.safe_push (variant_constructs[i]);
14642 else if (matched < nconstructs
14643 && variant_constructs[i] == constructs[matched])
14645 if (variant_constructs[i] == OMP_SIMD)
14647 if (matched)
14648 return 0;
14649 simd_seen = true;
14651 ++matched;
14655 if (!target_seen
14656 && lookup_attribute ("omp declare target block",
14657 DECL_ATTRIBUTES (current_function_decl)))
14659 if (scores)
14660 codes.safe_push (OMP_TARGET);
14661 else if (matched < nconstructs && constructs[matched] == OMP_TARGET)
14662 ++matched;
14664 if (scores)
14666 for (int pass = 0; pass < (declare_simd_cnt == -1 ? 1 : 2); pass++)
14668 int j = codes.length () - 1;
14669 for (int i = nconstructs - 1; i >= 0; i--)
14671 while (j >= 0
14672 && (pass != 0 || declare_simd_cnt != j)
14673 && constructs[i] != codes[j])
14674 --j;
14675 if (pass == 0 && declare_simd_cnt != -1 && j > declare_simd_cnt)
14676 *scores++ = j - 1;
14677 else
14678 *scores++ = j;
14680 *scores++ = ((pass == 0 && declare_simd_cnt != -1)
14681 ? codes.length () - 1 : codes.length ());
14683 return declare_simd_cnt == -1 ? 1 : 2;
14685 if (matched == nconstructs)
14686 return simd_seen ? -1 : 1;
14687 return 0;
14690 /* Gimplify OACC_CACHE. */
14692 static void
14693 gimplify_oacc_cache (tree *expr_p, gimple_seq *pre_p)
14695 tree expr = *expr_p;
14697 gimplify_scan_omp_clauses (&OACC_CACHE_CLAUSES (expr), pre_p, ORT_ACC,
14698 OACC_CACHE);
14699 gimplify_adjust_omp_clauses (pre_p, NULL, &OACC_CACHE_CLAUSES (expr),
14700 OACC_CACHE);
14702 /* TODO: Do something sensible with this information. */
14704 *expr_p = NULL_TREE;
14707 /* Helper function of gimplify_oacc_declare. The helper's purpose is to,
14708 if required, translate 'kind' in CLAUSE into an 'entry' kind and 'exit'
14709 kind. The entry kind will replace the one in CLAUSE, while the exit
14710 kind will be used in a new omp_clause and returned to the caller. */
14712 static tree
14713 gimplify_oacc_declare_1 (tree clause)
14715 HOST_WIDE_INT kind, new_op;
14716 bool ret = false;
14717 tree c = NULL;
14719 kind = OMP_CLAUSE_MAP_KIND (clause);
14721 switch (kind)
14723 case GOMP_MAP_ALLOC:
14724 new_op = GOMP_MAP_RELEASE;
14725 ret = true;
14726 break;
14728 case GOMP_MAP_FROM:
14729 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_FORCE_ALLOC);
14730 new_op = GOMP_MAP_FROM;
14731 ret = true;
14732 break;
14734 case GOMP_MAP_TOFROM:
14735 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_TO);
14736 new_op = GOMP_MAP_FROM;
14737 ret = true;
14738 break;
14740 case GOMP_MAP_DEVICE_RESIDENT:
14741 case GOMP_MAP_FORCE_DEVICEPTR:
14742 case GOMP_MAP_FORCE_PRESENT:
14743 case GOMP_MAP_LINK:
14744 case GOMP_MAP_POINTER:
14745 case GOMP_MAP_TO:
14746 break;
14748 default:
14749 gcc_unreachable ();
14750 break;
14753 if (ret)
14755 c = build_omp_clause (OMP_CLAUSE_LOCATION (clause), OMP_CLAUSE_MAP);
14756 OMP_CLAUSE_SET_MAP_KIND (c, new_op);
14757 OMP_CLAUSE_DECL (c) = OMP_CLAUSE_DECL (clause);
14760 return c;
14763 /* Gimplify OACC_DECLARE. */
14765 static void
14766 gimplify_oacc_declare (tree *expr_p, gimple_seq *pre_p)
14768 tree expr = *expr_p;
14769 gomp_target *stmt;
14770 tree clauses, t, decl;
14772 clauses = OACC_DECLARE_CLAUSES (expr);
14774 gimplify_scan_omp_clauses (&clauses, pre_p, ORT_TARGET_DATA, OACC_DECLARE);
14775 gimplify_adjust_omp_clauses (pre_p, NULL, &clauses, OACC_DECLARE);
14777 for (t = clauses; t; t = OMP_CLAUSE_CHAIN (t))
14779 decl = OMP_CLAUSE_DECL (t);
14781 if (TREE_CODE (decl) == MEM_REF)
14782 decl = TREE_OPERAND (decl, 0);
14784 if (VAR_P (decl) && !is_oacc_declared (decl))
14786 tree attr = get_identifier ("oacc declare target");
14787 DECL_ATTRIBUTES (decl) = tree_cons (attr, NULL_TREE,
14788 DECL_ATTRIBUTES (decl));
14791 if (VAR_P (decl)
14792 && !is_global_var (decl)
14793 && DECL_CONTEXT (decl) == current_function_decl)
14795 tree c = gimplify_oacc_declare_1 (t);
14796 if (c)
14798 if (oacc_declare_returns == NULL)
14799 oacc_declare_returns = new hash_map<tree, tree>;
14801 oacc_declare_returns->put (decl, c);
14805 if (gimplify_omp_ctxp)
14806 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_SEEN);
14809 stmt = gimple_build_omp_target (NULL, GF_OMP_TARGET_KIND_OACC_DECLARE,
14810 clauses);
14812 gimplify_seq_add_stmt (pre_p, stmt);
14814 *expr_p = NULL_TREE;
14817 /* Gimplify the contents of an OMP_PARALLEL statement. This involves
14818 gimplification of the body, as well as scanning the body for used
14819 variables. We need to do this scan now, because variable-sized
14820 decls will be decomposed during gimplification. */
14822 static void
14823 gimplify_omp_parallel (tree *expr_p, gimple_seq *pre_p)
14825 tree expr = *expr_p;
14826 gimple *g;
14827 gimple_seq body = NULL;
14829 gimplify_scan_omp_clauses (&OMP_PARALLEL_CLAUSES (expr), pre_p,
14830 OMP_PARALLEL_COMBINED (expr)
14831 ? ORT_COMBINED_PARALLEL
14832 : ORT_PARALLEL, OMP_PARALLEL);
14834 push_gimplify_context ();
14836 g = gimplify_and_return_first (OMP_PARALLEL_BODY (expr), &body);
14837 if (gimple_code (g) == GIMPLE_BIND)
14838 pop_gimplify_context (g);
14839 else
14840 pop_gimplify_context (NULL);
14842 gimplify_adjust_omp_clauses (pre_p, body, &OMP_PARALLEL_CLAUSES (expr),
14843 OMP_PARALLEL);
14845 g = gimple_build_omp_parallel (body,
14846 OMP_PARALLEL_CLAUSES (expr),
14847 NULL_TREE, NULL_TREE);
14848 if (OMP_PARALLEL_COMBINED (expr))
14849 gimple_omp_set_subcode (g, GF_OMP_PARALLEL_COMBINED);
14850 gimplify_seq_add_stmt (pre_p, g);
14851 *expr_p = NULL_TREE;
14854 /* Gimplify the contents of an OMP_TASK statement. This involves
14855 gimplification of the body, as well as scanning the body for used
14856 variables. We need to do this scan now, because variable-sized
14857 decls will be decomposed during gimplification. */
14859 static void
14860 gimplify_omp_task (tree *expr_p, gimple_seq *pre_p)
14862 tree expr = *expr_p;
14863 gimple *g;
14864 gimple_seq body = NULL;
14865 bool nowait = false;
14866 bool has_depend = false;
14868 if (OMP_TASK_BODY (expr) == NULL_TREE)
14870 for (tree c = OMP_TASK_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
14871 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND)
14873 has_depend = true;
14874 if (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_MUTEXINOUTSET)
14876 error_at (OMP_CLAUSE_LOCATION (c),
14877 "%<mutexinoutset%> kind in %<depend%> clause on a "
14878 "%<taskwait%> construct");
14879 break;
14882 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_NOWAIT)
14883 nowait = true;
14884 if (nowait && !has_depend)
14886 error_at (EXPR_LOCATION (expr),
14887 "%<taskwait%> construct with %<nowait%> clause but no "
14888 "%<depend%> clauses");
14889 *expr_p = NULL_TREE;
14890 return;
14894 gimplify_scan_omp_clauses (&OMP_TASK_CLAUSES (expr), pre_p,
14895 omp_find_clause (OMP_TASK_CLAUSES (expr),
14896 OMP_CLAUSE_UNTIED)
14897 ? ORT_UNTIED_TASK : ORT_TASK, OMP_TASK);
14899 if (OMP_TASK_BODY (expr))
14901 push_gimplify_context ();
14903 g = gimplify_and_return_first (OMP_TASK_BODY (expr), &body);
14904 if (gimple_code (g) == GIMPLE_BIND)
14905 pop_gimplify_context (g);
14906 else
14907 pop_gimplify_context (NULL);
14910 gimplify_adjust_omp_clauses (pre_p, body, &OMP_TASK_CLAUSES (expr),
14911 OMP_TASK);
14913 g = gimple_build_omp_task (body,
14914 OMP_TASK_CLAUSES (expr),
14915 NULL_TREE, NULL_TREE,
14916 NULL_TREE, NULL_TREE, NULL_TREE);
14917 if (OMP_TASK_BODY (expr) == NULL_TREE)
14918 gimple_omp_task_set_taskwait_p (g, true);
14919 gimplify_seq_add_stmt (pre_p, g);
14920 *expr_p = NULL_TREE;
14923 /* Helper function for gimplify_omp_for. If *TP is not a gimple constant,
14924 force it into a temporary initialized in PRE_P and add firstprivate clause
14925 to ORIG_FOR_STMT. */
14927 static void
14928 gimplify_omp_taskloop_expr (tree type, tree *tp, gimple_seq *pre_p,
14929 tree orig_for_stmt)
14931 if (*tp == NULL || is_gimple_constant (*tp))
14932 return;
14934 *tp = get_initialized_tmp_var (*tp, pre_p, NULL, false);
14935 /* Reference to pointer conversion is considered useless,
14936 but is significant for firstprivate clause. Force it
14937 here. */
14938 if (type
14939 && TREE_CODE (type) == POINTER_TYPE
14940 && TREE_CODE (TREE_TYPE (*tp)) == REFERENCE_TYPE)
14942 tree v = create_tmp_var (TYPE_MAIN_VARIANT (type));
14943 tree m = build2 (INIT_EXPR, TREE_TYPE (v), v, *tp);
14944 gimplify_and_add (m, pre_p);
14945 *tp = v;
14948 tree c = build_omp_clause (input_location, OMP_CLAUSE_FIRSTPRIVATE);
14949 OMP_CLAUSE_DECL (c) = *tp;
14950 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (orig_for_stmt);
14951 OMP_FOR_CLAUSES (orig_for_stmt) = c;
14954 /* Helper function of gimplify_omp_for, find OMP_ORDERED with
14955 null OMP_ORDERED_BODY inside of OMP_FOR's body. */
14957 static tree
14958 find_standalone_omp_ordered (tree *tp, int *walk_subtrees, void *)
14960 switch (TREE_CODE (*tp))
14962 case OMP_ORDERED:
14963 if (OMP_ORDERED_BODY (*tp) == NULL_TREE)
14964 return *tp;
14965 break;
14966 case OMP_SIMD:
14967 case OMP_PARALLEL:
14968 case OMP_TARGET:
14969 *walk_subtrees = 0;
14970 break;
14971 default:
14972 break;
14974 return NULL_TREE;
14977 /* Gimplify the gross structure of an OMP_FOR statement. */
14979 static enum gimplify_status
14980 gimplify_omp_for (tree *expr_p, gimple_seq *pre_p)
14982 tree for_stmt, orig_for_stmt, inner_for_stmt = NULL_TREE, decl, var, t;
14983 enum gimplify_status ret = GS_ALL_DONE;
14984 enum gimplify_status tret;
14985 gomp_for *gfor;
14986 gimple_seq for_body, for_pre_body;
14987 int i;
14988 bitmap has_decl_expr = NULL;
14989 enum omp_region_type ort = ORT_WORKSHARE;
14990 bool openacc = TREE_CODE (*expr_p) == OACC_LOOP;
14992 orig_for_stmt = for_stmt = *expr_p;
14994 bool loop_p = (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_BIND)
14995 != NULL_TREE);
14996 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
14998 tree *data[4] = { NULL, NULL, NULL, NULL };
14999 gcc_assert (TREE_CODE (for_stmt) != OACC_LOOP);
15000 inner_for_stmt = walk_tree (&OMP_FOR_BODY (for_stmt),
15001 find_combined_omp_for, data, NULL);
15002 if (inner_for_stmt == NULL_TREE)
15004 gcc_assert (seen_error ());
15005 *expr_p = NULL_TREE;
15006 return GS_ERROR;
15008 if (data[2] && OMP_FOR_PRE_BODY (*data[2]))
15010 append_to_statement_list_force (OMP_FOR_PRE_BODY (*data[2]),
15011 &OMP_FOR_PRE_BODY (for_stmt));
15012 OMP_FOR_PRE_BODY (*data[2]) = NULL_TREE;
15014 if (OMP_FOR_PRE_BODY (inner_for_stmt))
15016 append_to_statement_list_force (OMP_FOR_PRE_BODY (inner_for_stmt),
15017 &OMP_FOR_PRE_BODY (for_stmt));
15018 OMP_FOR_PRE_BODY (inner_for_stmt) = NULL_TREE;
15021 if (data[0])
15023 /* We have some statements or variable declarations in between
15024 the composite construct directives. Move them around the
15025 inner_for_stmt. */
15026 data[0] = expr_p;
15027 for (i = 0; i < 3; i++)
15028 if (data[i])
15030 tree t = *data[i];
15031 if (i < 2 && data[i + 1] == &OMP_BODY (t))
15032 data[i + 1] = data[i];
15033 *data[i] = OMP_BODY (t);
15034 tree body = build3 (BIND_EXPR, void_type_node, NULL_TREE,
15035 NULL_TREE, make_node (BLOCK));
15036 OMP_BODY (t) = body;
15037 append_to_statement_list_force (inner_for_stmt,
15038 &BIND_EXPR_BODY (body));
15039 *data[3] = t;
15040 data[3] = tsi_stmt_ptr (tsi_start (BIND_EXPR_BODY (body)));
15041 gcc_assert (*data[3] == inner_for_stmt);
15043 return GS_OK;
15046 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (inner_for_stmt)); i++)
15047 if (!loop_p
15048 && OMP_FOR_ORIG_DECLS (inner_for_stmt)
15049 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
15050 i)) == TREE_LIST
15051 && TREE_PURPOSE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
15052 i)))
15054 tree orig = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt), i);
15055 /* Class iterators aren't allowed on OMP_SIMD, so the only
15056 case we need to solve is distribute parallel for. They are
15057 allowed on the loop construct, but that is already handled
15058 in gimplify_omp_loop. */
15059 gcc_assert (TREE_CODE (inner_for_stmt) == OMP_FOR
15060 && TREE_CODE (for_stmt) == OMP_DISTRIBUTE
15061 && data[1]);
15062 tree orig_decl = TREE_PURPOSE (orig);
15063 tree last = TREE_VALUE (orig);
15064 tree *pc;
15065 for (pc = &OMP_FOR_CLAUSES (inner_for_stmt);
15066 *pc; pc = &OMP_CLAUSE_CHAIN (*pc))
15067 if ((OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_PRIVATE
15068 || OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_LASTPRIVATE)
15069 && OMP_CLAUSE_DECL (*pc) == orig_decl)
15070 break;
15071 if (*pc == NULL_TREE)
15073 tree *spc;
15074 for (spc = &OMP_PARALLEL_CLAUSES (*data[1]);
15075 *spc; spc = &OMP_CLAUSE_CHAIN (*spc))
15076 if (OMP_CLAUSE_CODE (*spc) == OMP_CLAUSE_PRIVATE
15077 && OMP_CLAUSE_DECL (*spc) == orig_decl)
15078 break;
15079 if (*spc)
15081 tree c = *spc;
15082 *spc = OMP_CLAUSE_CHAIN (c);
15083 OMP_CLAUSE_CHAIN (c) = NULL_TREE;
15084 *pc = c;
15087 if (*pc == NULL_TREE)
15089 else if (OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_PRIVATE)
15091 /* private clause will appear only on inner_for_stmt.
15092 Change it into firstprivate, and add private clause
15093 on for_stmt. */
15094 tree c = copy_node (*pc);
15095 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
15096 OMP_FOR_CLAUSES (for_stmt) = c;
15097 OMP_CLAUSE_CODE (*pc) = OMP_CLAUSE_FIRSTPRIVATE;
15098 lang_hooks.decls.omp_finish_clause (*pc, pre_p, openacc);
15100 else
15102 /* lastprivate clause will appear on both inner_for_stmt
15103 and for_stmt. Add firstprivate clause to
15104 inner_for_stmt. */
15105 tree c = build_omp_clause (OMP_CLAUSE_LOCATION (*pc),
15106 OMP_CLAUSE_FIRSTPRIVATE);
15107 OMP_CLAUSE_DECL (c) = OMP_CLAUSE_DECL (*pc);
15108 OMP_CLAUSE_CHAIN (c) = *pc;
15109 *pc = c;
15110 lang_hooks.decls.omp_finish_clause (*pc, pre_p, openacc);
15112 tree c = build_omp_clause (UNKNOWN_LOCATION,
15113 OMP_CLAUSE_FIRSTPRIVATE);
15114 OMP_CLAUSE_DECL (c) = last;
15115 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
15116 OMP_PARALLEL_CLAUSES (*data[1]) = c;
15117 c = build_omp_clause (UNKNOWN_LOCATION,
15118 *pc ? OMP_CLAUSE_SHARED
15119 : OMP_CLAUSE_FIRSTPRIVATE);
15120 OMP_CLAUSE_DECL (c) = orig_decl;
15121 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
15122 OMP_PARALLEL_CLAUSES (*data[1]) = c;
15124 /* Similarly, take care of C++ range for temporaries, those should
15125 be firstprivate on OMP_PARALLEL if any. */
15126 if (data[1])
15127 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (inner_for_stmt)); i++)
15128 if (OMP_FOR_ORIG_DECLS (inner_for_stmt)
15129 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
15130 i)) == TREE_LIST
15131 && TREE_CHAIN (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
15132 i)))
15134 tree orig
15135 = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt), i);
15136 tree v = TREE_CHAIN (orig);
15137 tree c = build_omp_clause (UNKNOWN_LOCATION,
15138 OMP_CLAUSE_FIRSTPRIVATE);
15139 /* First add firstprivate clause for the __for_end artificial
15140 decl. */
15141 OMP_CLAUSE_DECL (c) = TREE_VEC_ELT (v, 1);
15142 if (TREE_CODE (TREE_TYPE (OMP_CLAUSE_DECL (c)))
15143 == REFERENCE_TYPE)
15144 OMP_CLAUSE_FIRSTPRIVATE_NO_REFERENCE (c) = 1;
15145 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
15146 OMP_PARALLEL_CLAUSES (*data[1]) = c;
15147 if (TREE_VEC_ELT (v, 0))
15149 /* And now the same for __for_range artificial decl if it
15150 exists. */
15151 c = build_omp_clause (UNKNOWN_LOCATION,
15152 OMP_CLAUSE_FIRSTPRIVATE);
15153 OMP_CLAUSE_DECL (c) = TREE_VEC_ELT (v, 0);
15154 if (TREE_CODE (TREE_TYPE (OMP_CLAUSE_DECL (c)))
15155 == REFERENCE_TYPE)
15156 OMP_CLAUSE_FIRSTPRIVATE_NO_REFERENCE (c) = 1;
15157 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
15158 OMP_PARALLEL_CLAUSES (*data[1]) = c;
15163 switch (TREE_CODE (for_stmt))
15165 case OMP_FOR:
15166 if (OMP_FOR_NON_RECTANGULAR (inner_for_stmt ? inner_for_stmt : for_stmt))
15168 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
15169 OMP_CLAUSE_SCHEDULE))
15170 error_at (EXPR_LOCATION (for_stmt),
15171 "%qs clause may not appear on non-rectangular %qs",
15172 "schedule", lang_GNU_Fortran () ? "do" : "for");
15173 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ORDERED))
15174 error_at (EXPR_LOCATION (for_stmt),
15175 "%qs clause may not appear on non-rectangular %qs",
15176 "ordered", lang_GNU_Fortran () ? "do" : "for");
15178 break;
15179 case OMP_DISTRIBUTE:
15180 if (OMP_FOR_NON_RECTANGULAR (inner_for_stmt ? inner_for_stmt : for_stmt)
15181 && omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
15182 OMP_CLAUSE_DIST_SCHEDULE))
15183 error_at (EXPR_LOCATION (for_stmt),
15184 "%qs clause may not appear on non-rectangular %qs",
15185 "dist_schedule", "distribute");
15186 break;
15187 case OACC_LOOP:
15188 ort = ORT_ACC;
15189 break;
15190 case OMP_TASKLOOP:
15191 if (OMP_FOR_NON_RECTANGULAR (inner_for_stmt ? inner_for_stmt : for_stmt))
15193 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
15194 OMP_CLAUSE_GRAINSIZE))
15195 error_at (EXPR_LOCATION (for_stmt),
15196 "%qs clause may not appear on non-rectangular %qs",
15197 "grainsize", "taskloop");
15198 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
15199 OMP_CLAUSE_NUM_TASKS))
15200 error_at (EXPR_LOCATION (for_stmt),
15201 "%qs clause may not appear on non-rectangular %qs",
15202 "num_tasks", "taskloop");
15204 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_UNTIED))
15205 ort = ORT_UNTIED_TASKLOOP;
15206 else
15207 ort = ORT_TASKLOOP;
15208 break;
15209 case OMP_SIMD:
15210 ort = ORT_SIMD;
15211 break;
15212 default:
15213 gcc_unreachable ();
15216 /* Set OMP_CLAUSE_LINEAR_NO_COPYIN flag on explicit linear
15217 clause for the IV. */
15218 if (ort == ORT_SIMD && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
15220 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), 0);
15221 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
15222 decl = TREE_OPERAND (t, 0);
15223 for (tree c = OMP_FOR_CLAUSES (for_stmt); c; c = OMP_CLAUSE_CHAIN (c))
15224 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
15225 && OMP_CLAUSE_DECL (c) == decl)
15227 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
15228 break;
15232 if (TREE_CODE (for_stmt) != OMP_TASKLOOP)
15233 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (for_stmt), pre_p, ort,
15234 loop_p && TREE_CODE (for_stmt) != OMP_SIMD
15235 ? OMP_LOOP : TREE_CODE (for_stmt));
15237 if (TREE_CODE (for_stmt) == OMP_DISTRIBUTE)
15238 gimplify_omp_ctxp->distribute = true;
15240 /* Handle OMP_FOR_INIT. */
15241 for_pre_body = NULL;
15242 if ((ort == ORT_SIMD
15243 || (inner_for_stmt && TREE_CODE (inner_for_stmt) == OMP_SIMD))
15244 && OMP_FOR_PRE_BODY (for_stmt))
15246 has_decl_expr = BITMAP_ALLOC (NULL);
15247 if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == DECL_EXPR
15248 && VAR_P (DECL_EXPR_DECL (OMP_FOR_PRE_BODY (for_stmt))))
15250 t = OMP_FOR_PRE_BODY (for_stmt);
15251 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
15253 else if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == STATEMENT_LIST)
15255 tree_stmt_iterator si;
15256 for (si = tsi_start (OMP_FOR_PRE_BODY (for_stmt)); !tsi_end_p (si);
15257 tsi_next (&si))
15259 t = tsi_stmt (si);
15260 if (TREE_CODE (t) == DECL_EXPR
15261 && VAR_P (DECL_EXPR_DECL (t)))
15262 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
15266 if (OMP_FOR_PRE_BODY (for_stmt))
15268 if (TREE_CODE (for_stmt) != OMP_TASKLOOP || gimplify_omp_ctxp)
15269 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
15270 else
15272 struct gimplify_omp_ctx ctx;
15273 memset (&ctx, 0, sizeof (ctx));
15274 ctx.region_type = ORT_NONE;
15275 gimplify_omp_ctxp = &ctx;
15276 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
15277 gimplify_omp_ctxp = NULL;
15280 OMP_FOR_PRE_BODY (for_stmt) = NULL_TREE;
15282 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
15283 for_stmt = inner_for_stmt;
15285 /* For taskloop, need to gimplify the start, end and step before the
15286 taskloop, outside of the taskloop omp context. */
15287 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
15289 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
15291 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
15292 gimple_seq *for_pre_p = (gimple_seq_empty_p (for_pre_body)
15293 ? pre_p : &for_pre_body);
15294 tree type = TREE_TYPE (TREE_OPERAND (t, 0));
15295 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
15297 tree v = TREE_OPERAND (t, 1);
15298 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 1),
15299 for_pre_p, orig_for_stmt);
15300 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 2),
15301 for_pre_p, orig_for_stmt);
15303 else
15304 gimplify_omp_taskloop_expr (type, &TREE_OPERAND (t, 1), for_pre_p,
15305 orig_for_stmt);
15307 /* Handle OMP_FOR_COND. */
15308 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
15309 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
15311 tree v = TREE_OPERAND (t, 1);
15312 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 1),
15313 for_pre_p, orig_for_stmt);
15314 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 2),
15315 for_pre_p, orig_for_stmt);
15317 else
15318 gimplify_omp_taskloop_expr (type, &TREE_OPERAND (t, 1), for_pre_p,
15319 orig_for_stmt);
15321 /* Handle OMP_FOR_INCR. */
15322 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
15323 if (TREE_CODE (t) == MODIFY_EXPR)
15325 decl = TREE_OPERAND (t, 0);
15326 t = TREE_OPERAND (t, 1);
15327 tree *tp = &TREE_OPERAND (t, 1);
15328 if (TREE_CODE (t) == PLUS_EXPR && *tp == decl)
15329 tp = &TREE_OPERAND (t, 0);
15331 gimplify_omp_taskloop_expr (NULL_TREE, tp, for_pre_p,
15332 orig_for_stmt);
15336 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (orig_for_stmt), pre_p, ort,
15337 OMP_TASKLOOP);
15340 if (orig_for_stmt != for_stmt)
15341 gimplify_omp_ctxp->combined_loop = true;
15343 for_body = NULL;
15344 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
15345 == TREE_VEC_LENGTH (OMP_FOR_COND (for_stmt)));
15346 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
15347 == TREE_VEC_LENGTH (OMP_FOR_INCR (for_stmt)));
15349 tree c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ORDERED);
15350 bool is_doacross = false;
15351 if (c && walk_tree_without_duplicates (&OMP_FOR_BODY (for_stmt),
15352 find_standalone_omp_ordered, NULL))
15354 OMP_CLAUSE_ORDERED_DOACROSS (c) = 1;
15355 is_doacross = true;
15356 int len = TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt));
15357 gimplify_omp_ctxp->loop_iter_var.create (len * 2);
15358 for (tree *pc = &OMP_FOR_CLAUSES (for_stmt); *pc; )
15359 if (OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_LINEAR)
15361 error_at (OMP_CLAUSE_LOCATION (*pc),
15362 "%<linear%> clause may not be specified together "
15363 "with %<ordered%> clause if stand-alone %<ordered%> "
15364 "construct is nested in it");
15365 *pc = OMP_CLAUSE_CHAIN (*pc);
15367 else
15368 pc = &OMP_CLAUSE_CHAIN (*pc);
15370 int collapse = 1, tile = 0;
15371 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_COLLAPSE);
15372 if (c)
15373 collapse = tree_to_shwi (OMP_CLAUSE_COLLAPSE_EXPR (c));
15374 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_TILE);
15375 if (c)
15376 tile = list_length (OMP_CLAUSE_TILE_LIST (c));
15377 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ALLOCATE);
15378 hash_set<tree> *allocate_uids = NULL;
15379 if (c)
15381 allocate_uids = new hash_set<tree>;
15382 for (; c; c = OMP_CLAUSE_CHAIN (c))
15383 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_ALLOCATE)
15384 allocate_uids->add (OMP_CLAUSE_DECL (c));
15386 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
15388 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
15389 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
15390 decl = TREE_OPERAND (t, 0);
15391 gcc_assert (DECL_P (decl));
15392 gcc_assert (INTEGRAL_TYPE_P (TREE_TYPE (decl))
15393 || POINTER_TYPE_P (TREE_TYPE (decl)));
15394 if (is_doacross)
15396 if (TREE_CODE (for_stmt) == OMP_FOR && OMP_FOR_ORIG_DECLS (for_stmt))
15398 tree orig_decl = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
15399 if (TREE_CODE (orig_decl) == TREE_LIST)
15401 orig_decl = TREE_PURPOSE (orig_decl);
15402 if (!orig_decl)
15403 orig_decl = decl;
15405 gimplify_omp_ctxp->loop_iter_var.quick_push (orig_decl);
15407 else
15408 gimplify_omp_ctxp->loop_iter_var.quick_push (decl);
15409 gimplify_omp_ctxp->loop_iter_var.quick_push (decl);
15412 if (for_stmt == orig_for_stmt)
15414 tree orig_decl = decl;
15415 if (OMP_FOR_ORIG_DECLS (for_stmt))
15417 tree orig_decl = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
15418 if (TREE_CODE (orig_decl) == TREE_LIST)
15420 orig_decl = TREE_PURPOSE (orig_decl);
15421 if (!orig_decl)
15422 orig_decl = decl;
15425 if (is_global_var (orig_decl) && DECL_THREAD_LOCAL_P (orig_decl))
15426 error_at (EXPR_LOCATION (for_stmt),
15427 "threadprivate iteration variable %qD", orig_decl);
15430 /* Make sure the iteration variable is private. */
15431 tree c = NULL_TREE;
15432 tree c2 = NULL_TREE;
15433 if (orig_for_stmt != for_stmt)
15435 /* Preserve this information until we gimplify the inner simd. */
15436 if (has_decl_expr
15437 && bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
15438 TREE_PRIVATE (t) = 1;
15440 else if (ort == ORT_SIMD)
15442 splay_tree_node n = splay_tree_lookup (gimplify_omp_ctxp->variables,
15443 (splay_tree_key) decl);
15444 omp_is_private (gimplify_omp_ctxp, decl,
15445 1 + (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
15446 != 1));
15447 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
15449 omp_notice_variable (gimplify_omp_ctxp, decl, true);
15450 if (n->value & GOVD_LASTPRIVATE_CONDITIONAL)
15451 for (tree c3 = omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
15452 OMP_CLAUSE_LASTPRIVATE);
15453 c3; c3 = omp_find_clause (OMP_CLAUSE_CHAIN (c3),
15454 OMP_CLAUSE_LASTPRIVATE))
15455 if (OMP_CLAUSE_DECL (c3) == decl)
15457 warning_at (OMP_CLAUSE_LOCATION (c3), OPT_Wopenmp,
15458 "conditional %<lastprivate%> on loop "
15459 "iterator %qD ignored", decl);
15460 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c3) = 0;
15461 n->value &= ~GOVD_LASTPRIVATE_CONDITIONAL;
15464 else if (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1 && !loop_p)
15466 c = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
15467 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
15468 unsigned int flags = GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN;
15469 if ((has_decl_expr
15470 && bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
15471 || TREE_PRIVATE (t))
15473 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
15474 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
15476 struct gimplify_omp_ctx *outer
15477 = gimplify_omp_ctxp->outer_context;
15478 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
15480 if (outer->region_type == ORT_WORKSHARE
15481 && outer->combined_loop)
15483 n = splay_tree_lookup (outer->variables,
15484 (splay_tree_key)decl);
15485 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
15487 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
15488 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
15490 else
15492 struct gimplify_omp_ctx *octx = outer->outer_context;
15493 if (octx
15494 && octx->region_type == ORT_COMBINED_PARALLEL
15495 && octx->outer_context
15496 && (octx->outer_context->region_type
15497 == ORT_WORKSHARE)
15498 && octx->outer_context->combined_loop)
15500 octx = octx->outer_context;
15501 n = splay_tree_lookup (octx->variables,
15502 (splay_tree_key)decl);
15503 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
15505 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
15506 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
15513 OMP_CLAUSE_DECL (c) = decl;
15514 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
15515 OMP_FOR_CLAUSES (for_stmt) = c;
15516 omp_add_variable (gimplify_omp_ctxp, decl, flags);
15517 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
15518 omp_lastprivate_for_combined_outer_constructs (outer, decl,
15519 true);
15521 else
15523 bool lastprivate
15524 = (!has_decl_expr
15525 || !bitmap_bit_p (has_decl_expr, DECL_UID (decl)));
15526 if (TREE_PRIVATE (t))
15527 lastprivate = false;
15528 if (loop_p && OMP_FOR_ORIG_DECLS (for_stmt))
15530 tree elt = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
15531 if (TREE_CODE (elt) == TREE_LIST && TREE_PURPOSE (elt))
15532 lastprivate = false;
15535 struct gimplify_omp_ctx *outer
15536 = gimplify_omp_ctxp->outer_context;
15537 if (outer && lastprivate)
15538 omp_lastprivate_for_combined_outer_constructs (outer, decl,
15539 true);
15541 c = build_omp_clause (input_location,
15542 lastprivate ? OMP_CLAUSE_LASTPRIVATE
15543 : OMP_CLAUSE_PRIVATE);
15544 OMP_CLAUSE_DECL (c) = decl;
15545 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
15546 OMP_FOR_CLAUSES (for_stmt) = c;
15547 omp_add_variable (gimplify_omp_ctxp, decl,
15548 (lastprivate ? GOVD_LASTPRIVATE : GOVD_PRIVATE)
15549 | GOVD_EXPLICIT | GOVD_SEEN);
15550 c = NULL_TREE;
15553 else if (omp_is_private (gimplify_omp_ctxp, decl, 0))
15555 omp_notice_variable (gimplify_omp_ctxp, decl, true);
15556 splay_tree_node n = splay_tree_lookup (gimplify_omp_ctxp->variables,
15557 (splay_tree_key) decl);
15558 if (n && (n->value & GOVD_LASTPRIVATE_CONDITIONAL))
15559 for (tree c3 = omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
15560 OMP_CLAUSE_LASTPRIVATE);
15561 c3; c3 = omp_find_clause (OMP_CLAUSE_CHAIN (c3),
15562 OMP_CLAUSE_LASTPRIVATE))
15563 if (OMP_CLAUSE_DECL (c3) == decl)
15565 warning_at (OMP_CLAUSE_LOCATION (c3), OPT_Wopenmp,
15566 "conditional %<lastprivate%> on loop "
15567 "iterator %qD ignored", decl);
15568 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c3) = 0;
15569 n->value &= ~GOVD_LASTPRIVATE_CONDITIONAL;
15572 else
15573 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_PRIVATE | GOVD_SEEN);
15575 /* If DECL is not a gimple register, create a temporary variable to act
15576 as an iteration counter. This is valid, since DECL cannot be
15577 modified in the body of the loop. Similarly for any iteration vars
15578 in simd with collapse > 1 where the iterator vars must be
15579 lastprivate. And similarly for vars mentioned in allocate clauses. */
15580 if (orig_for_stmt != for_stmt)
15581 var = decl;
15582 else if (!is_gimple_reg (decl)
15583 || (ort == ORT_SIMD
15584 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) > 1)
15585 || (allocate_uids && allocate_uids->contains (decl)))
15587 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
15588 /* Make sure omp_add_variable is not called on it prematurely.
15589 We call it ourselves a few lines later. */
15590 gimplify_omp_ctxp = NULL;
15591 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
15592 gimplify_omp_ctxp = ctx;
15593 TREE_OPERAND (t, 0) = var;
15595 gimplify_seq_add_stmt (&for_body, gimple_build_assign (decl, var));
15597 if (ort == ORT_SIMD
15598 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
15600 c2 = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
15601 OMP_CLAUSE_LINEAR_NO_COPYIN (c2) = 1;
15602 OMP_CLAUSE_LINEAR_NO_COPYOUT (c2) = 1;
15603 OMP_CLAUSE_DECL (c2) = var;
15604 OMP_CLAUSE_CHAIN (c2) = OMP_FOR_CLAUSES (for_stmt);
15605 OMP_FOR_CLAUSES (for_stmt) = c2;
15606 omp_add_variable (gimplify_omp_ctxp, var,
15607 GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN);
15608 if (c == NULL_TREE)
15610 c = c2;
15611 c2 = NULL_TREE;
15614 else
15615 omp_add_variable (gimplify_omp_ctxp, var,
15616 GOVD_PRIVATE | GOVD_SEEN);
15618 else
15619 var = decl;
15621 gimplify_omp_ctxp->in_for_exprs = true;
15622 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
15624 tree lb = TREE_OPERAND (t, 1);
15625 tret = gimplify_expr (&TREE_VEC_ELT (lb, 1), &for_pre_body, NULL,
15626 is_gimple_val, fb_rvalue, false);
15627 ret = MIN (ret, tret);
15628 tret = gimplify_expr (&TREE_VEC_ELT (lb, 2), &for_pre_body, NULL,
15629 is_gimple_val, fb_rvalue, false);
15631 else
15632 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
15633 is_gimple_val, fb_rvalue, false);
15634 gimplify_omp_ctxp->in_for_exprs = false;
15635 ret = MIN (ret, tret);
15636 if (ret == GS_ERROR)
15637 return ret;
15639 /* Handle OMP_FOR_COND. */
15640 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
15641 gcc_assert (COMPARISON_CLASS_P (t));
15642 gcc_assert (TREE_OPERAND (t, 0) == decl);
15644 gimplify_omp_ctxp->in_for_exprs = true;
15645 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
15647 tree ub = TREE_OPERAND (t, 1);
15648 tret = gimplify_expr (&TREE_VEC_ELT (ub, 1), &for_pre_body, NULL,
15649 is_gimple_val, fb_rvalue, false);
15650 ret = MIN (ret, tret);
15651 tret = gimplify_expr (&TREE_VEC_ELT (ub, 2), &for_pre_body, NULL,
15652 is_gimple_val, fb_rvalue, false);
15654 else
15655 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
15656 is_gimple_val, fb_rvalue, false);
15657 gimplify_omp_ctxp->in_for_exprs = false;
15658 ret = MIN (ret, tret);
15660 /* Handle OMP_FOR_INCR. */
15661 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
15662 switch (TREE_CODE (t))
15664 case PREINCREMENT_EXPR:
15665 case POSTINCREMENT_EXPR:
15667 tree decl = TREE_OPERAND (t, 0);
15668 /* c_omp_for_incr_canonicalize_ptr() should have been
15669 called to massage things appropriately. */
15670 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
15672 if (orig_for_stmt != for_stmt)
15673 break;
15674 t = build_int_cst (TREE_TYPE (decl), 1);
15675 if (c)
15676 OMP_CLAUSE_LINEAR_STEP (c) = t;
15677 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
15678 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
15679 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
15680 break;
15683 case PREDECREMENT_EXPR:
15684 case POSTDECREMENT_EXPR:
15685 /* c_omp_for_incr_canonicalize_ptr() should have been
15686 called to massage things appropriately. */
15687 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
15688 if (orig_for_stmt != for_stmt)
15689 break;
15690 t = build_int_cst (TREE_TYPE (decl), -1);
15691 if (c)
15692 OMP_CLAUSE_LINEAR_STEP (c) = t;
15693 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
15694 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
15695 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
15696 break;
15698 case MODIFY_EXPR:
15699 gcc_assert (TREE_OPERAND (t, 0) == decl);
15700 TREE_OPERAND (t, 0) = var;
15702 t = TREE_OPERAND (t, 1);
15703 switch (TREE_CODE (t))
15705 case PLUS_EXPR:
15706 if (TREE_OPERAND (t, 1) == decl)
15708 TREE_OPERAND (t, 1) = TREE_OPERAND (t, 0);
15709 TREE_OPERAND (t, 0) = var;
15710 break;
15713 /* Fallthru. */
15714 case MINUS_EXPR:
15715 case POINTER_PLUS_EXPR:
15716 gcc_assert (TREE_OPERAND (t, 0) == decl);
15717 TREE_OPERAND (t, 0) = var;
15718 break;
15719 default:
15720 gcc_unreachable ();
15723 gimplify_omp_ctxp->in_for_exprs = true;
15724 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
15725 is_gimple_val, fb_rvalue, false);
15726 ret = MIN (ret, tret);
15727 if (c)
15729 tree step = TREE_OPERAND (t, 1);
15730 tree stept = TREE_TYPE (decl);
15731 if (POINTER_TYPE_P (stept))
15732 stept = sizetype;
15733 step = fold_convert (stept, step);
15734 if (TREE_CODE (t) == MINUS_EXPR)
15735 step = fold_build1 (NEGATE_EXPR, stept, step);
15736 OMP_CLAUSE_LINEAR_STEP (c) = step;
15737 if (step != TREE_OPERAND (t, 1))
15739 tret = gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c),
15740 &for_pre_body, NULL,
15741 is_gimple_val, fb_rvalue, false);
15742 ret = MIN (ret, tret);
15745 gimplify_omp_ctxp->in_for_exprs = false;
15746 break;
15748 default:
15749 gcc_unreachable ();
15752 if (c2)
15754 gcc_assert (c);
15755 OMP_CLAUSE_LINEAR_STEP (c2) = OMP_CLAUSE_LINEAR_STEP (c);
15758 if ((var != decl || collapse > 1 || tile) && orig_for_stmt == for_stmt)
15760 for (c = OMP_FOR_CLAUSES (for_stmt); c ; c = OMP_CLAUSE_CHAIN (c))
15761 if (((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
15762 && OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c) == NULL)
15763 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
15764 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)
15765 && OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c) == NULL))
15766 && OMP_CLAUSE_DECL (c) == decl)
15768 if (is_doacross && (collapse == 1 || i >= collapse))
15769 t = var;
15770 else
15772 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
15773 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
15774 gcc_assert (TREE_OPERAND (t, 0) == var);
15775 t = TREE_OPERAND (t, 1);
15776 gcc_assert (TREE_CODE (t) == PLUS_EXPR
15777 || TREE_CODE (t) == MINUS_EXPR
15778 || TREE_CODE (t) == POINTER_PLUS_EXPR);
15779 gcc_assert (TREE_OPERAND (t, 0) == var);
15780 t = build2 (TREE_CODE (t), TREE_TYPE (decl),
15781 is_doacross ? var : decl,
15782 TREE_OPERAND (t, 1));
15784 gimple_seq *seq;
15785 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE)
15786 seq = &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c);
15787 else
15788 seq = &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c);
15789 push_gimplify_context ();
15790 gimplify_assign (decl, t, seq);
15791 gimple *bind = NULL;
15792 if (gimplify_ctxp->temps)
15794 bind = gimple_build_bind (NULL_TREE, *seq, NULL_TREE);
15795 *seq = NULL;
15796 gimplify_seq_add_stmt (seq, bind);
15798 pop_gimplify_context (bind);
15801 if (OMP_FOR_NON_RECTANGULAR (for_stmt) && var != decl)
15802 for (int j = i + 1; j < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); j++)
15804 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), j);
15805 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
15806 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
15807 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
15808 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
15809 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), j);
15810 gcc_assert (COMPARISON_CLASS_P (t));
15811 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
15812 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
15813 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
15817 BITMAP_FREE (has_decl_expr);
15818 delete allocate_uids;
15820 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP
15821 || (loop_p && orig_for_stmt == for_stmt))
15823 push_gimplify_context ();
15824 if (TREE_CODE (OMP_FOR_BODY (orig_for_stmt)) != BIND_EXPR)
15826 OMP_FOR_BODY (orig_for_stmt)
15827 = build3 (BIND_EXPR, void_type_node, NULL,
15828 OMP_FOR_BODY (orig_for_stmt), NULL);
15829 TREE_SIDE_EFFECTS (OMP_FOR_BODY (orig_for_stmt)) = 1;
15833 gimple *g = gimplify_and_return_first (OMP_FOR_BODY (orig_for_stmt),
15834 &for_body);
15836 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP
15837 || (loop_p && orig_for_stmt == for_stmt))
15839 if (gimple_code (g) == GIMPLE_BIND)
15840 pop_gimplify_context (g);
15841 else
15842 pop_gimplify_context (NULL);
15845 if (orig_for_stmt != for_stmt)
15846 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
15848 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
15849 decl = TREE_OPERAND (t, 0);
15850 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
15851 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
15852 gimplify_omp_ctxp = ctx->outer_context;
15853 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
15854 gimplify_omp_ctxp = ctx;
15855 omp_add_variable (gimplify_omp_ctxp, var, GOVD_PRIVATE | GOVD_SEEN);
15856 TREE_OPERAND (t, 0) = var;
15857 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
15858 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
15859 TREE_OPERAND (TREE_OPERAND (t, 1), 0) = var;
15860 if (OMP_FOR_NON_RECTANGULAR (for_stmt))
15861 for (int j = i + 1;
15862 j < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); j++)
15864 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), j);
15865 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
15866 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
15867 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
15869 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
15870 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
15872 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), j);
15873 gcc_assert (COMPARISON_CLASS_P (t));
15874 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
15875 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
15877 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
15878 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
15883 gimplify_adjust_omp_clauses (pre_p, for_body,
15884 &OMP_FOR_CLAUSES (orig_for_stmt),
15885 TREE_CODE (orig_for_stmt));
15887 int kind;
15888 switch (TREE_CODE (orig_for_stmt))
15890 case OMP_FOR: kind = GF_OMP_FOR_KIND_FOR; break;
15891 case OMP_SIMD: kind = GF_OMP_FOR_KIND_SIMD; break;
15892 case OMP_DISTRIBUTE: kind = GF_OMP_FOR_KIND_DISTRIBUTE; break;
15893 case OMP_TASKLOOP: kind = GF_OMP_FOR_KIND_TASKLOOP; break;
15894 case OACC_LOOP: kind = GF_OMP_FOR_KIND_OACC_LOOP; break;
15895 default:
15896 gcc_unreachable ();
15898 if (loop_p && kind == GF_OMP_FOR_KIND_SIMD)
15900 gimplify_seq_add_seq (pre_p, for_pre_body);
15901 for_pre_body = NULL;
15903 gfor = gimple_build_omp_for (for_body, kind, OMP_FOR_CLAUSES (orig_for_stmt),
15904 TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)),
15905 for_pre_body);
15906 if (orig_for_stmt != for_stmt)
15907 gimple_omp_for_set_combined_p (gfor, true);
15908 if (gimplify_omp_ctxp
15909 && (gimplify_omp_ctxp->combined_loop
15910 || (gimplify_omp_ctxp->region_type == ORT_COMBINED_PARALLEL
15911 && gimplify_omp_ctxp->outer_context
15912 && gimplify_omp_ctxp->outer_context->combined_loop)))
15914 gimple_omp_for_set_combined_into_p (gfor, true);
15915 if (gimplify_omp_ctxp->combined_loop)
15916 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_SIMD);
15917 else
15918 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_FOR);
15921 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
15923 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
15924 gimple_omp_for_set_index (gfor, i, TREE_OPERAND (t, 0));
15925 gimple_omp_for_set_initial (gfor, i, TREE_OPERAND (t, 1));
15926 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
15927 gimple_omp_for_set_cond (gfor, i, TREE_CODE (t));
15928 gimple_omp_for_set_final (gfor, i, TREE_OPERAND (t, 1));
15929 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
15930 gimple_omp_for_set_incr (gfor, i, TREE_OPERAND (t, 1));
15933 /* OMP_TASKLOOP is gimplified as two GIMPLE_OMP_FOR taskloop
15934 constructs with GIMPLE_OMP_TASK sandwiched in between them.
15935 The outer taskloop stands for computing the number of iterations,
15936 counts for collapsed loops and holding taskloop specific clauses.
15937 The task construct stands for the effect of data sharing on the
15938 explicit task it creates and the inner taskloop stands for expansion
15939 of the static loop inside of the explicit task construct. */
15940 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
15942 tree *gfor_clauses_ptr = gimple_omp_for_clauses_ptr (gfor);
15943 tree task_clauses = NULL_TREE;
15944 tree c = *gfor_clauses_ptr;
15945 tree *gtask_clauses_ptr = &task_clauses;
15946 tree outer_for_clauses = NULL_TREE;
15947 tree *gforo_clauses_ptr = &outer_for_clauses;
15948 bitmap lastprivate_uids = NULL;
15949 if (omp_find_clause (c, OMP_CLAUSE_ALLOCATE))
15951 c = omp_find_clause (c, OMP_CLAUSE_LASTPRIVATE);
15952 if (c)
15954 lastprivate_uids = BITMAP_ALLOC (NULL);
15955 for (; c; c = omp_find_clause (OMP_CLAUSE_CHAIN (c),
15956 OMP_CLAUSE_LASTPRIVATE))
15957 bitmap_set_bit (lastprivate_uids,
15958 DECL_UID (OMP_CLAUSE_DECL (c)));
15960 c = *gfor_clauses_ptr;
15962 for (; c; c = OMP_CLAUSE_CHAIN (c))
15963 switch (OMP_CLAUSE_CODE (c))
15965 /* These clauses are allowed on task, move them there. */
15966 case OMP_CLAUSE_SHARED:
15967 case OMP_CLAUSE_FIRSTPRIVATE:
15968 case OMP_CLAUSE_DEFAULT:
15969 case OMP_CLAUSE_IF:
15970 case OMP_CLAUSE_UNTIED:
15971 case OMP_CLAUSE_FINAL:
15972 case OMP_CLAUSE_MERGEABLE:
15973 case OMP_CLAUSE_PRIORITY:
15974 case OMP_CLAUSE_REDUCTION:
15975 case OMP_CLAUSE_IN_REDUCTION:
15976 *gtask_clauses_ptr = c;
15977 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
15978 break;
15979 case OMP_CLAUSE_PRIVATE:
15980 if (OMP_CLAUSE_PRIVATE_TASKLOOP_IV (c))
15982 /* We want private on outer for and firstprivate
15983 on task. */
15984 *gtask_clauses_ptr
15985 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
15986 OMP_CLAUSE_FIRSTPRIVATE);
15987 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
15988 lang_hooks.decls.omp_finish_clause (*gtask_clauses_ptr, NULL,
15989 openacc);
15990 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
15991 *gforo_clauses_ptr = c;
15992 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
15994 else
15996 *gtask_clauses_ptr = c;
15997 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
15999 break;
16000 /* These clauses go into outer taskloop clauses. */
16001 case OMP_CLAUSE_GRAINSIZE:
16002 case OMP_CLAUSE_NUM_TASKS:
16003 case OMP_CLAUSE_NOGROUP:
16004 *gforo_clauses_ptr = c;
16005 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
16006 break;
16007 /* Collapse clause we duplicate on both taskloops. */
16008 case OMP_CLAUSE_COLLAPSE:
16009 *gfor_clauses_ptr = c;
16010 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
16011 *gforo_clauses_ptr = copy_node (c);
16012 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr);
16013 break;
16014 /* For lastprivate, keep the clause on inner taskloop, and add
16015 a shared clause on task. If the same decl is also firstprivate,
16016 add also firstprivate clause on the inner taskloop. */
16017 case OMP_CLAUSE_LASTPRIVATE:
16018 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c))
16020 /* For taskloop C++ lastprivate IVs, we want:
16021 1) private on outer taskloop
16022 2) firstprivate and shared on task
16023 3) lastprivate on inner taskloop */
16024 *gtask_clauses_ptr
16025 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
16026 OMP_CLAUSE_FIRSTPRIVATE);
16027 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
16028 lang_hooks.decls.omp_finish_clause (*gtask_clauses_ptr, NULL,
16029 openacc);
16030 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
16031 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c) = 1;
16032 *gforo_clauses_ptr = build_omp_clause (OMP_CLAUSE_LOCATION (c),
16033 OMP_CLAUSE_PRIVATE);
16034 OMP_CLAUSE_DECL (*gforo_clauses_ptr) = OMP_CLAUSE_DECL (c);
16035 OMP_CLAUSE_PRIVATE_TASKLOOP_IV (*gforo_clauses_ptr) = 1;
16036 TREE_TYPE (*gforo_clauses_ptr) = TREE_TYPE (c);
16037 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr);
16039 *gfor_clauses_ptr = c;
16040 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
16041 *gtask_clauses_ptr
16042 = build_omp_clause (OMP_CLAUSE_LOCATION (c), OMP_CLAUSE_SHARED);
16043 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
16044 if (OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
16045 OMP_CLAUSE_SHARED_FIRSTPRIVATE (*gtask_clauses_ptr) = 1;
16046 gtask_clauses_ptr
16047 = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
16048 break;
16049 /* Allocate clause we duplicate on task and inner taskloop
16050 if the decl is lastprivate, otherwise just put on task. */
16051 case OMP_CLAUSE_ALLOCATE:
16052 if (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
16053 && DECL_P (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)))
16055 /* Additionally, put firstprivate clause on task
16056 for the allocator if it is not constant. */
16057 *gtask_clauses_ptr
16058 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
16059 OMP_CLAUSE_FIRSTPRIVATE);
16060 OMP_CLAUSE_DECL (*gtask_clauses_ptr)
16061 = OMP_CLAUSE_ALLOCATE_ALLOCATOR (c);
16062 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
16064 if (lastprivate_uids
16065 && bitmap_bit_p (lastprivate_uids,
16066 DECL_UID (OMP_CLAUSE_DECL (c))))
16068 *gfor_clauses_ptr = c;
16069 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
16070 *gtask_clauses_ptr = copy_node (c);
16071 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
16073 else
16075 *gtask_clauses_ptr = c;
16076 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
16078 break;
16079 default:
16080 gcc_unreachable ();
16082 *gfor_clauses_ptr = NULL_TREE;
16083 *gtask_clauses_ptr = NULL_TREE;
16084 *gforo_clauses_ptr = NULL_TREE;
16085 BITMAP_FREE (lastprivate_uids);
16086 gimple_set_location (gfor, input_location);
16087 g = gimple_build_bind (NULL_TREE, gfor, NULL_TREE);
16088 g = gimple_build_omp_task (g, task_clauses, NULL_TREE, NULL_TREE,
16089 NULL_TREE, NULL_TREE, NULL_TREE);
16090 gimple_set_location (g, input_location);
16091 gimple_omp_task_set_taskloop_p (g, true);
16092 g = gimple_build_bind (NULL_TREE, g, NULL_TREE);
16093 gomp_for *gforo
16094 = gimple_build_omp_for (g, GF_OMP_FOR_KIND_TASKLOOP, outer_for_clauses,
16095 gimple_omp_for_collapse (gfor),
16096 gimple_omp_for_pre_body (gfor));
16097 gimple_omp_for_set_pre_body (gfor, NULL);
16098 gimple_omp_for_set_combined_p (gforo, true);
16099 gimple_omp_for_set_combined_into_p (gfor, true);
16100 for (i = 0; i < (int) gimple_omp_for_collapse (gfor); i++)
16102 tree type = TREE_TYPE (gimple_omp_for_index (gfor, i));
16103 tree v = create_tmp_var (type);
16104 gimple_omp_for_set_index (gforo, i, v);
16105 t = unshare_expr (gimple_omp_for_initial (gfor, i));
16106 gimple_omp_for_set_initial (gforo, i, t);
16107 gimple_omp_for_set_cond (gforo, i,
16108 gimple_omp_for_cond (gfor, i));
16109 t = unshare_expr (gimple_omp_for_final (gfor, i));
16110 gimple_omp_for_set_final (gforo, i, t);
16111 t = unshare_expr (gimple_omp_for_incr (gfor, i));
16112 gcc_assert (TREE_OPERAND (t, 0) == gimple_omp_for_index (gfor, i));
16113 TREE_OPERAND (t, 0) = v;
16114 gimple_omp_for_set_incr (gforo, i, t);
16115 t = build_omp_clause (input_location, OMP_CLAUSE_PRIVATE);
16116 OMP_CLAUSE_DECL (t) = v;
16117 OMP_CLAUSE_CHAIN (t) = gimple_omp_for_clauses (gforo);
16118 gimple_omp_for_set_clauses (gforo, t);
16119 if (OMP_FOR_NON_RECTANGULAR (for_stmt))
16121 tree *p1 = NULL, *p2 = NULL;
16122 t = gimple_omp_for_initial (gforo, i);
16123 if (TREE_CODE (t) == TREE_VEC)
16124 p1 = &TREE_VEC_ELT (t, 0);
16125 t = gimple_omp_for_final (gforo, i);
16126 if (TREE_CODE (t) == TREE_VEC)
16128 if (p1)
16129 p2 = &TREE_VEC_ELT (t, 0);
16130 else
16131 p1 = &TREE_VEC_ELT (t, 0);
16133 if (p1)
16135 int j;
16136 for (j = 0; j < i; j++)
16137 if (*p1 == gimple_omp_for_index (gfor, j))
16139 *p1 = gimple_omp_for_index (gforo, j);
16140 if (p2)
16141 *p2 = *p1;
16142 break;
16144 gcc_assert (j < i);
16148 gimplify_seq_add_stmt (pre_p, gforo);
16150 else
16151 gimplify_seq_add_stmt (pre_p, gfor);
16153 if (TREE_CODE (orig_for_stmt) == OMP_FOR)
16155 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
16156 unsigned lastprivate_conditional = 0;
16157 while (ctx
16158 && (ctx->region_type == ORT_TARGET_DATA
16159 || ctx->region_type == ORT_TASKGROUP))
16160 ctx = ctx->outer_context;
16161 if (ctx && (ctx->region_type & ORT_PARALLEL) != 0)
16162 for (tree c = gimple_omp_for_clauses (gfor);
16163 c; c = OMP_CLAUSE_CHAIN (c))
16164 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
16165 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
16166 ++lastprivate_conditional;
16167 if (lastprivate_conditional)
16169 struct omp_for_data fd;
16170 omp_extract_for_data (gfor, &fd, NULL);
16171 tree type = build_array_type_nelts (unsigned_type_for (fd.iter_type),
16172 lastprivate_conditional);
16173 tree var = create_tmp_var_raw (type);
16174 tree c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE__CONDTEMP_);
16175 OMP_CLAUSE_DECL (c) = var;
16176 OMP_CLAUSE_CHAIN (c) = gimple_omp_for_clauses (gfor);
16177 gimple_omp_for_set_clauses (gfor, c);
16178 omp_add_variable (ctx, var, GOVD_CONDTEMP | GOVD_SEEN);
16181 else if (TREE_CODE (orig_for_stmt) == OMP_SIMD)
16183 unsigned lastprivate_conditional = 0;
16184 for (tree c = gimple_omp_for_clauses (gfor); c; c = OMP_CLAUSE_CHAIN (c))
16185 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
16186 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
16187 ++lastprivate_conditional;
16188 if (lastprivate_conditional)
16190 struct omp_for_data fd;
16191 omp_extract_for_data (gfor, &fd, NULL);
16192 tree type = unsigned_type_for (fd.iter_type);
16193 while (lastprivate_conditional--)
16195 tree c = build_omp_clause (UNKNOWN_LOCATION,
16196 OMP_CLAUSE__CONDTEMP_);
16197 OMP_CLAUSE_DECL (c) = create_tmp_var (type);
16198 OMP_CLAUSE_CHAIN (c) = gimple_omp_for_clauses (gfor);
16199 gimple_omp_for_set_clauses (gfor, c);
16204 if (ret != GS_ALL_DONE)
16205 return GS_ERROR;
16206 *expr_p = NULL_TREE;
16207 return GS_ALL_DONE;
16210 /* Helper for gimplify_omp_loop, called through walk_tree. */
16212 static tree
16213 note_no_context_vars (tree *tp, int *, void *data)
16215 if (VAR_P (*tp)
16216 && DECL_CONTEXT (*tp) == NULL_TREE
16217 && !is_global_var (*tp))
16219 vec<tree> *d = (vec<tree> *) data;
16220 d->safe_push (*tp);
16221 DECL_CONTEXT (*tp) = current_function_decl;
16223 return NULL_TREE;
16226 /* Gimplify the gross structure of an OMP_LOOP statement. */
16228 static enum gimplify_status
16229 gimplify_omp_loop (tree *expr_p, gimple_seq *pre_p)
16231 tree for_stmt = *expr_p;
16232 tree clauses = OMP_FOR_CLAUSES (for_stmt);
16233 struct gimplify_omp_ctx *octx = gimplify_omp_ctxp;
16234 enum omp_clause_bind_kind kind = OMP_CLAUSE_BIND_THREAD;
16235 int i;
16237 /* If order is not present, the behavior is as if order(concurrent)
16238 appeared. */
16239 tree order = omp_find_clause (clauses, OMP_CLAUSE_ORDER);
16240 if (order == NULL_TREE)
16242 order = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_ORDER);
16243 OMP_CLAUSE_CHAIN (order) = clauses;
16244 OMP_FOR_CLAUSES (for_stmt) = clauses = order;
16247 tree bind = omp_find_clause (clauses, OMP_CLAUSE_BIND);
16248 if (bind == NULL_TREE)
16250 if (!flag_openmp) /* flag_openmp_simd */
16252 else if (octx && (octx->region_type & ORT_TEAMS) != 0)
16253 kind = OMP_CLAUSE_BIND_TEAMS;
16254 else if (octx && (octx->region_type & ORT_PARALLEL) != 0)
16255 kind = OMP_CLAUSE_BIND_PARALLEL;
16256 else
16258 for (; octx; octx = octx->outer_context)
16260 if ((octx->region_type & ORT_ACC) != 0
16261 || octx->region_type == ORT_NONE
16262 || octx->region_type == ORT_IMPLICIT_TARGET)
16263 continue;
16264 break;
16266 if (octx == NULL && !in_omp_construct)
16267 error_at (EXPR_LOCATION (for_stmt),
16268 "%<bind%> clause not specified on a %<loop%> "
16269 "construct not nested inside another OpenMP construct");
16271 bind = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_BIND);
16272 OMP_CLAUSE_CHAIN (bind) = clauses;
16273 OMP_CLAUSE_BIND_KIND (bind) = kind;
16274 OMP_FOR_CLAUSES (for_stmt) = bind;
16276 else
16277 switch (OMP_CLAUSE_BIND_KIND (bind))
16279 case OMP_CLAUSE_BIND_THREAD:
16280 break;
16281 case OMP_CLAUSE_BIND_PARALLEL:
16282 if (!flag_openmp) /* flag_openmp_simd */
16284 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
16285 break;
16287 for (; octx; octx = octx->outer_context)
16288 if (octx->region_type == ORT_SIMD
16289 && omp_find_clause (octx->clauses, OMP_CLAUSE_BIND) == NULL_TREE)
16291 error_at (EXPR_LOCATION (for_stmt),
16292 "%<bind(parallel)%> on a %<loop%> construct nested "
16293 "inside %<simd%> construct");
16294 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
16295 break;
16297 kind = OMP_CLAUSE_BIND_PARALLEL;
16298 break;
16299 case OMP_CLAUSE_BIND_TEAMS:
16300 if (!flag_openmp) /* flag_openmp_simd */
16302 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
16303 break;
16305 if ((octx
16306 && octx->region_type != ORT_IMPLICIT_TARGET
16307 && octx->region_type != ORT_NONE
16308 && (octx->region_type & ORT_TEAMS) == 0)
16309 || in_omp_construct)
16311 error_at (EXPR_LOCATION (for_stmt),
16312 "%<bind(teams)%> on a %<loop%> region not strictly "
16313 "nested inside of a %<teams%> region");
16314 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
16315 break;
16317 kind = OMP_CLAUSE_BIND_TEAMS;
16318 break;
16319 default:
16320 gcc_unreachable ();
16323 for (tree *pc = &OMP_FOR_CLAUSES (for_stmt); *pc; )
16324 switch (OMP_CLAUSE_CODE (*pc))
16326 case OMP_CLAUSE_REDUCTION:
16327 if (OMP_CLAUSE_REDUCTION_INSCAN (*pc))
16329 error_at (OMP_CLAUSE_LOCATION (*pc),
16330 "%<inscan%> %<reduction%> clause on "
16331 "%qs construct", "loop");
16332 OMP_CLAUSE_REDUCTION_INSCAN (*pc) = 0;
16334 if (OMP_CLAUSE_REDUCTION_TASK (*pc))
16336 error_at (OMP_CLAUSE_LOCATION (*pc),
16337 "invalid %<task%> reduction modifier on construct "
16338 "other than %<parallel%>, %qs or %<sections%>",
16339 lang_GNU_Fortran () ? "do" : "for");
16340 OMP_CLAUSE_REDUCTION_TASK (*pc) = 0;
16342 pc = &OMP_CLAUSE_CHAIN (*pc);
16343 break;
16344 case OMP_CLAUSE_LASTPRIVATE:
16345 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
16347 tree t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
16348 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
16349 if (OMP_CLAUSE_DECL (*pc) == TREE_OPERAND (t, 0))
16350 break;
16351 if (OMP_FOR_ORIG_DECLS (for_stmt)
16352 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt),
16353 i)) == TREE_LIST
16354 && TREE_PURPOSE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt),
16355 i)))
16357 tree orig = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
16358 if (OMP_CLAUSE_DECL (*pc) == TREE_PURPOSE (orig))
16359 break;
16362 if (i == TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)))
16364 error_at (OMP_CLAUSE_LOCATION (*pc),
16365 "%<lastprivate%> clause on a %<loop%> construct refers "
16366 "to a variable %qD which is not the loop iterator",
16367 OMP_CLAUSE_DECL (*pc));
16368 *pc = OMP_CLAUSE_CHAIN (*pc);
16369 break;
16371 pc = &OMP_CLAUSE_CHAIN (*pc);
16372 break;
16373 default:
16374 pc = &OMP_CLAUSE_CHAIN (*pc);
16375 break;
16378 TREE_SET_CODE (for_stmt, OMP_SIMD);
16380 int last;
16381 switch (kind)
16383 case OMP_CLAUSE_BIND_THREAD: last = 0; break;
16384 case OMP_CLAUSE_BIND_PARALLEL: last = 1; break;
16385 case OMP_CLAUSE_BIND_TEAMS: last = 2; break;
16387 for (int pass = 1; pass <= last; pass++)
16389 if (pass == 2)
16391 tree bind = build3 (BIND_EXPR, void_type_node, NULL, NULL,
16392 make_node (BLOCK));
16393 append_to_statement_list (*expr_p, &BIND_EXPR_BODY (bind));
16394 *expr_p = make_node (OMP_PARALLEL);
16395 TREE_TYPE (*expr_p) = void_type_node;
16396 OMP_PARALLEL_BODY (*expr_p) = bind;
16397 OMP_PARALLEL_COMBINED (*expr_p) = 1;
16398 SET_EXPR_LOCATION (*expr_p, EXPR_LOCATION (for_stmt));
16399 tree *pc = &OMP_PARALLEL_CLAUSES (*expr_p);
16400 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
16401 if (OMP_FOR_ORIG_DECLS (for_stmt)
16402 && (TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i))
16403 == TREE_LIST))
16405 tree elt = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
16406 if (TREE_PURPOSE (elt) && TREE_VALUE (elt))
16408 *pc = build_omp_clause (UNKNOWN_LOCATION,
16409 OMP_CLAUSE_FIRSTPRIVATE);
16410 OMP_CLAUSE_DECL (*pc) = TREE_VALUE (elt);
16411 pc = &OMP_CLAUSE_CHAIN (*pc);
16415 tree t = make_node (pass == 2 ? OMP_DISTRIBUTE : OMP_FOR);
16416 tree *pc = &OMP_FOR_CLAUSES (t);
16417 TREE_TYPE (t) = void_type_node;
16418 OMP_FOR_BODY (t) = *expr_p;
16419 SET_EXPR_LOCATION (t, EXPR_LOCATION (for_stmt));
16420 for (tree c = OMP_FOR_CLAUSES (for_stmt); c; c = OMP_CLAUSE_CHAIN (c))
16421 switch (OMP_CLAUSE_CODE (c))
16423 case OMP_CLAUSE_BIND:
16424 case OMP_CLAUSE_ORDER:
16425 case OMP_CLAUSE_COLLAPSE:
16426 *pc = copy_node (c);
16427 pc = &OMP_CLAUSE_CHAIN (*pc);
16428 break;
16429 case OMP_CLAUSE_PRIVATE:
16430 case OMP_CLAUSE_FIRSTPRIVATE:
16431 /* Only needed on innermost. */
16432 break;
16433 case OMP_CLAUSE_LASTPRIVATE:
16434 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c) && pass != last)
16436 *pc = build_omp_clause (OMP_CLAUSE_LOCATION (c),
16437 OMP_CLAUSE_FIRSTPRIVATE);
16438 OMP_CLAUSE_DECL (*pc) = OMP_CLAUSE_DECL (c);
16439 lang_hooks.decls.omp_finish_clause (*pc, NULL, false);
16440 pc = &OMP_CLAUSE_CHAIN (*pc);
16442 *pc = copy_node (c);
16443 OMP_CLAUSE_LASTPRIVATE_STMT (*pc) = NULL_TREE;
16444 TREE_TYPE (*pc) = unshare_expr (TREE_TYPE (c));
16445 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c))
16447 if (pass != last)
16448 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (*pc) = 1;
16449 else
16450 lang_hooks.decls.omp_finish_clause (*pc, NULL, false);
16451 OMP_CLAUSE_LASTPRIVATE_LOOP_IV (*pc) = 0;
16453 pc = &OMP_CLAUSE_CHAIN (*pc);
16454 break;
16455 case OMP_CLAUSE_REDUCTION:
16456 *pc = copy_node (c);
16457 OMP_CLAUSE_DECL (*pc) = unshare_expr (OMP_CLAUSE_DECL (c));
16458 TREE_TYPE (*pc) = unshare_expr (TREE_TYPE (c));
16459 if (OMP_CLAUSE_REDUCTION_PLACEHOLDER (*pc))
16461 auto_vec<tree> no_context_vars;
16462 int walk_subtrees = 0;
16463 note_no_context_vars (&OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
16464 &walk_subtrees, &no_context_vars);
16465 if (tree p = OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c))
16466 note_no_context_vars (&p, &walk_subtrees, &no_context_vars);
16467 walk_tree_without_duplicates (&OMP_CLAUSE_REDUCTION_INIT (c),
16468 note_no_context_vars,
16469 &no_context_vars);
16470 walk_tree_without_duplicates (&OMP_CLAUSE_REDUCTION_MERGE (c),
16471 note_no_context_vars,
16472 &no_context_vars);
16474 OMP_CLAUSE_REDUCTION_PLACEHOLDER (*pc)
16475 = copy_node (OMP_CLAUSE_REDUCTION_PLACEHOLDER (c));
16476 if (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (*pc))
16477 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (*pc)
16478 = copy_node (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c));
16480 hash_map<tree, tree> decl_map;
16481 decl_map.put (OMP_CLAUSE_DECL (c), OMP_CLAUSE_DECL (c));
16482 decl_map.put (OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
16483 OMP_CLAUSE_REDUCTION_PLACEHOLDER (*pc));
16484 if (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (*pc))
16485 decl_map.put (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
16486 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (*pc));
16488 copy_body_data id;
16489 memset (&id, 0, sizeof (id));
16490 id.src_fn = current_function_decl;
16491 id.dst_fn = current_function_decl;
16492 id.src_cfun = cfun;
16493 id.decl_map = &decl_map;
16494 id.copy_decl = copy_decl_no_change;
16495 id.transform_call_graph_edges = CB_CGE_DUPLICATE;
16496 id.transform_new_cfg = true;
16497 id.transform_return_to_modify = false;
16498 id.eh_lp_nr = 0;
16499 walk_tree (&OMP_CLAUSE_REDUCTION_INIT (*pc), copy_tree_body_r,
16500 &id, NULL);
16501 walk_tree (&OMP_CLAUSE_REDUCTION_MERGE (*pc), copy_tree_body_r,
16502 &id, NULL);
16504 for (tree d : no_context_vars)
16506 DECL_CONTEXT (d) = NULL_TREE;
16507 DECL_CONTEXT (*decl_map.get (d)) = NULL_TREE;
16510 else
16512 OMP_CLAUSE_REDUCTION_INIT (*pc)
16513 = unshare_expr (OMP_CLAUSE_REDUCTION_INIT (c));
16514 OMP_CLAUSE_REDUCTION_MERGE (*pc)
16515 = unshare_expr (OMP_CLAUSE_REDUCTION_MERGE (c));
16517 pc = &OMP_CLAUSE_CHAIN (*pc);
16518 break;
16519 default:
16520 gcc_unreachable ();
16522 *pc = NULL_TREE;
16523 *expr_p = t;
16525 return gimplify_expr (expr_p, pre_p, NULL, is_gimple_stmt, fb_none);
16529 /* Helper function of optimize_target_teams, find OMP_TEAMS inside
16530 of OMP_TARGET's body. */
16532 static tree
16533 find_omp_teams (tree *tp, int *walk_subtrees, void *)
16535 *walk_subtrees = 0;
16536 switch (TREE_CODE (*tp))
16538 case OMP_TEAMS:
16539 return *tp;
16540 case BIND_EXPR:
16541 case STATEMENT_LIST:
16542 *walk_subtrees = 1;
16543 break;
16544 default:
16545 break;
16547 return NULL_TREE;
16550 /* Helper function of optimize_target_teams, determine if the expression
16551 can be computed safely before the target construct on the host. */
16553 static tree
16554 computable_teams_clause (tree *tp, int *walk_subtrees, void *)
16556 splay_tree_node n;
16558 if (TYPE_P (*tp))
16560 *walk_subtrees = 0;
16561 return NULL_TREE;
16563 switch (TREE_CODE (*tp))
16565 case VAR_DECL:
16566 case PARM_DECL:
16567 case RESULT_DECL:
16568 *walk_subtrees = 0;
16569 if (error_operand_p (*tp)
16570 || !INTEGRAL_TYPE_P (TREE_TYPE (*tp))
16571 || DECL_HAS_VALUE_EXPR_P (*tp)
16572 || DECL_THREAD_LOCAL_P (*tp)
16573 || TREE_SIDE_EFFECTS (*tp)
16574 || TREE_THIS_VOLATILE (*tp))
16575 return *tp;
16576 if (is_global_var (*tp)
16577 && (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (*tp))
16578 || lookup_attribute ("omp declare target link",
16579 DECL_ATTRIBUTES (*tp))))
16580 return *tp;
16581 if (VAR_P (*tp)
16582 && !DECL_SEEN_IN_BIND_EXPR_P (*tp)
16583 && !is_global_var (*tp)
16584 && decl_function_context (*tp) == current_function_decl)
16585 return *tp;
16586 n = splay_tree_lookup (gimplify_omp_ctxp->variables,
16587 (splay_tree_key) *tp);
16588 if (n == NULL)
16590 if (gimplify_omp_ctxp->defaultmap[GDMK_SCALAR] & GOVD_FIRSTPRIVATE)
16591 return NULL_TREE;
16592 return *tp;
16594 else if (n->value & GOVD_LOCAL)
16595 return *tp;
16596 else if (n->value & GOVD_FIRSTPRIVATE)
16597 return NULL_TREE;
16598 else if ((n->value & (GOVD_MAP | GOVD_MAP_ALWAYS_TO))
16599 == (GOVD_MAP | GOVD_MAP_ALWAYS_TO))
16600 return NULL_TREE;
16601 return *tp;
16602 case INTEGER_CST:
16603 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp)))
16604 return *tp;
16605 return NULL_TREE;
16606 case TARGET_EXPR:
16607 if (TARGET_EXPR_INITIAL (*tp)
16608 || TREE_CODE (TARGET_EXPR_SLOT (*tp)) != VAR_DECL)
16609 return *tp;
16610 return computable_teams_clause (&TARGET_EXPR_SLOT (*tp),
16611 walk_subtrees, NULL);
16612 /* Allow some reasonable subset of integral arithmetics. */
16613 case PLUS_EXPR:
16614 case MINUS_EXPR:
16615 case MULT_EXPR:
16616 case TRUNC_DIV_EXPR:
16617 case CEIL_DIV_EXPR:
16618 case FLOOR_DIV_EXPR:
16619 case ROUND_DIV_EXPR:
16620 case TRUNC_MOD_EXPR:
16621 case CEIL_MOD_EXPR:
16622 case FLOOR_MOD_EXPR:
16623 case ROUND_MOD_EXPR:
16624 case RDIV_EXPR:
16625 case EXACT_DIV_EXPR:
16626 case MIN_EXPR:
16627 case MAX_EXPR:
16628 case LSHIFT_EXPR:
16629 case RSHIFT_EXPR:
16630 case BIT_IOR_EXPR:
16631 case BIT_XOR_EXPR:
16632 case BIT_AND_EXPR:
16633 case NEGATE_EXPR:
16634 case ABS_EXPR:
16635 case BIT_NOT_EXPR:
16636 case NON_LVALUE_EXPR:
16637 CASE_CONVERT:
16638 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp)))
16639 return *tp;
16640 return NULL_TREE;
16641 /* And disallow anything else, except for comparisons. */
16642 default:
16643 if (COMPARISON_CLASS_P (*tp))
16644 return NULL_TREE;
16645 return *tp;
16649 /* Try to determine if the num_teams and/or thread_limit expressions
16650 can have their values determined already before entering the
16651 target construct.
16652 INTEGER_CSTs trivially are,
16653 integral decls that are firstprivate (explicitly or implicitly)
16654 or explicitly map(always, to:) or map(always, tofrom:) on the target
16655 region too, and expressions involving simple arithmetics on those
16656 too, function calls are not ok, dereferencing something neither etc.
16657 Add NUM_TEAMS and THREAD_LIMIT clauses to the OMP_CLAUSES of
16658 EXPR based on what we find:
16659 0 stands for clause not specified at all, use implementation default
16660 -1 stands for value that can't be determined easily before entering
16661 the target construct.
16662 -2 means that no explicit teams construct was specified
16663 If teams construct is not present at all, use 1 for num_teams
16664 and 0 for thread_limit (only one team is involved, and the thread
16665 limit is implementation defined. */
16667 static void
16668 optimize_target_teams (tree target, gimple_seq *pre_p)
16670 tree body = OMP_BODY (target);
16671 tree teams = walk_tree (&body, find_omp_teams, NULL, NULL);
16672 tree num_teams_lower = NULL_TREE;
16673 tree num_teams_upper = integer_zero_node;
16674 tree thread_limit = integer_zero_node;
16675 location_t num_teams_loc = EXPR_LOCATION (target);
16676 location_t thread_limit_loc = EXPR_LOCATION (target);
16677 tree c, *p, expr;
16678 struct gimplify_omp_ctx *target_ctx = gimplify_omp_ctxp;
16680 if (teams == NULL_TREE)
16681 num_teams_upper = build_int_cst (integer_type_node, -2);
16682 else
16683 for (c = OMP_TEAMS_CLAUSES (teams); c; c = OMP_CLAUSE_CHAIN (c))
16685 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_NUM_TEAMS)
16687 p = &num_teams_upper;
16688 num_teams_loc = OMP_CLAUSE_LOCATION (c);
16689 if (OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c))
16691 expr = OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c);
16692 if (TREE_CODE (expr) == INTEGER_CST)
16693 num_teams_lower = expr;
16694 else if (walk_tree (&expr, computable_teams_clause,
16695 NULL, NULL))
16696 num_teams_lower = integer_minus_one_node;
16697 else
16699 num_teams_lower = expr;
16700 gimplify_omp_ctxp = gimplify_omp_ctxp->outer_context;
16701 if (gimplify_expr (&num_teams_lower, pre_p, NULL,
16702 is_gimple_val, fb_rvalue, false)
16703 == GS_ERROR)
16705 gimplify_omp_ctxp = target_ctx;
16706 num_teams_lower = integer_minus_one_node;
16708 else
16710 gimplify_omp_ctxp = target_ctx;
16711 if (!DECL_P (expr) && TREE_CODE (expr) != TARGET_EXPR)
16712 OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c)
16713 = num_teams_lower;
16718 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_THREAD_LIMIT)
16720 p = &thread_limit;
16721 thread_limit_loc = OMP_CLAUSE_LOCATION (c);
16723 else
16724 continue;
16725 expr = OMP_CLAUSE_OPERAND (c, 0);
16726 if (TREE_CODE (expr) == INTEGER_CST)
16728 *p = expr;
16729 continue;
16731 if (walk_tree (&expr, computable_teams_clause, NULL, NULL))
16733 *p = integer_minus_one_node;
16734 continue;
16736 *p = expr;
16737 gimplify_omp_ctxp = gimplify_omp_ctxp->outer_context;
16738 if (gimplify_expr (p, pre_p, NULL, is_gimple_val, fb_rvalue, false)
16739 == GS_ERROR)
16741 gimplify_omp_ctxp = target_ctx;
16742 *p = integer_minus_one_node;
16743 continue;
16745 gimplify_omp_ctxp = target_ctx;
16746 if (!DECL_P (expr) && TREE_CODE (expr) != TARGET_EXPR)
16747 OMP_CLAUSE_OPERAND (c, 0) = *p;
16749 if (!omp_find_clause (OMP_TARGET_CLAUSES (target), OMP_CLAUSE_THREAD_LIMIT))
16751 c = build_omp_clause (thread_limit_loc, OMP_CLAUSE_THREAD_LIMIT);
16752 OMP_CLAUSE_THREAD_LIMIT_EXPR (c) = thread_limit;
16753 OMP_CLAUSE_CHAIN (c) = OMP_TARGET_CLAUSES (target);
16754 OMP_TARGET_CLAUSES (target) = c;
16756 c = build_omp_clause (num_teams_loc, OMP_CLAUSE_NUM_TEAMS);
16757 OMP_CLAUSE_NUM_TEAMS_UPPER_EXPR (c) = num_teams_upper;
16758 OMP_CLAUSE_NUM_TEAMS_LOWER_EXPR (c) = num_teams_lower;
16759 OMP_CLAUSE_CHAIN (c) = OMP_TARGET_CLAUSES (target);
16760 OMP_TARGET_CLAUSES (target) = c;
16763 /* Gimplify the gross structure of several OMP constructs. */
16765 static void
16766 gimplify_omp_workshare (tree *expr_p, gimple_seq *pre_p)
16768 tree expr = *expr_p;
16769 gimple *stmt;
16770 gimple_seq body = NULL;
16771 enum omp_region_type ort;
16773 switch (TREE_CODE (expr))
16775 case OMP_SECTIONS:
16776 case OMP_SINGLE:
16777 ort = ORT_WORKSHARE;
16778 break;
16779 case OMP_SCOPE:
16780 ort = ORT_TASKGROUP;
16781 break;
16782 case OMP_TARGET:
16783 ort = OMP_TARGET_COMBINED (expr) ? ORT_COMBINED_TARGET : ORT_TARGET;
16784 break;
16785 case OACC_KERNELS:
16786 ort = ORT_ACC_KERNELS;
16787 break;
16788 case OACC_PARALLEL:
16789 ort = ORT_ACC_PARALLEL;
16790 break;
16791 case OACC_SERIAL:
16792 ort = ORT_ACC_SERIAL;
16793 break;
16794 case OACC_DATA:
16795 ort = ORT_ACC_DATA;
16796 break;
16797 case OMP_TARGET_DATA:
16798 ort = ORT_TARGET_DATA;
16799 break;
16800 case OMP_TEAMS:
16801 ort = OMP_TEAMS_COMBINED (expr) ? ORT_COMBINED_TEAMS : ORT_TEAMS;
16802 if (gimplify_omp_ctxp == NULL
16803 || gimplify_omp_ctxp->region_type == ORT_IMPLICIT_TARGET)
16804 ort = (enum omp_region_type) (ort | ORT_HOST_TEAMS);
16805 break;
16806 case OACC_HOST_DATA:
16807 ort = ORT_ACC_HOST_DATA;
16808 break;
16809 default:
16810 gcc_unreachable ();
16813 bool save_in_omp_construct = in_omp_construct;
16814 if ((ort & ORT_ACC) == 0)
16815 in_omp_construct = false;
16816 gimplify_scan_omp_clauses (&OMP_CLAUSES (expr), pre_p, ort,
16817 TREE_CODE (expr));
16818 if (TREE_CODE (expr) == OMP_TARGET)
16819 optimize_target_teams (expr, pre_p);
16820 if ((ort & (ORT_TARGET | ORT_TARGET_DATA)) != 0
16821 || (ort & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
16823 push_gimplify_context ();
16824 gimple *g = gimplify_and_return_first (OMP_BODY (expr), &body);
16825 if (gimple_code (g) == GIMPLE_BIND)
16826 pop_gimplify_context (g);
16827 else
16828 pop_gimplify_context (NULL);
16829 if ((ort & ORT_TARGET_DATA) != 0)
16831 enum built_in_function end_ix;
16832 switch (TREE_CODE (expr))
16834 case OACC_DATA:
16835 case OACC_HOST_DATA:
16836 end_ix = BUILT_IN_GOACC_DATA_END;
16837 break;
16838 case OMP_TARGET_DATA:
16839 end_ix = BUILT_IN_GOMP_TARGET_END_DATA;
16840 break;
16841 default:
16842 gcc_unreachable ();
16844 tree fn = builtin_decl_explicit (end_ix);
16845 g = gimple_build_call (fn, 0);
16846 gimple_seq cleanup = NULL;
16847 gimple_seq_add_stmt (&cleanup, g);
16848 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
16849 body = NULL;
16850 gimple_seq_add_stmt (&body, g);
16853 else
16854 gimplify_and_add (OMP_BODY (expr), &body);
16855 gimplify_adjust_omp_clauses (pre_p, body, &OMP_CLAUSES (expr),
16856 TREE_CODE (expr));
16857 in_omp_construct = save_in_omp_construct;
16859 switch (TREE_CODE (expr))
16861 case OACC_DATA:
16862 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_DATA,
16863 OMP_CLAUSES (expr));
16864 break;
16865 case OACC_HOST_DATA:
16866 if (omp_find_clause (OMP_CLAUSES (expr), OMP_CLAUSE_IF_PRESENT))
16868 for (tree c = OMP_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
16869 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_USE_DEVICE_PTR)
16870 OMP_CLAUSE_USE_DEVICE_PTR_IF_PRESENT (c) = 1;
16873 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_HOST_DATA,
16874 OMP_CLAUSES (expr));
16875 break;
16876 case OACC_KERNELS:
16877 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_KERNELS,
16878 OMP_CLAUSES (expr));
16879 break;
16880 case OACC_PARALLEL:
16881 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_PARALLEL,
16882 OMP_CLAUSES (expr));
16883 break;
16884 case OACC_SERIAL:
16885 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_SERIAL,
16886 OMP_CLAUSES (expr));
16887 break;
16888 case OMP_SECTIONS:
16889 stmt = gimple_build_omp_sections (body, OMP_CLAUSES (expr));
16890 break;
16891 case OMP_SINGLE:
16892 stmt = gimple_build_omp_single (body, OMP_CLAUSES (expr));
16893 break;
16894 case OMP_SCOPE:
16895 stmt = gimple_build_omp_scope (body, OMP_CLAUSES (expr));
16896 break;
16897 case OMP_TARGET:
16898 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_REGION,
16899 OMP_CLAUSES (expr));
16900 break;
16901 case OMP_TARGET_DATA:
16902 /* Put use_device_{ptr,addr} clauses last, as map clauses are supposed
16903 to be evaluated before the use_device_{ptr,addr} clauses if they
16904 refer to the same variables. */
16906 tree use_device_clauses;
16907 tree *pc, *uc = &use_device_clauses;
16908 for (pc = &OMP_CLAUSES (expr); *pc; )
16909 if (OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_USE_DEVICE_PTR
16910 || OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_USE_DEVICE_ADDR)
16912 *uc = *pc;
16913 *pc = OMP_CLAUSE_CHAIN (*pc);
16914 uc = &OMP_CLAUSE_CHAIN (*uc);
16916 else
16917 pc = &OMP_CLAUSE_CHAIN (*pc);
16918 *uc = NULL_TREE;
16919 *pc = use_device_clauses;
16920 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_DATA,
16921 OMP_CLAUSES (expr));
16923 break;
16924 case OMP_TEAMS:
16925 stmt = gimple_build_omp_teams (body, OMP_CLAUSES (expr));
16926 if ((ort & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
16927 gimple_omp_teams_set_host (as_a <gomp_teams *> (stmt), true);
16928 break;
16929 default:
16930 gcc_unreachable ();
16933 gimplify_seq_add_stmt (pre_p, stmt);
16934 *expr_p = NULL_TREE;
16937 /* Gimplify the gross structure of OpenACC enter/exit data, update, and OpenMP
16938 target update constructs. */
16940 static void
16941 gimplify_omp_target_update (tree *expr_p, gimple_seq *pre_p)
16943 tree expr = *expr_p;
16944 int kind;
16945 gomp_target *stmt;
16946 enum omp_region_type ort = ORT_WORKSHARE;
16948 switch (TREE_CODE (expr))
16950 case OACC_ENTER_DATA:
16951 kind = GF_OMP_TARGET_KIND_OACC_ENTER_DATA;
16952 ort = ORT_ACC;
16953 break;
16954 case OACC_EXIT_DATA:
16955 kind = GF_OMP_TARGET_KIND_OACC_EXIT_DATA;
16956 ort = ORT_ACC;
16957 break;
16958 case OACC_UPDATE:
16959 kind = GF_OMP_TARGET_KIND_OACC_UPDATE;
16960 ort = ORT_ACC;
16961 break;
16962 case OMP_TARGET_UPDATE:
16963 kind = GF_OMP_TARGET_KIND_UPDATE;
16964 break;
16965 case OMP_TARGET_ENTER_DATA:
16966 kind = GF_OMP_TARGET_KIND_ENTER_DATA;
16967 break;
16968 case OMP_TARGET_EXIT_DATA:
16969 kind = GF_OMP_TARGET_KIND_EXIT_DATA;
16970 break;
16971 default:
16972 gcc_unreachable ();
16974 gimplify_scan_omp_clauses (&OMP_STANDALONE_CLAUSES (expr), pre_p,
16975 ort, TREE_CODE (expr));
16976 gimplify_adjust_omp_clauses (pre_p, NULL, &OMP_STANDALONE_CLAUSES (expr),
16977 TREE_CODE (expr));
16978 if (TREE_CODE (expr) == OACC_UPDATE
16979 && omp_find_clause (OMP_STANDALONE_CLAUSES (expr),
16980 OMP_CLAUSE_IF_PRESENT))
16982 /* The runtime uses GOMP_MAP_{TO,FROM} to denote the if_present
16983 clause. */
16984 for (tree c = OMP_STANDALONE_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
16985 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP)
16986 switch (OMP_CLAUSE_MAP_KIND (c))
16988 case GOMP_MAP_FORCE_TO:
16989 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_TO);
16990 break;
16991 case GOMP_MAP_FORCE_FROM:
16992 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FROM);
16993 break;
16994 default:
16995 break;
16998 else if (TREE_CODE (expr) == OACC_EXIT_DATA
16999 && omp_find_clause (OMP_STANDALONE_CLAUSES (expr),
17000 OMP_CLAUSE_FINALIZE))
17002 /* Use GOMP_MAP_DELETE/GOMP_MAP_FORCE_FROM to denote "finalize"
17003 semantics. */
17004 bool have_clause = false;
17005 for (tree c = OMP_STANDALONE_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
17006 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP)
17007 switch (OMP_CLAUSE_MAP_KIND (c))
17009 case GOMP_MAP_FROM:
17010 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FORCE_FROM);
17011 have_clause = true;
17012 break;
17013 case GOMP_MAP_RELEASE:
17014 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_DELETE);
17015 have_clause = true;
17016 break;
17017 case GOMP_MAP_TO_PSET:
17018 /* Fortran arrays with descriptors must map that descriptor when
17019 doing standalone "attach" operations (in OpenACC). In that
17020 case GOMP_MAP_TO_PSET appears by itself with no preceding
17021 clause (see trans-openmp.cc:gfc_trans_omp_clauses). */
17022 break;
17023 case GOMP_MAP_POINTER:
17024 /* TODO PR92929: we may see these here, but they'll always follow
17025 one of the clauses above, and will be handled by libgomp as
17026 one group, so no handling required here. */
17027 gcc_assert (have_clause);
17028 break;
17029 case GOMP_MAP_DETACH:
17030 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FORCE_DETACH);
17031 have_clause = false;
17032 break;
17033 case GOMP_MAP_STRUCT:
17034 case GOMP_MAP_STRUCT_UNORD:
17035 have_clause = false;
17036 break;
17037 default:
17038 gcc_unreachable ();
17041 stmt = gimple_build_omp_target (NULL, kind, OMP_STANDALONE_CLAUSES (expr));
17043 gimplify_seq_add_stmt (pre_p, stmt);
17044 *expr_p = NULL_TREE;
17047 /* A subroutine of gimplify_omp_atomic. The front end is supposed to have
17048 stabilized the lhs of the atomic operation as *ADDR. Return true if
17049 EXPR is this stabilized form. */
17051 static bool
17052 goa_lhs_expr_p (tree expr, tree addr)
17054 /* Also include casts to other type variants. The C front end is fond
17055 of adding these for e.g. volatile variables. This is like
17056 STRIP_TYPE_NOPS but includes the main variant lookup. */
17057 STRIP_USELESS_TYPE_CONVERSION (expr);
17059 if (INDIRECT_REF_P (expr))
17061 expr = TREE_OPERAND (expr, 0);
17062 while (expr != addr
17063 && (CONVERT_EXPR_P (expr)
17064 || TREE_CODE (expr) == NON_LVALUE_EXPR)
17065 && TREE_CODE (expr) == TREE_CODE (addr)
17066 && types_compatible_p (TREE_TYPE (expr), TREE_TYPE (addr)))
17068 expr = TREE_OPERAND (expr, 0);
17069 addr = TREE_OPERAND (addr, 0);
17071 if (expr == addr)
17072 return true;
17073 return (TREE_CODE (addr) == ADDR_EXPR
17074 && TREE_CODE (expr) == ADDR_EXPR
17075 && TREE_OPERAND (addr, 0) == TREE_OPERAND (expr, 0));
17077 if (TREE_CODE (addr) == ADDR_EXPR && expr == TREE_OPERAND (addr, 0))
17078 return true;
17079 return false;
17082 /* Walk *EXPR_P and replace appearances of *LHS_ADDR with LHS_VAR. If an
17083 expression does not involve the lhs, evaluate it into a temporary.
17084 Return 1 if the lhs appeared as a subexpression, 0 if it did not,
17085 or -1 if an error was encountered. */
17087 static int
17088 goa_stabilize_expr (tree *expr_p, gimple_seq *pre_p, tree lhs_addr,
17089 tree lhs_var, tree &target_expr, bool rhs, int depth)
17091 tree expr = *expr_p;
17092 int saw_lhs = 0;
17094 if (goa_lhs_expr_p (expr, lhs_addr))
17096 if (pre_p)
17097 *expr_p = lhs_var;
17098 return 1;
17100 if (is_gimple_val (expr))
17101 return 0;
17103 /* Maximum depth of lhs in expression is for the
17104 __builtin_clear_padding (...), __builtin_clear_padding (...),
17105 __builtin_memcmp (&TARGET_EXPR <lhs, >, ...) == 0 ? ... : lhs; */
17106 if (++depth > 7)
17107 goto finish;
17109 switch (TREE_CODE_CLASS (TREE_CODE (expr)))
17111 case tcc_binary:
17112 case tcc_comparison:
17113 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p, lhs_addr,
17114 lhs_var, target_expr, true, depth);
17115 /* FALLTHRU */
17116 case tcc_unary:
17117 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p, lhs_addr,
17118 lhs_var, target_expr, true, depth);
17119 break;
17120 case tcc_expression:
17121 switch (TREE_CODE (expr))
17123 case TRUTH_ANDIF_EXPR:
17124 case TRUTH_ORIF_EXPR:
17125 case TRUTH_AND_EXPR:
17126 case TRUTH_OR_EXPR:
17127 case TRUTH_XOR_EXPR:
17128 case BIT_INSERT_EXPR:
17129 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
17130 lhs_addr, lhs_var, target_expr, true,
17131 depth);
17132 /* FALLTHRU */
17133 case TRUTH_NOT_EXPR:
17134 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
17135 lhs_addr, lhs_var, target_expr, true,
17136 depth);
17137 break;
17138 case MODIFY_EXPR:
17139 if (pre_p && !goa_stabilize_expr (expr_p, NULL, lhs_addr, lhs_var,
17140 target_expr, true, depth))
17141 break;
17142 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
17143 lhs_addr, lhs_var, target_expr, true,
17144 depth);
17145 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
17146 lhs_addr, lhs_var, target_expr, false,
17147 depth);
17148 break;
17149 /* FALLTHRU */
17150 case ADDR_EXPR:
17151 if (pre_p && !goa_stabilize_expr (expr_p, NULL, lhs_addr, lhs_var,
17152 target_expr, true, depth))
17153 break;
17154 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
17155 lhs_addr, lhs_var, target_expr, false,
17156 depth);
17157 break;
17158 case COMPOUND_EXPR:
17159 /* Break out any preevaluations from cp_build_modify_expr. */
17160 for (; TREE_CODE (expr) == COMPOUND_EXPR;
17161 expr = TREE_OPERAND (expr, 1))
17163 /* Special-case __builtin_clear_padding call before
17164 __builtin_memcmp. */
17165 if (TREE_CODE (TREE_OPERAND (expr, 0)) == CALL_EXPR)
17167 tree fndecl = get_callee_fndecl (TREE_OPERAND (expr, 0));
17168 if (fndecl
17169 && fndecl_built_in_p (fndecl, BUILT_IN_CLEAR_PADDING)
17170 && VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (expr, 0)))
17171 && (!pre_p
17172 || goa_stabilize_expr (&TREE_OPERAND (expr, 0), NULL,
17173 lhs_addr, lhs_var,
17174 target_expr, true, depth)))
17176 if (pre_p)
17177 *expr_p = expr;
17178 saw_lhs = goa_stabilize_expr (&TREE_OPERAND (expr, 0),
17179 pre_p, lhs_addr, lhs_var,
17180 target_expr, true, depth);
17181 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1),
17182 pre_p, lhs_addr, lhs_var,
17183 target_expr, rhs, depth);
17184 return saw_lhs;
17188 if (pre_p)
17189 gimplify_stmt (&TREE_OPERAND (expr, 0), pre_p);
17191 if (!pre_p)
17192 return goa_stabilize_expr (&expr, pre_p, lhs_addr, lhs_var,
17193 target_expr, rhs, depth);
17194 *expr_p = expr;
17195 return goa_stabilize_expr (expr_p, pre_p, lhs_addr, lhs_var,
17196 target_expr, rhs, depth);
17197 case COND_EXPR:
17198 if (!goa_stabilize_expr (&TREE_OPERAND (expr, 0), NULL, lhs_addr,
17199 lhs_var, target_expr, true, depth))
17200 break;
17201 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
17202 lhs_addr, lhs_var, target_expr, true,
17203 depth);
17204 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
17205 lhs_addr, lhs_var, target_expr, true,
17206 depth);
17207 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 2), pre_p,
17208 lhs_addr, lhs_var, target_expr, true,
17209 depth);
17210 break;
17211 case TARGET_EXPR:
17212 if (TARGET_EXPR_INITIAL (expr))
17214 if (pre_p && !goa_stabilize_expr (expr_p, NULL, lhs_addr,
17215 lhs_var, target_expr, true,
17216 depth))
17217 break;
17218 if (expr == target_expr)
17219 saw_lhs = 1;
17220 else
17222 saw_lhs = goa_stabilize_expr (&TARGET_EXPR_INITIAL (expr),
17223 pre_p, lhs_addr, lhs_var,
17224 target_expr, true, depth);
17225 if (saw_lhs && target_expr == NULL_TREE && pre_p)
17226 target_expr = expr;
17229 break;
17230 default:
17231 break;
17233 break;
17234 case tcc_reference:
17235 if (TREE_CODE (expr) == BIT_FIELD_REF
17236 || TREE_CODE (expr) == VIEW_CONVERT_EXPR)
17237 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
17238 lhs_addr, lhs_var, target_expr, true,
17239 depth);
17240 break;
17241 case tcc_vl_exp:
17242 if (TREE_CODE (expr) == CALL_EXPR)
17244 if (tree fndecl = get_callee_fndecl (expr))
17245 if (fndecl_built_in_p (fndecl, BUILT_IN_CLEAR_PADDING,
17246 BUILT_IN_MEMCMP))
17248 int nargs = call_expr_nargs (expr);
17249 for (int i = 0; i < nargs; i++)
17250 saw_lhs |= goa_stabilize_expr (&CALL_EXPR_ARG (expr, i),
17251 pre_p, lhs_addr, lhs_var,
17252 target_expr, true, depth);
17255 break;
17256 default:
17257 break;
17260 finish:
17261 if (saw_lhs == 0 && pre_p)
17263 enum gimplify_status gs;
17264 if (TREE_CODE (expr) == CALL_EXPR && VOID_TYPE_P (TREE_TYPE (expr)))
17266 gimplify_stmt (&expr, pre_p);
17267 return saw_lhs;
17269 else if (rhs)
17270 gs = gimplify_expr (expr_p, pre_p, NULL, is_gimple_val, fb_rvalue);
17271 else
17272 gs = gimplify_expr (expr_p, pre_p, NULL, is_gimple_lvalue, fb_lvalue);
17273 if (gs != GS_ALL_DONE)
17274 saw_lhs = -1;
17277 return saw_lhs;
17280 /* Gimplify an OMP_ATOMIC statement. */
17282 static enum gimplify_status
17283 gimplify_omp_atomic (tree *expr_p, gimple_seq *pre_p)
17285 tree addr = TREE_OPERAND (*expr_p, 0);
17286 tree rhs = TREE_CODE (*expr_p) == OMP_ATOMIC_READ
17287 ? NULL : TREE_OPERAND (*expr_p, 1);
17288 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (addr)));
17289 tree tmp_load;
17290 gomp_atomic_load *loadstmt;
17291 gomp_atomic_store *storestmt;
17292 tree target_expr = NULL_TREE;
17294 tmp_load = create_tmp_reg (type);
17295 if (rhs
17296 && goa_stabilize_expr (&rhs, pre_p, addr, tmp_load, target_expr,
17297 true, 0) < 0)
17298 return GS_ERROR;
17300 if (gimplify_expr (&addr, pre_p, NULL, is_gimple_val, fb_rvalue)
17301 != GS_ALL_DONE)
17302 return GS_ERROR;
17304 loadstmt = gimple_build_omp_atomic_load (tmp_load, addr,
17305 OMP_ATOMIC_MEMORY_ORDER (*expr_p));
17306 gimplify_seq_add_stmt (pre_p, loadstmt);
17307 if (rhs)
17309 /* BIT_INSERT_EXPR is not valid for non-integral bitfield
17310 representatives. Use BIT_FIELD_REF on the lhs instead. */
17311 tree rhsarg = rhs;
17312 if (TREE_CODE (rhs) == COND_EXPR)
17313 rhsarg = TREE_OPERAND (rhs, 1);
17314 if (TREE_CODE (rhsarg) == BIT_INSERT_EXPR
17315 && !INTEGRAL_TYPE_P (TREE_TYPE (tmp_load)))
17317 tree bitpos = TREE_OPERAND (rhsarg, 2);
17318 tree op1 = TREE_OPERAND (rhsarg, 1);
17319 tree bitsize;
17320 tree tmp_store = tmp_load;
17321 if (TREE_CODE (*expr_p) == OMP_ATOMIC_CAPTURE_OLD)
17322 tmp_store = get_initialized_tmp_var (tmp_load, pre_p);
17323 if (INTEGRAL_TYPE_P (TREE_TYPE (op1)))
17324 bitsize = bitsize_int (TYPE_PRECISION (TREE_TYPE (op1)));
17325 else
17326 bitsize = TYPE_SIZE (TREE_TYPE (op1));
17327 gcc_assert (TREE_OPERAND (rhsarg, 0) == tmp_load);
17328 tree t = build2_loc (EXPR_LOCATION (rhsarg),
17329 MODIFY_EXPR, void_type_node,
17330 build3_loc (EXPR_LOCATION (rhsarg),
17331 BIT_FIELD_REF, TREE_TYPE (op1),
17332 tmp_store, bitsize, bitpos), op1);
17333 if (TREE_CODE (rhs) == COND_EXPR)
17334 t = build3_loc (EXPR_LOCATION (rhs), COND_EXPR, void_type_node,
17335 TREE_OPERAND (rhs, 0), t, void_node);
17336 gimplify_and_add (t, pre_p);
17337 rhs = tmp_store;
17339 bool save_allow_rhs_cond_expr = gimplify_ctxp->allow_rhs_cond_expr;
17340 if (TREE_CODE (rhs) == COND_EXPR)
17341 gimplify_ctxp->allow_rhs_cond_expr = true;
17342 enum gimplify_status gs = gimplify_expr (&rhs, pre_p, NULL,
17343 is_gimple_val, fb_rvalue);
17344 gimplify_ctxp->allow_rhs_cond_expr = save_allow_rhs_cond_expr;
17345 if (gs != GS_ALL_DONE)
17346 return GS_ERROR;
17349 if (TREE_CODE (*expr_p) == OMP_ATOMIC_READ)
17350 rhs = tmp_load;
17351 storestmt
17352 = gimple_build_omp_atomic_store (rhs, OMP_ATOMIC_MEMORY_ORDER (*expr_p));
17353 if (TREE_CODE (*expr_p) != OMP_ATOMIC_READ && OMP_ATOMIC_WEAK (*expr_p))
17355 gimple_omp_atomic_set_weak (loadstmt);
17356 gimple_omp_atomic_set_weak (storestmt);
17358 gimplify_seq_add_stmt (pre_p, storestmt);
17359 switch (TREE_CODE (*expr_p))
17361 case OMP_ATOMIC_READ:
17362 case OMP_ATOMIC_CAPTURE_OLD:
17363 *expr_p = tmp_load;
17364 gimple_omp_atomic_set_need_value (loadstmt);
17365 break;
17366 case OMP_ATOMIC_CAPTURE_NEW:
17367 *expr_p = rhs;
17368 gimple_omp_atomic_set_need_value (storestmt);
17369 break;
17370 default:
17371 *expr_p = NULL;
17372 break;
17375 return GS_ALL_DONE;
17378 /* Gimplify a TRANSACTION_EXPR. This involves gimplification of the
17379 body, and adding some EH bits. */
17381 static enum gimplify_status
17382 gimplify_transaction (tree *expr_p, gimple_seq *pre_p)
17384 tree expr = *expr_p, temp, tbody = TRANSACTION_EXPR_BODY (expr);
17385 gimple *body_stmt;
17386 gtransaction *trans_stmt;
17387 gimple_seq body = NULL;
17388 int subcode = 0;
17390 /* Wrap the transaction body in a BIND_EXPR so we have a context
17391 where to put decls for OMP. */
17392 if (TREE_CODE (tbody) != BIND_EXPR)
17394 tree bind = build3 (BIND_EXPR, void_type_node, NULL, tbody, NULL);
17395 TREE_SIDE_EFFECTS (bind) = 1;
17396 SET_EXPR_LOCATION (bind, EXPR_LOCATION (tbody));
17397 TRANSACTION_EXPR_BODY (expr) = bind;
17400 push_gimplify_context ();
17401 temp = voidify_wrapper_expr (*expr_p, NULL);
17403 body_stmt = gimplify_and_return_first (TRANSACTION_EXPR_BODY (expr), &body);
17404 pop_gimplify_context (body_stmt);
17406 trans_stmt = gimple_build_transaction (body);
17407 if (TRANSACTION_EXPR_OUTER (expr))
17408 subcode = GTMA_IS_OUTER;
17409 else if (TRANSACTION_EXPR_RELAXED (expr))
17410 subcode = GTMA_IS_RELAXED;
17411 gimple_transaction_set_subcode (trans_stmt, subcode);
17413 gimplify_seq_add_stmt (pre_p, trans_stmt);
17415 if (temp)
17417 *expr_p = temp;
17418 return GS_OK;
17421 *expr_p = NULL_TREE;
17422 return GS_ALL_DONE;
17425 /* Gimplify an OMP_ORDERED construct. EXPR is the tree version. BODY
17426 is the OMP_BODY of the original EXPR (which has already been
17427 gimplified so it's not present in the EXPR).
17429 Return the gimplified GIMPLE_OMP_ORDERED tuple. */
17431 static gimple *
17432 gimplify_omp_ordered (tree expr, gimple_seq body)
17434 tree c, decls;
17435 int failures = 0;
17436 unsigned int i;
17437 tree source_c = NULL_TREE;
17438 tree sink_c = NULL_TREE;
17440 if (gimplify_omp_ctxp)
17442 for (c = OMP_ORDERED_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
17443 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DOACROSS
17444 && gimplify_omp_ctxp->loop_iter_var.is_empty ())
17446 error_at (OMP_CLAUSE_LOCATION (c),
17447 "%<ordered%> construct with %qs clause must be "
17448 "closely nested inside a loop with %<ordered%> clause",
17449 OMP_CLAUSE_DOACROSS_DEPEND (c) ? "depend" : "doacross");
17450 failures++;
17452 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DOACROSS
17453 && OMP_CLAUSE_DOACROSS_KIND (c) == OMP_CLAUSE_DOACROSS_SINK)
17455 bool fail = false;
17456 sink_c = c;
17457 if (OMP_CLAUSE_DECL (c) == NULL_TREE)
17458 continue; /* omp_cur_iteration - 1 */
17459 for (decls = OMP_CLAUSE_DECL (c), i = 0;
17460 decls && TREE_CODE (decls) == TREE_LIST;
17461 decls = TREE_CHAIN (decls), ++i)
17462 if (i >= gimplify_omp_ctxp->loop_iter_var.length () / 2)
17463 continue;
17464 else if (TREE_VALUE (decls)
17465 != gimplify_omp_ctxp->loop_iter_var[2 * i])
17467 error_at (OMP_CLAUSE_LOCATION (c),
17468 "variable %qE is not an iteration "
17469 "of outermost loop %d, expected %qE",
17470 TREE_VALUE (decls), i + 1,
17471 gimplify_omp_ctxp->loop_iter_var[2 * i]);
17472 fail = true;
17473 failures++;
17475 else
17476 TREE_VALUE (decls)
17477 = gimplify_omp_ctxp->loop_iter_var[2 * i + 1];
17478 if (!fail && i != gimplify_omp_ctxp->loop_iter_var.length () / 2)
17480 error_at (OMP_CLAUSE_LOCATION (c),
17481 "number of variables in %qs clause with "
17482 "%<sink%> modifier does not match number of "
17483 "iteration variables",
17484 OMP_CLAUSE_DOACROSS_DEPEND (c)
17485 ? "depend" : "doacross");
17486 failures++;
17489 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DOACROSS
17490 && OMP_CLAUSE_DOACROSS_KIND (c) == OMP_CLAUSE_DOACROSS_SOURCE)
17492 if (source_c)
17494 error_at (OMP_CLAUSE_LOCATION (c),
17495 "more than one %qs clause with %<source%> "
17496 "modifier on an %<ordered%> construct",
17497 OMP_CLAUSE_DOACROSS_DEPEND (source_c)
17498 ? "depend" : "doacross");
17499 failures++;
17501 else
17502 source_c = c;
17505 if (source_c && sink_c)
17507 error_at (OMP_CLAUSE_LOCATION (source_c),
17508 "%qs clause with %<source%> modifier specified "
17509 "together with %qs clauses with %<sink%> modifier "
17510 "on the same construct",
17511 OMP_CLAUSE_DOACROSS_DEPEND (source_c) ? "depend" : "doacross",
17512 OMP_CLAUSE_DOACROSS_DEPEND (sink_c) ? "depend" : "doacross");
17513 failures++;
17516 if (failures)
17517 return gimple_build_nop ();
17518 return gimple_build_omp_ordered (body, OMP_ORDERED_CLAUSES (expr));
17521 /* Convert the GENERIC expression tree *EXPR_P to GIMPLE. If the
17522 expression produces a value to be used as an operand inside a GIMPLE
17523 statement, the value will be stored back in *EXPR_P. This value will
17524 be a tree of class tcc_declaration, tcc_constant, tcc_reference or
17525 an SSA_NAME. The corresponding sequence of GIMPLE statements is
17526 emitted in PRE_P and POST_P.
17528 Additionally, this process may overwrite parts of the input
17529 expression during gimplification. Ideally, it should be
17530 possible to do non-destructive gimplification.
17532 EXPR_P points to the GENERIC expression to convert to GIMPLE. If
17533 the expression needs to evaluate to a value to be used as
17534 an operand in a GIMPLE statement, this value will be stored in
17535 *EXPR_P on exit. This happens when the caller specifies one
17536 of fb_lvalue or fb_rvalue fallback flags.
17538 PRE_P will contain the sequence of GIMPLE statements corresponding
17539 to the evaluation of EXPR and all the side-effects that must
17540 be executed before the main expression. On exit, the last
17541 statement of PRE_P is the core statement being gimplified. For
17542 instance, when gimplifying 'if (++a)' the last statement in
17543 PRE_P will be 'if (t.1)' where t.1 is the result of
17544 pre-incrementing 'a'.
17546 POST_P will contain the sequence of GIMPLE statements corresponding
17547 to the evaluation of all the side-effects that must be executed
17548 after the main expression. If this is NULL, the post
17549 side-effects are stored at the end of PRE_P.
17551 The reason why the output is split in two is to handle post
17552 side-effects explicitly. In some cases, an expression may have
17553 inner and outer post side-effects which need to be emitted in
17554 an order different from the one given by the recursive
17555 traversal. For instance, for the expression (*p--)++ the post
17556 side-effects of '--' must actually occur *after* the post
17557 side-effects of '++'. However, gimplification will first visit
17558 the inner expression, so if a separate POST sequence was not
17559 used, the resulting sequence would be:
17561 1 t.1 = *p
17562 2 p = p - 1
17563 3 t.2 = t.1 + 1
17564 4 *p = t.2
17566 However, the post-decrement operation in line #2 must not be
17567 evaluated until after the store to *p at line #4, so the
17568 correct sequence should be:
17570 1 t.1 = *p
17571 2 t.2 = t.1 + 1
17572 3 *p = t.2
17573 4 p = p - 1
17575 So, by specifying a separate post queue, it is possible
17576 to emit the post side-effects in the correct order.
17577 If POST_P is NULL, an internal queue will be used. Before
17578 returning to the caller, the sequence POST_P is appended to
17579 the main output sequence PRE_P.
17581 GIMPLE_TEST_F points to a function that takes a tree T and
17582 returns nonzero if T is in the GIMPLE form requested by the
17583 caller. The GIMPLE predicates are in gimple.cc.
17585 FALLBACK tells the function what sort of a temporary we want if
17586 gimplification cannot produce an expression that complies with
17587 GIMPLE_TEST_F.
17589 fb_none means that no temporary should be generated
17590 fb_rvalue means that an rvalue is OK to generate
17591 fb_lvalue means that an lvalue is OK to generate
17592 fb_either means that either is OK, but an lvalue is preferable.
17593 fb_mayfail means that gimplification may fail (in which case
17594 GS_ERROR will be returned)
17596 The return value is either GS_ERROR or GS_ALL_DONE, since this
17597 function iterates until EXPR is completely gimplified or an error
17598 occurs. */
17600 enum gimplify_status
17601 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
17602 bool (*gimple_test_f) (tree), fallback_t fallback)
17604 tree tmp;
17605 gimple_seq internal_pre = NULL;
17606 gimple_seq internal_post = NULL;
17607 tree save_expr;
17608 bool is_statement;
17609 location_t saved_location;
17610 enum gimplify_status ret;
17611 gimple_stmt_iterator pre_last_gsi, post_last_gsi;
17612 tree label;
17614 save_expr = *expr_p;
17615 if (save_expr == NULL_TREE)
17616 return GS_ALL_DONE;
17618 /* If we are gimplifying a top-level statement, PRE_P must be valid. */
17619 is_statement = gimple_test_f == is_gimple_stmt;
17620 if (is_statement)
17621 gcc_assert (pre_p);
17623 /* Consistency checks. */
17624 if (gimple_test_f == is_gimple_reg)
17625 gcc_assert (fallback & (fb_rvalue | fb_lvalue));
17626 else if (gimple_test_f == is_gimple_val
17627 || gimple_test_f == is_gimple_call_addr
17628 || gimple_test_f == is_gimple_condexpr_for_cond
17629 || gimple_test_f == is_gimple_mem_rhs
17630 || gimple_test_f == is_gimple_mem_rhs_or_call
17631 || gimple_test_f == is_gimple_reg_rhs
17632 || gimple_test_f == is_gimple_reg_rhs_or_call
17633 || gimple_test_f == is_gimple_asm_val
17634 || gimple_test_f == is_gimple_mem_ref_addr)
17635 gcc_assert (fallback & fb_rvalue);
17636 else if (gimple_test_f == is_gimple_min_lval
17637 || gimple_test_f == is_gimple_lvalue)
17638 gcc_assert (fallback & fb_lvalue);
17639 else if (gimple_test_f == is_gimple_addressable)
17640 gcc_assert (fallback & fb_either);
17641 else if (gimple_test_f == is_gimple_stmt)
17642 gcc_assert (fallback == fb_none);
17643 else
17645 /* We should have recognized the GIMPLE_TEST_F predicate to
17646 know what kind of fallback to use in case a temporary is
17647 needed to hold the value or address of *EXPR_P. */
17648 gcc_unreachable ();
17651 /* We used to check the predicate here and return immediately if it
17652 succeeds. This is wrong; the design is for gimplification to be
17653 idempotent, and for the predicates to only test for valid forms, not
17654 whether they are fully simplified. */
17655 if (pre_p == NULL)
17656 pre_p = &internal_pre;
17658 if (post_p == NULL)
17659 post_p = &internal_post;
17661 /* Remember the last statements added to PRE_P and POST_P. Every
17662 new statement added by the gimplification helpers needs to be
17663 annotated with location information. To centralize the
17664 responsibility, we remember the last statement that had been
17665 added to both queues before gimplifying *EXPR_P. If
17666 gimplification produces new statements in PRE_P and POST_P, those
17667 statements will be annotated with the same location information
17668 as *EXPR_P. */
17669 pre_last_gsi = gsi_last (*pre_p);
17670 post_last_gsi = gsi_last (*post_p);
17672 saved_location = input_location;
17673 if (save_expr != error_mark_node
17674 && EXPR_HAS_LOCATION (*expr_p))
17675 input_location = EXPR_LOCATION (*expr_p);
17677 /* Loop over the specific gimplifiers until the toplevel node
17678 remains the same. */
17681 /* Strip away as many useless type conversions as possible
17682 at the toplevel. */
17683 STRIP_USELESS_TYPE_CONVERSION (*expr_p);
17685 /* Remember the expr. */
17686 save_expr = *expr_p;
17688 /* Die, die, die, my darling. */
17689 if (error_operand_p (save_expr))
17691 ret = GS_ERROR;
17692 break;
17695 /* Do any language-specific gimplification. */
17696 ret = ((enum gimplify_status)
17697 lang_hooks.gimplify_expr (expr_p, pre_p, post_p));
17698 if (ret == GS_OK)
17700 if (*expr_p == NULL_TREE)
17701 break;
17702 if (*expr_p != save_expr)
17703 continue;
17705 else if (ret != GS_UNHANDLED)
17706 break;
17708 /* Make sure that all the cases set 'ret' appropriately. */
17709 ret = GS_UNHANDLED;
17710 switch (TREE_CODE (*expr_p))
17712 /* First deal with the special cases. */
17714 case POSTINCREMENT_EXPR:
17715 case POSTDECREMENT_EXPR:
17716 case PREINCREMENT_EXPR:
17717 case PREDECREMENT_EXPR:
17718 ret = gimplify_self_mod_expr (expr_p, pre_p, post_p,
17719 fallback != fb_none,
17720 TREE_TYPE (*expr_p));
17721 break;
17723 case VIEW_CONVERT_EXPR:
17724 if ((fallback & fb_rvalue)
17725 && is_gimple_reg_type (TREE_TYPE (*expr_p))
17726 && is_gimple_reg_type (TREE_TYPE (TREE_OPERAND (*expr_p, 0))))
17728 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
17729 post_p, is_gimple_val, fb_rvalue);
17730 recalculate_side_effects (*expr_p);
17731 break;
17733 /* Fallthru. */
17735 case ARRAY_REF:
17736 case ARRAY_RANGE_REF:
17737 case REALPART_EXPR:
17738 case IMAGPART_EXPR:
17739 case COMPONENT_REF:
17740 ret = gimplify_compound_lval (expr_p, pre_p, post_p,
17741 fallback ? fallback : fb_rvalue);
17742 break;
17744 case COND_EXPR:
17745 ret = gimplify_cond_expr (expr_p, pre_p, fallback);
17747 /* C99 code may assign to an array in a structure value of a
17748 conditional expression, and this has undefined behavior
17749 only on execution, so create a temporary if an lvalue is
17750 required. */
17751 if (fallback == fb_lvalue)
17753 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
17754 mark_addressable (*expr_p);
17755 ret = GS_OK;
17757 break;
17759 case CALL_EXPR:
17760 ret = gimplify_call_expr (expr_p, pre_p, fallback != fb_none);
17762 /* C99 code may assign to an array in a structure returned
17763 from a function, and this has undefined behavior only on
17764 execution, so create a temporary if an lvalue is
17765 required. */
17766 if (fallback == fb_lvalue)
17768 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
17769 mark_addressable (*expr_p);
17770 ret = GS_OK;
17772 break;
17774 case TREE_LIST:
17775 gcc_unreachable ();
17777 case OMP_ARRAY_SECTION:
17778 gcc_unreachable ();
17780 case COMPOUND_EXPR:
17781 ret = gimplify_compound_expr (expr_p, pre_p, fallback != fb_none);
17782 break;
17784 case COMPOUND_LITERAL_EXPR:
17785 ret = gimplify_compound_literal_expr (expr_p, pre_p,
17786 gimple_test_f, fallback);
17787 break;
17789 case MODIFY_EXPR:
17790 case INIT_EXPR:
17791 ret = gimplify_modify_expr (expr_p, pre_p, post_p,
17792 fallback != fb_none);
17793 break;
17795 case TRUTH_ANDIF_EXPR:
17796 case TRUTH_ORIF_EXPR:
17798 /* Preserve the original type of the expression and the
17799 source location of the outer expression. */
17800 tree org_type = TREE_TYPE (*expr_p);
17801 *expr_p = gimple_boolify (*expr_p);
17802 *expr_p = build3_loc (input_location, COND_EXPR,
17803 org_type, *expr_p,
17804 fold_convert_loc
17805 (input_location,
17806 org_type, boolean_true_node),
17807 fold_convert_loc
17808 (input_location,
17809 org_type, boolean_false_node));
17810 ret = GS_OK;
17811 break;
17814 case TRUTH_NOT_EXPR:
17816 tree type = TREE_TYPE (*expr_p);
17817 /* The parsers are careful to generate TRUTH_NOT_EXPR
17818 only with operands that are always zero or one.
17819 We do not fold here but handle the only interesting case
17820 manually, as fold may re-introduce the TRUTH_NOT_EXPR. */
17821 *expr_p = gimple_boolify (*expr_p);
17822 if (TYPE_PRECISION (TREE_TYPE (*expr_p)) == 1)
17823 *expr_p = build1_loc (input_location, BIT_NOT_EXPR,
17824 TREE_TYPE (*expr_p),
17825 TREE_OPERAND (*expr_p, 0));
17826 else
17827 *expr_p = build2_loc (input_location, BIT_XOR_EXPR,
17828 TREE_TYPE (*expr_p),
17829 TREE_OPERAND (*expr_p, 0),
17830 build_int_cst (TREE_TYPE (*expr_p), 1));
17831 if (!useless_type_conversion_p (type, TREE_TYPE (*expr_p)))
17832 *expr_p = fold_convert_loc (input_location, type, *expr_p);
17833 ret = GS_OK;
17834 break;
17837 case ADDR_EXPR:
17838 ret = gimplify_addr_expr (expr_p, pre_p, post_p);
17839 break;
17841 case ANNOTATE_EXPR:
17843 tree cond = TREE_OPERAND (*expr_p, 0);
17844 tree kind = TREE_OPERAND (*expr_p, 1);
17845 tree data = TREE_OPERAND (*expr_p, 2);
17846 tree type = TREE_TYPE (cond);
17847 if (!INTEGRAL_TYPE_P (type))
17849 *expr_p = cond;
17850 ret = GS_OK;
17851 break;
17853 tree tmp = create_tmp_var (type);
17854 gimplify_arg (&cond, pre_p, EXPR_LOCATION (*expr_p));
17855 gcall *call
17856 = gimple_build_call_internal (IFN_ANNOTATE, 3, cond, kind, data);
17857 gimple_call_set_lhs (call, tmp);
17858 gimplify_seq_add_stmt (pre_p, call);
17859 *expr_p = tmp;
17860 ret = GS_ALL_DONE;
17861 break;
17864 case VA_ARG_EXPR:
17865 ret = gimplify_va_arg_expr (expr_p, pre_p, post_p);
17866 break;
17868 CASE_CONVERT:
17869 if (IS_EMPTY_STMT (*expr_p))
17871 ret = GS_ALL_DONE;
17872 break;
17875 if (VOID_TYPE_P (TREE_TYPE (*expr_p))
17876 || fallback == fb_none)
17878 /* Just strip a conversion to void (or in void context) and
17879 try again. */
17880 *expr_p = TREE_OPERAND (*expr_p, 0);
17881 ret = GS_OK;
17882 break;
17885 ret = gimplify_conversion (expr_p);
17886 if (ret == GS_ERROR)
17887 break;
17888 if (*expr_p != save_expr)
17889 break;
17890 /* FALLTHRU */
17892 case FIX_TRUNC_EXPR:
17893 /* unary_expr: ... | '(' cast ')' val | ... */
17894 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
17895 is_gimple_val, fb_rvalue);
17896 recalculate_side_effects (*expr_p);
17897 break;
17899 case INDIRECT_REF:
17901 bool volatilep = TREE_THIS_VOLATILE (*expr_p);
17902 bool notrap = TREE_THIS_NOTRAP (*expr_p);
17903 tree saved_ptr_type = TREE_TYPE (TREE_OPERAND (*expr_p, 0));
17905 *expr_p = fold_indirect_ref_loc (input_location, *expr_p);
17906 if (*expr_p != save_expr)
17908 ret = GS_OK;
17909 break;
17912 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
17913 is_gimple_reg, fb_rvalue);
17914 if (ret == GS_ERROR)
17915 break;
17917 recalculate_side_effects (*expr_p);
17918 *expr_p = fold_build2_loc (input_location, MEM_REF,
17919 TREE_TYPE (*expr_p),
17920 TREE_OPERAND (*expr_p, 0),
17921 build_int_cst (saved_ptr_type, 0));
17922 TREE_THIS_VOLATILE (*expr_p) = volatilep;
17923 TREE_THIS_NOTRAP (*expr_p) = notrap;
17924 ret = GS_OK;
17925 break;
17928 /* We arrive here through the various re-gimplifcation paths. */
17929 case MEM_REF:
17930 /* First try re-folding the whole thing. */
17931 tmp = fold_binary (MEM_REF, TREE_TYPE (*expr_p),
17932 TREE_OPERAND (*expr_p, 0),
17933 TREE_OPERAND (*expr_p, 1));
17934 if (tmp)
17936 REF_REVERSE_STORAGE_ORDER (tmp)
17937 = REF_REVERSE_STORAGE_ORDER (*expr_p);
17938 *expr_p = tmp;
17939 recalculate_side_effects (*expr_p);
17940 ret = GS_OK;
17941 break;
17943 /* Avoid re-gimplifying the address operand if it is already
17944 in suitable form. Re-gimplifying would mark the address
17945 operand addressable. Always gimplify when not in SSA form
17946 as we still may have to gimplify decls with value-exprs. */
17947 if (!gimplify_ctxp || !gimple_in_ssa_p (cfun)
17948 || !is_gimple_mem_ref_addr (TREE_OPERAND (*expr_p, 0)))
17950 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
17951 is_gimple_mem_ref_addr, fb_rvalue);
17952 if (ret == GS_ERROR)
17953 break;
17955 recalculate_side_effects (*expr_p);
17956 ret = GS_ALL_DONE;
17957 break;
17959 /* Constants need not be gimplified. */
17960 case INTEGER_CST:
17961 case REAL_CST:
17962 case FIXED_CST:
17963 case STRING_CST:
17964 case COMPLEX_CST:
17965 case VECTOR_CST:
17966 /* Drop the overflow flag on constants, we do not want
17967 that in the GIMPLE IL. */
17968 if (TREE_OVERFLOW_P (*expr_p))
17969 *expr_p = drop_tree_overflow (*expr_p);
17970 ret = GS_ALL_DONE;
17971 break;
17973 case CONST_DECL:
17974 /* If we require an lvalue, such as for ADDR_EXPR, retain the
17975 CONST_DECL node. Otherwise the decl is replaceable by its
17976 value. */
17977 /* ??? Should be == fb_lvalue, but ADDR_EXPR passes fb_either. */
17978 if (fallback & fb_lvalue)
17979 ret = GS_ALL_DONE;
17980 else
17982 *expr_p = DECL_INITIAL (*expr_p);
17983 ret = GS_OK;
17985 break;
17987 case DECL_EXPR:
17988 ret = gimplify_decl_expr (expr_p, pre_p);
17989 break;
17991 case BIND_EXPR:
17992 ret = gimplify_bind_expr (expr_p, pre_p);
17993 break;
17995 case LOOP_EXPR:
17996 ret = gimplify_loop_expr (expr_p, pre_p);
17997 break;
17999 case SWITCH_EXPR:
18000 ret = gimplify_switch_expr (expr_p, pre_p);
18001 break;
18003 case EXIT_EXPR:
18004 ret = gimplify_exit_expr (expr_p);
18005 break;
18007 case GOTO_EXPR:
18008 /* If the target is not LABEL, then it is a computed jump
18009 and the target needs to be gimplified. */
18010 if (TREE_CODE (GOTO_DESTINATION (*expr_p)) != LABEL_DECL)
18012 ret = gimplify_expr (&GOTO_DESTINATION (*expr_p), pre_p,
18013 NULL, is_gimple_val, fb_rvalue);
18014 if (ret == GS_ERROR)
18015 break;
18017 gimplify_seq_add_stmt (pre_p,
18018 gimple_build_goto (GOTO_DESTINATION (*expr_p)));
18019 ret = GS_ALL_DONE;
18020 break;
18022 case PREDICT_EXPR:
18023 gimplify_seq_add_stmt (pre_p,
18024 gimple_build_predict (PREDICT_EXPR_PREDICTOR (*expr_p),
18025 PREDICT_EXPR_OUTCOME (*expr_p)));
18026 ret = GS_ALL_DONE;
18027 break;
18029 case LABEL_EXPR:
18030 ret = gimplify_label_expr (expr_p, pre_p);
18031 label = LABEL_EXPR_LABEL (*expr_p);
18032 gcc_assert (decl_function_context (label) == current_function_decl);
18034 /* If the label is used in a goto statement, or address of the label
18035 is taken, we need to unpoison all variables that were seen so far.
18036 Doing so would prevent us from reporting a false positives. */
18037 if (asan_poisoned_variables
18038 && asan_used_labels != NULL
18039 && asan_used_labels->contains (label)
18040 && !gimplify_omp_ctxp)
18041 asan_poison_variables (asan_poisoned_variables, false, pre_p);
18042 break;
18044 case CASE_LABEL_EXPR:
18045 ret = gimplify_case_label_expr (expr_p, pre_p);
18047 if (gimplify_ctxp->live_switch_vars)
18048 asan_poison_variables (gimplify_ctxp->live_switch_vars, false,
18049 pre_p);
18050 break;
18052 case RETURN_EXPR:
18053 ret = gimplify_return_expr (*expr_p, pre_p);
18054 break;
18056 case CONSTRUCTOR:
18057 /* Don't reduce this in place; let gimplify_init_constructor work its
18058 magic. Buf if we're just elaborating this for side effects, just
18059 gimplify any element that has side-effects. */
18060 if (fallback == fb_none)
18062 unsigned HOST_WIDE_INT ix;
18063 tree val;
18064 tree temp = NULL_TREE;
18065 FOR_EACH_CONSTRUCTOR_VALUE (CONSTRUCTOR_ELTS (*expr_p), ix, val)
18066 if (TREE_SIDE_EFFECTS (val))
18067 append_to_statement_list (val, &temp);
18069 *expr_p = temp;
18070 ret = temp ? GS_OK : GS_ALL_DONE;
18072 /* C99 code may assign to an array in a constructed
18073 structure or union, and this has undefined behavior only
18074 on execution, so create a temporary if an lvalue is
18075 required. */
18076 else if (fallback == fb_lvalue)
18078 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
18079 mark_addressable (*expr_p);
18080 ret = GS_OK;
18082 else
18083 ret = GS_ALL_DONE;
18084 break;
18086 /* The following are special cases that are not handled by the
18087 original GIMPLE grammar. */
18089 /* SAVE_EXPR nodes are converted into a GIMPLE identifier and
18090 eliminated. */
18091 case SAVE_EXPR:
18092 ret = gimplify_save_expr (expr_p, pre_p, post_p);
18093 break;
18095 case BIT_FIELD_REF:
18096 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
18097 post_p, is_gimple_lvalue, fb_either);
18098 recalculate_side_effects (*expr_p);
18099 break;
18101 case TARGET_MEM_REF:
18103 enum gimplify_status r0 = GS_ALL_DONE, r1 = GS_ALL_DONE;
18105 if (TMR_BASE (*expr_p))
18106 r0 = gimplify_expr (&TMR_BASE (*expr_p), pre_p,
18107 post_p, is_gimple_mem_ref_addr, fb_either);
18108 if (TMR_INDEX (*expr_p))
18109 r1 = gimplify_expr (&TMR_INDEX (*expr_p), pre_p,
18110 post_p, is_gimple_val, fb_rvalue);
18111 if (TMR_INDEX2 (*expr_p))
18112 r1 = gimplify_expr (&TMR_INDEX2 (*expr_p), pre_p,
18113 post_p, is_gimple_val, fb_rvalue);
18114 /* TMR_STEP and TMR_OFFSET are always integer constants. */
18115 ret = MIN (r0, r1);
18117 break;
18119 case NON_LVALUE_EXPR:
18120 /* This should have been stripped above. */
18121 gcc_unreachable ();
18123 case ASM_EXPR:
18124 ret = gimplify_asm_expr (expr_p, pre_p, post_p);
18125 break;
18127 case TRY_FINALLY_EXPR:
18128 case TRY_CATCH_EXPR:
18130 gimple_seq eval, cleanup;
18131 gtry *try_;
18133 /* Calls to destructors are generated automatically in FINALLY/CATCH
18134 block. They should have location as UNKNOWN_LOCATION. However,
18135 gimplify_call_expr will reset these call stmts to input_location
18136 if it finds stmt's location is unknown. To prevent resetting for
18137 destructors, we set the input_location to unknown.
18138 Note that this only affects the destructor calls in FINALLY/CATCH
18139 block, and will automatically reset to its original value by the
18140 end of gimplify_expr. */
18141 input_location = UNKNOWN_LOCATION;
18142 eval = cleanup = NULL;
18143 gimplify_and_add (TREE_OPERAND (*expr_p, 0), &eval);
18144 if (TREE_CODE (*expr_p) == TRY_FINALLY_EXPR
18145 && TREE_CODE (TREE_OPERAND (*expr_p, 1)) == EH_ELSE_EXPR)
18147 gimple_seq n = NULL, e = NULL;
18148 gimplify_and_add (TREE_OPERAND (TREE_OPERAND (*expr_p, 1),
18149 0), &n);
18150 gimplify_and_add (TREE_OPERAND (TREE_OPERAND (*expr_p, 1),
18151 1), &e);
18152 if (!gimple_seq_empty_p (n) && !gimple_seq_empty_p (e))
18154 geh_else *stmt = gimple_build_eh_else (n, e);
18155 gimple_seq_add_stmt (&cleanup, stmt);
18158 else
18159 gimplify_and_add (TREE_OPERAND (*expr_p, 1), &cleanup);
18160 /* Don't create bogus GIMPLE_TRY with empty cleanup. */
18161 if (gimple_seq_empty_p (cleanup))
18163 gimple_seq_add_seq (pre_p, eval);
18164 ret = GS_ALL_DONE;
18165 break;
18167 try_ = gimple_build_try (eval, cleanup,
18168 TREE_CODE (*expr_p) == TRY_FINALLY_EXPR
18169 ? GIMPLE_TRY_FINALLY
18170 : GIMPLE_TRY_CATCH);
18171 if (EXPR_HAS_LOCATION (save_expr))
18172 gimple_set_location (try_, EXPR_LOCATION (save_expr));
18173 else if (LOCATION_LOCUS (saved_location) != UNKNOWN_LOCATION)
18174 gimple_set_location (try_, saved_location);
18175 if (TREE_CODE (*expr_p) == TRY_CATCH_EXPR)
18176 gimple_try_set_catch_is_cleanup (try_,
18177 TRY_CATCH_IS_CLEANUP (*expr_p));
18178 gimplify_seq_add_stmt (pre_p, try_);
18179 ret = GS_ALL_DONE;
18180 break;
18183 case CLEANUP_POINT_EXPR:
18184 ret = gimplify_cleanup_point_expr (expr_p, pre_p);
18185 break;
18187 case TARGET_EXPR:
18188 ret = gimplify_target_expr (expr_p, pre_p, post_p);
18189 break;
18191 case CATCH_EXPR:
18193 gimple *c;
18194 gimple_seq handler = NULL;
18195 gimplify_and_add (CATCH_BODY (*expr_p), &handler);
18196 c = gimple_build_catch (CATCH_TYPES (*expr_p), handler);
18197 gimplify_seq_add_stmt (pre_p, c);
18198 ret = GS_ALL_DONE;
18199 break;
18202 case EH_FILTER_EXPR:
18204 gimple *ehf;
18205 gimple_seq failure = NULL;
18207 gimplify_and_add (EH_FILTER_FAILURE (*expr_p), &failure);
18208 ehf = gimple_build_eh_filter (EH_FILTER_TYPES (*expr_p), failure);
18209 copy_warning (ehf, *expr_p);
18210 gimplify_seq_add_stmt (pre_p, ehf);
18211 ret = GS_ALL_DONE;
18212 break;
18215 case OBJ_TYPE_REF:
18217 enum gimplify_status r0, r1;
18218 r0 = gimplify_expr (&OBJ_TYPE_REF_OBJECT (*expr_p), pre_p,
18219 post_p, is_gimple_val, fb_rvalue);
18220 r1 = gimplify_expr (&OBJ_TYPE_REF_EXPR (*expr_p), pre_p,
18221 post_p, is_gimple_val, fb_rvalue);
18222 TREE_SIDE_EFFECTS (*expr_p) = 0;
18223 ret = MIN (r0, r1);
18225 break;
18227 case LABEL_DECL:
18228 /* We get here when taking the address of a label. We mark
18229 the label as "forced"; meaning it can never be removed and
18230 it is a potential target for any computed goto. */
18231 FORCED_LABEL (*expr_p) = 1;
18232 ret = GS_ALL_DONE;
18233 break;
18235 case STATEMENT_LIST:
18236 ret = gimplify_statement_list (expr_p, pre_p);
18237 break;
18239 case WITH_SIZE_EXPR:
18241 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
18242 post_p == &internal_post ? NULL : post_p,
18243 gimple_test_f, fallback);
18244 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
18245 is_gimple_val, fb_rvalue);
18246 ret = GS_ALL_DONE;
18248 break;
18250 case VAR_DECL:
18251 case PARM_DECL:
18252 ret = gimplify_var_or_parm_decl (expr_p);
18253 break;
18255 case RESULT_DECL:
18256 /* When within an OMP context, notice uses of variables. */
18257 if (gimplify_omp_ctxp)
18258 omp_notice_variable (gimplify_omp_ctxp, *expr_p, true);
18259 ret = GS_ALL_DONE;
18260 break;
18262 case DEBUG_EXPR_DECL:
18263 gcc_unreachable ();
18265 case DEBUG_BEGIN_STMT:
18266 gimplify_seq_add_stmt (pre_p,
18267 gimple_build_debug_begin_stmt
18268 (TREE_BLOCK (*expr_p),
18269 EXPR_LOCATION (*expr_p)));
18270 ret = GS_ALL_DONE;
18271 *expr_p = NULL;
18272 break;
18274 case SSA_NAME:
18275 /* Allow callbacks into the gimplifier during optimization. */
18276 ret = GS_ALL_DONE;
18277 break;
18279 case OMP_PARALLEL:
18280 gimplify_omp_parallel (expr_p, pre_p);
18281 ret = GS_ALL_DONE;
18282 break;
18284 case OMP_TASK:
18285 gimplify_omp_task (expr_p, pre_p);
18286 ret = GS_ALL_DONE;
18287 break;
18289 case OMP_SIMD:
18291 /* Temporarily disable into_ssa, as scan_omp_simd
18292 which calls copy_gimple_seq_and_replace_locals can't deal
18293 with SSA_NAMEs defined outside of the body properly. */
18294 bool saved_into_ssa = gimplify_ctxp->into_ssa;
18295 gimplify_ctxp->into_ssa = false;
18296 ret = gimplify_omp_for (expr_p, pre_p);
18297 gimplify_ctxp->into_ssa = saved_into_ssa;
18298 break;
18301 case OMP_FOR:
18302 case OMP_DISTRIBUTE:
18303 case OMP_TASKLOOP:
18304 case OACC_LOOP:
18305 ret = gimplify_omp_for (expr_p, pre_p);
18306 break;
18308 case OMP_LOOP:
18309 ret = gimplify_omp_loop (expr_p, pre_p);
18310 break;
18312 case OACC_CACHE:
18313 gimplify_oacc_cache (expr_p, pre_p);
18314 ret = GS_ALL_DONE;
18315 break;
18317 case OACC_DECLARE:
18318 gimplify_oacc_declare (expr_p, pre_p);
18319 ret = GS_ALL_DONE;
18320 break;
18322 case OACC_HOST_DATA:
18323 case OACC_DATA:
18324 case OACC_KERNELS:
18325 case OACC_PARALLEL:
18326 case OACC_SERIAL:
18327 case OMP_SCOPE:
18328 case OMP_SECTIONS:
18329 case OMP_SINGLE:
18330 case OMP_TARGET:
18331 case OMP_TARGET_DATA:
18332 case OMP_TEAMS:
18333 gimplify_omp_workshare (expr_p, pre_p);
18334 ret = GS_ALL_DONE;
18335 break;
18337 case OACC_ENTER_DATA:
18338 case OACC_EXIT_DATA:
18339 case OACC_UPDATE:
18340 case OMP_TARGET_UPDATE:
18341 case OMP_TARGET_ENTER_DATA:
18342 case OMP_TARGET_EXIT_DATA:
18343 gimplify_omp_target_update (expr_p, pre_p);
18344 ret = GS_ALL_DONE;
18345 break;
18347 case OMP_SECTION:
18348 case OMP_STRUCTURED_BLOCK:
18349 case OMP_MASTER:
18350 case OMP_MASKED:
18351 case OMP_ORDERED:
18352 case OMP_CRITICAL:
18353 case OMP_SCAN:
18355 gimple_seq body = NULL;
18356 gimple *g;
18357 bool saved_in_omp_construct = in_omp_construct;
18359 in_omp_construct = true;
18360 gimplify_and_add (OMP_BODY (*expr_p), &body);
18361 in_omp_construct = saved_in_omp_construct;
18362 switch (TREE_CODE (*expr_p))
18364 case OMP_SECTION:
18365 g = gimple_build_omp_section (body);
18366 break;
18367 case OMP_STRUCTURED_BLOCK:
18368 g = gimple_build_omp_structured_block (body);
18369 break;
18370 case OMP_MASTER:
18371 g = gimple_build_omp_master (body);
18372 break;
18373 case OMP_ORDERED:
18374 g = gimplify_omp_ordered (*expr_p, body);
18375 if (OMP_BODY (*expr_p) == NULL_TREE
18376 && gimple_code (g) == GIMPLE_OMP_ORDERED)
18377 gimple_omp_ordered_standalone (g);
18378 break;
18379 case OMP_MASKED:
18380 gimplify_scan_omp_clauses (&OMP_MASKED_CLAUSES (*expr_p),
18381 pre_p, ORT_WORKSHARE, OMP_MASKED);
18382 gimplify_adjust_omp_clauses (pre_p, body,
18383 &OMP_MASKED_CLAUSES (*expr_p),
18384 OMP_MASKED);
18385 g = gimple_build_omp_masked (body,
18386 OMP_MASKED_CLAUSES (*expr_p));
18387 break;
18388 case OMP_CRITICAL:
18389 gimplify_scan_omp_clauses (&OMP_CRITICAL_CLAUSES (*expr_p),
18390 pre_p, ORT_WORKSHARE, OMP_CRITICAL);
18391 gimplify_adjust_omp_clauses (pre_p, body,
18392 &OMP_CRITICAL_CLAUSES (*expr_p),
18393 OMP_CRITICAL);
18394 g = gimple_build_omp_critical (body,
18395 OMP_CRITICAL_NAME (*expr_p),
18396 OMP_CRITICAL_CLAUSES (*expr_p));
18397 break;
18398 case OMP_SCAN:
18399 gimplify_scan_omp_clauses (&OMP_SCAN_CLAUSES (*expr_p),
18400 pre_p, ORT_WORKSHARE, OMP_SCAN);
18401 gimplify_adjust_omp_clauses (pre_p, body,
18402 &OMP_SCAN_CLAUSES (*expr_p),
18403 OMP_SCAN);
18404 g = gimple_build_omp_scan (body, OMP_SCAN_CLAUSES (*expr_p));
18405 break;
18406 default:
18407 gcc_unreachable ();
18409 gimplify_seq_add_stmt (pre_p, g);
18410 ret = GS_ALL_DONE;
18411 break;
18414 case OMP_TASKGROUP:
18416 gimple_seq body = NULL;
18418 tree *pclauses = &OMP_TASKGROUP_CLAUSES (*expr_p);
18419 bool saved_in_omp_construct = in_omp_construct;
18420 gimplify_scan_omp_clauses (pclauses, pre_p, ORT_TASKGROUP,
18421 OMP_TASKGROUP);
18422 gimplify_adjust_omp_clauses (pre_p, NULL, pclauses, OMP_TASKGROUP);
18424 in_omp_construct = true;
18425 gimplify_and_add (OMP_BODY (*expr_p), &body);
18426 in_omp_construct = saved_in_omp_construct;
18427 gimple_seq cleanup = NULL;
18428 tree fn = builtin_decl_explicit (BUILT_IN_GOMP_TASKGROUP_END);
18429 gimple *g = gimple_build_call (fn, 0);
18430 gimple_seq_add_stmt (&cleanup, g);
18431 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
18432 body = NULL;
18433 gimple_seq_add_stmt (&body, g);
18434 g = gimple_build_omp_taskgroup (body, *pclauses);
18435 gimplify_seq_add_stmt (pre_p, g);
18436 ret = GS_ALL_DONE;
18437 break;
18440 case OMP_ATOMIC:
18441 case OMP_ATOMIC_READ:
18442 case OMP_ATOMIC_CAPTURE_OLD:
18443 case OMP_ATOMIC_CAPTURE_NEW:
18444 ret = gimplify_omp_atomic (expr_p, pre_p);
18445 break;
18447 case TRANSACTION_EXPR:
18448 ret = gimplify_transaction (expr_p, pre_p);
18449 break;
18451 case TRUTH_AND_EXPR:
18452 case TRUTH_OR_EXPR:
18453 case TRUTH_XOR_EXPR:
18455 tree orig_type = TREE_TYPE (*expr_p);
18456 tree new_type, xop0, xop1;
18457 *expr_p = gimple_boolify (*expr_p);
18458 new_type = TREE_TYPE (*expr_p);
18459 if (!useless_type_conversion_p (orig_type, new_type))
18461 *expr_p = fold_convert_loc (input_location, orig_type, *expr_p);
18462 ret = GS_OK;
18463 break;
18466 /* Boolified binary truth expressions are semantically equivalent
18467 to bitwise binary expressions. Canonicalize them to the
18468 bitwise variant. */
18469 switch (TREE_CODE (*expr_p))
18471 case TRUTH_AND_EXPR:
18472 TREE_SET_CODE (*expr_p, BIT_AND_EXPR);
18473 break;
18474 case TRUTH_OR_EXPR:
18475 TREE_SET_CODE (*expr_p, BIT_IOR_EXPR);
18476 break;
18477 case TRUTH_XOR_EXPR:
18478 TREE_SET_CODE (*expr_p, BIT_XOR_EXPR);
18479 break;
18480 default:
18481 break;
18483 /* Now make sure that operands have compatible type to
18484 expression's new_type. */
18485 xop0 = TREE_OPERAND (*expr_p, 0);
18486 xop1 = TREE_OPERAND (*expr_p, 1);
18487 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop0)))
18488 TREE_OPERAND (*expr_p, 0) = fold_convert_loc (input_location,
18489 new_type,
18490 xop0);
18491 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop1)))
18492 TREE_OPERAND (*expr_p, 1) = fold_convert_loc (input_location,
18493 new_type,
18494 xop1);
18495 /* Continue classified as tcc_binary. */
18496 goto expr_2;
18499 case VEC_COND_EXPR:
18500 goto expr_3;
18502 case VEC_PERM_EXPR:
18503 /* Classified as tcc_expression. */
18504 goto expr_3;
18506 case BIT_INSERT_EXPR:
18507 /* Argument 3 is a constant. */
18508 goto expr_2;
18510 case POINTER_PLUS_EXPR:
18512 enum gimplify_status r0, r1;
18513 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
18514 post_p, is_gimple_val, fb_rvalue);
18515 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
18516 post_p, is_gimple_val, fb_rvalue);
18517 recalculate_side_effects (*expr_p);
18518 ret = MIN (r0, r1);
18519 break;
18522 default:
18523 switch (TREE_CODE_CLASS (TREE_CODE (*expr_p)))
18525 case tcc_comparison:
18526 /* Handle comparison of objects of non scalar mode aggregates
18527 with a call to memcmp. It would be nice to only have to do
18528 this for variable-sized objects, but then we'd have to allow
18529 the same nest of reference nodes we allow for MODIFY_EXPR and
18530 that's too complex.
18532 Compare scalar mode aggregates as scalar mode values. Using
18533 memcmp for them would be very inefficient at best, and is
18534 plain wrong if bitfields are involved. */
18535 if (error_operand_p (TREE_OPERAND (*expr_p, 1)))
18536 ret = GS_ERROR;
18537 else
18539 tree type = TREE_TYPE (TREE_OPERAND (*expr_p, 1));
18541 /* Vector comparisons need no boolification. */
18542 if (TREE_CODE (type) == VECTOR_TYPE)
18543 goto expr_2;
18544 else if (!AGGREGATE_TYPE_P (type))
18546 tree org_type = TREE_TYPE (*expr_p);
18547 *expr_p = gimple_boolify (*expr_p);
18548 if (!useless_type_conversion_p (org_type,
18549 TREE_TYPE (*expr_p)))
18551 *expr_p = fold_convert_loc (input_location,
18552 org_type, *expr_p);
18553 ret = GS_OK;
18555 else
18556 goto expr_2;
18558 else if (TYPE_MODE (type) != BLKmode)
18559 ret = gimplify_scalar_mode_aggregate_compare (expr_p);
18560 else
18561 ret = gimplify_variable_sized_compare (expr_p);
18563 break;
18565 /* If *EXPR_P does not need to be special-cased, handle it
18566 according to its class. */
18567 case tcc_unary:
18568 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
18569 post_p, is_gimple_val, fb_rvalue);
18570 break;
18572 case tcc_binary:
18573 expr_2:
18575 enum gimplify_status r0, r1;
18577 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
18578 post_p, is_gimple_val, fb_rvalue);
18579 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
18580 post_p, is_gimple_val, fb_rvalue);
18582 ret = MIN (r0, r1);
18583 break;
18586 expr_3:
18588 enum gimplify_status r0, r1, r2;
18590 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
18591 post_p, is_gimple_val, fb_rvalue);
18592 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
18593 post_p, is_gimple_val, fb_rvalue);
18594 r2 = gimplify_expr (&TREE_OPERAND (*expr_p, 2), pre_p,
18595 post_p, is_gimple_val, fb_rvalue);
18597 ret = MIN (MIN (r0, r1), r2);
18598 break;
18601 case tcc_declaration:
18602 case tcc_constant:
18603 ret = GS_ALL_DONE;
18604 goto dont_recalculate;
18606 default:
18607 gcc_unreachable ();
18610 recalculate_side_effects (*expr_p);
18612 dont_recalculate:
18613 break;
18616 gcc_assert (*expr_p || ret != GS_OK);
18618 while (ret == GS_OK);
18620 /* If we encountered an error_mark somewhere nested inside, either
18621 stub out the statement or propagate the error back out. */
18622 if (ret == GS_ERROR)
18624 if (is_statement)
18625 *expr_p = NULL;
18626 goto out;
18629 /* This was only valid as a return value from the langhook, which
18630 we handled. Make sure it doesn't escape from any other context. */
18631 gcc_assert (ret != GS_UNHANDLED);
18633 if (fallback == fb_none && *expr_p && !is_gimple_stmt (*expr_p))
18635 /* We aren't looking for a value, and we don't have a valid
18636 statement. If it doesn't have side-effects, throw it away.
18637 We can also get here with code such as "*&&L;", where L is
18638 a LABEL_DECL that is marked as FORCED_LABEL. */
18639 if (TREE_CODE (*expr_p) == LABEL_DECL
18640 || !TREE_SIDE_EFFECTS (*expr_p))
18641 *expr_p = NULL;
18642 else if (!TREE_THIS_VOLATILE (*expr_p))
18644 /* This is probably a _REF that contains something nested that
18645 has side effects. Recurse through the operands to find it. */
18646 enum tree_code code = TREE_CODE (*expr_p);
18648 switch (code)
18650 case COMPONENT_REF:
18651 case REALPART_EXPR:
18652 case IMAGPART_EXPR:
18653 case VIEW_CONVERT_EXPR:
18654 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
18655 gimple_test_f, fallback);
18656 break;
18658 case ARRAY_REF:
18659 case ARRAY_RANGE_REF:
18660 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
18661 gimple_test_f, fallback);
18662 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
18663 gimple_test_f, fallback);
18664 break;
18666 default:
18667 /* Anything else with side-effects must be converted to
18668 a valid statement before we get here. */
18669 gcc_unreachable ();
18672 *expr_p = NULL;
18674 else if (COMPLETE_TYPE_P (TREE_TYPE (*expr_p))
18675 && TYPE_MODE (TREE_TYPE (*expr_p)) != BLKmode
18676 && !is_empty_type (TREE_TYPE (*expr_p)))
18678 /* Historically, the compiler has treated a bare reference
18679 to a non-BLKmode volatile lvalue as forcing a load. */
18680 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (*expr_p));
18682 /* Normally, we do not want to create a temporary for a
18683 TREE_ADDRESSABLE type because such a type should not be
18684 copied by bitwise-assignment. However, we make an
18685 exception here, as all we are doing here is ensuring that
18686 we read the bytes that make up the type. We use
18687 create_tmp_var_raw because create_tmp_var will abort when
18688 given a TREE_ADDRESSABLE type. */
18689 tree tmp = create_tmp_var_raw (type, "vol");
18690 gimple_add_tmp_var (tmp);
18691 gimplify_assign (tmp, *expr_p, pre_p);
18692 *expr_p = NULL;
18694 else
18695 /* We can't do anything useful with a volatile reference to
18696 an incomplete type, so just throw it away. Likewise for
18697 a BLKmode type, since any implicit inner load should
18698 already have been turned into an explicit one by the
18699 gimplification process. */
18700 *expr_p = NULL;
18703 /* If we are gimplifying at the statement level, we're done. Tack
18704 everything together and return. */
18705 if (fallback == fb_none || is_statement)
18707 /* Since *EXPR_P has been converted into a GIMPLE tuple, clear
18708 it out for GC to reclaim it. */
18709 *expr_p = NULL_TREE;
18711 if (!gimple_seq_empty_p (internal_pre)
18712 || !gimple_seq_empty_p (internal_post))
18714 gimplify_seq_add_seq (&internal_pre, internal_post);
18715 gimplify_seq_add_seq (pre_p, internal_pre);
18718 /* The result of gimplifying *EXPR_P is going to be the last few
18719 statements in *PRE_P and *POST_P. Add location information
18720 to all the statements that were added by the gimplification
18721 helpers. */
18722 if (!gimple_seq_empty_p (*pre_p))
18723 annotate_all_with_location_after (*pre_p, pre_last_gsi, input_location);
18725 if (!gimple_seq_empty_p (*post_p))
18726 annotate_all_with_location_after (*post_p, post_last_gsi,
18727 input_location);
18729 goto out;
18732 #ifdef ENABLE_GIMPLE_CHECKING
18733 if (*expr_p)
18735 enum tree_code code = TREE_CODE (*expr_p);
18736 /* These expressions should already be in gimple IR form. */
18737 gcc_assert (code != MODIFY_EXPR
18738 && code != ASM_EXPR
18739 && code != BIND_EXPR
18740 && code != CATCH_EXPR
18741 && (code != COND_EXPR || gimplify_ctxp->allow_rhs_cond_expr)
18742 && code != EH_FILTER_EXPR
18743 && code != GOTO_EXPR
18744 && code != LABEL_EXPR
18745 && code != LOOP_EXPR
18746 && code != SWITCH_EXPR
18747 && code != TRY_FINALLY_EXPR
18748 && code != EH_ELSE_EXPR
18749 && code != OACC_PARALLEL
18750 && code != OACC_KERNELS
18751 && code != OACC_SERIAL
18752 && code != OACC_DATA
18753 && code != OACC_HOST_DATA
18754 && code != OACC_DECLARE
18755 && code != OACC_UPDATE
18756 && code != OACC_ENTER_DATA
18757 && code != OACC_EXIT_DATA
18758 && code != OACC_CACHE
18759 && code != OMP_CRITICAL
18760 && code != OMP_FOR
18761 && code != OACC_LOOP
18762 && code != OMP_MASTER
18763 && code != OMP_MASKED
18764 && code != OMP_TASKGROUP
18765 && code != OMP_ORDERED
18766 && code != OMP_PARALLEL
18767 && code != OMP_SCAN
18768 && code != OMP_SECTIONS
18769 && code != OMP_SECTION
18770 && code != OMP_STRUCTURED_BLOCK
18771 && code != OMP_SINGLE
18772 && code != OMP_SCOPE);
18774 #endif
18776 /* Otherwise we're gimplifying a subexpression, so the resulting
18777 value is interesting. If it's a valid operand that matches
18778 GIMPLE_TEST_F, we're done. Unless we are handling some
18779 post-effects internally; if that's the case, we need to copy into
18780 a temporary before adding the post-effects to POST_P. */
18781 if (gimple_seq_empty_p (internal_post) && (*gimple_test_f) (*expr_p))
18782 goto out;
18784 /* Otherwise, we need to create a new temporary for the gimplified
18785 expression. */
18787 /* We can't return an lvalue if we have an internal postqueue. The
18788 object the lvalue refers to would (probably) be modified by the
18789 postqueue; we need to copy the value out first, which means an
18790 rvalue. */
18791 if ((fallback & fb_lvalue)
18792 && gimple_seq_empty_p (internal_post)
18793 && is_gimple_addressable (*expr_p))
18795 /* An lvalue will do. Take the address of the expression, store it
18796 in a temporary, and replace the expression with an INDIRECT_REF of
18797 that temporary. */
18798 tree ref_alias_type = reference_alias_ptr_type (*expr_p);
18799 unsigned int ref_align = get_object_alignment (*expr_p);
18800 tree ref_type = TREE_TYPE (*expr_p);
18801 tmp = build_fold_addr_expr_loc (input_location, *expr_p);
18802 gimplify_expr (&tmp, pre_p, post_p, is_gimple_reg, fb_rvalue);
18803 if (TYPE_ALIGN (ref_type) != ref_align)
18804 ref_type = build_aligned_type (ref_type, ref_align);
18805 *expr_p = build2 (MEM_REF, ref_type,
18806 tmp, build_zero_cst (ref_alias_type));
18808 else if ((fallback & fb_rvalue) && is_gimple_reg_rhs_or_call (*expr_p))
18810 /* An rvalue will do. Assign the gimplified expression into a
18811 new temporary TMP and replace the original expression with
18812 TMP. First, make sure that the expression has a type so that
18813 it can be assigned into a temporary. */
18814 gcc_assert (!VOID_TYPE_P (TREE_TYPE (*expr_p)));
18815 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
18817 else
18819 #ifdef ENABLE_GIMPLE_CHECKING
18820 if (!(fallback & fb_mayfail))
18822 fprintf (stderr, "gimplification failed:\n");
18823 print_generic_expr (stderr, *expr_p);
18824 debug_tree (*expr_p);
18825 internal_error ("gimplification failed");
18827 #endif
18828 gcc_assert (fallback & fb_mayfail);
18830 /* If this is an asm statement, and the user asked for the
18831 impossible, don't die. Fail and let gimplify_asm_expr
18832 issue an error. */
18833 ret = GS_ERROR;
18834 goto out;
18837 /* Make sure the temporary matches our predicate. */
18838 gcc_assert ((*gimple_test_f) (*expr_p));
18840 if (!gimple_seq_empty_p (internal_post))
18842 annotate_all_with_location (internal_post, input_location);
18843 gimplify_seq_add_seq (pre_p, internal_post);
18846 out:
18847 input_location = saved_location;
18848 return ret;
18851 /* Like gimplify_expr but make sure the gimplified result is not itself
18852 a SSA name (but a decl if it were). Temporaries required by
18853 evaluating *EXPR_P may be still SSA names. */
18855 static enum gimplify_status
18856 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
18857 bool (*gimple_test_f) (tree), fallback_t fallback,
18858 bool allow_ssa)
18860 enum gimplify_status ret = gimplify_expr (expr_p, pre_p, post_p,
18861 gimple_test_f, fallback);
18862 if (! allow_ssa
18863 && TREE_CODE (*expr_p) == SSA_NAME)
18864 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, NULL, false);
18865 return ret;
18868 /* Look through TYPE for variable-sized objects and gimplify each such
18869 size that we find. Add to LIST_P any statements generated. */
18871 void
18872 gimplify_type_sizes (tree type, gimple_seq *list_p)
18874 if (type == NULL || type == error_mark_node)
18875 return;
18877 const bool ignored_p
18878 = TYPE_NAME (type)
18879 && TREE_CODE (TYPE_NAME (type)) == TYPE_DECL
18880 && DECL_IGNORED_P (TYPE_NAME (type));
18881 tree t;
18883 /* We first do the main variant, then copy into any other variants. */
18884 type = TYPE_MAIN_VARIANT (type);
18886 /* Avoid infinite recursion. */
18887 if (TYPE_SIZES_GIMPLIFIED (type))
18888 return;
18890 TYPE_SIZES_GIMPLIFIED (type) = 1;
18892 switch (TREE_CODE (type))
18894 case INTEGER_TYPE:
18895 case ENUMERAL_TYPE:
18896 case BOOLEAN_TYPE:
18897 case REAL_TYPE:
18898 case FIXED_POINT_TYPE:
18899 gimplify_one_sizepos (&TYPE_MIN_VALUE (type), list_p);
18900 gimplify_one_sizepos (&TYPE_MAX_VALUE (type), list_p);
18902 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
18904 TYPE_MIN_VALUE (t) = TYPE_MIN_VALUE (type);
18905 TYPE_MAX_VALUE (t) = TYPE_MAX_VALUE (type);
18907 break;
18909 case ARRAY_TYPE:
18910 /* These types may not have declarations, so handle them here. */
18911 gimplify_type_sizes (TREE_TYPE (type), list_p);
18912 gimplify_type_sizes (TYPE_DOMAIN (type), list_p);
18913 /* Ensure VLA bounds aren't removed, for -O0 they should be variables
18914 with assigned stack slots, for -O1+ -g they should be tracked
18915 by VTA. */
18916 if (!ignored_p
18917 && TYPE_DOMAIN (type)
18918 && INTEGRAL_TYPE_P (TYPE_DOMAIN (type)))
18920 t = TYPE_MIN_VALUE (TYPE_DOMAIN (type));
18921 if (t && VAR_P (t) && DECL_ARTIFICIAL (t))
18922 DECL_IGNORED_P (t) = 0;
18923 t = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
18924 if (t && VAR_P (t) && DECL_ARTIFICIAL (t))
18925 DECL_IGNORED_P (t) = 0;
18927 break;
18929 case RECORD_TYPE:
18930 case UNION_TYPE:
18931 case QUAL_UNION_TYPE:
18932 for (tree field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
18933 if (TREE_CODE (field) == FIELD_DECL)
18935 gimplify_one_sizepos (&DECL_FIELD_OFFSET (field), list_p);
18936 /* Likewise, ensure variable offsets aren't removed. */
18937 if (!ignored_p
18938 && (t = DECL_FIELD_OFFSET (field))
18939 && VAR_P (t)
18940 && DECL_ARTIFICIAL (t))
18941 DECL_IGNORED_P (t) = 0;
18942 gimplify_one_sizepos (&DECL_SIZE (field), list_p);
18943 gimplify_one_sizepos (&DECL_SIZE_UNIT (field), list_p);
18944 gimplify_type_sizes (TREE_TYPE (field), list_p);
18946 break;
18948 case POINTER_TYPE:
18949 case REFERENCE_TYPE:
18950 /* We used to recurse on the pointed-to type here, which turned out to
18951 be incorrect because its definition might refer to variables not
18952 yet initialized at this point if a forward declaration is involved.
18954 It was actually useful for anonymous pointed-to types to ensure
18955 that the sizes evaluation dominates every possible later use of the
18956 values. Restricting to such types here would be safe since there
18957 is no possible forward declaration around, but would introduce an
18958 undesirable middle-end semantic to anonymity. We then defer to
18959 front-ends the responsibility of ensuring that the sizes are
18960 evaluated both early and late enough, e.g. by attaching artificial
18961 type declarations to the tree. */
18962 break;
18964 default:
18965 break;
18968 gimplify_one_sizepos (&TYPE_SIZE (type), list_p);
18969 gimplify_one_sizepos (&TYPE_SIZE_UNIT (type), list_p);
18971 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
18973 TYPE_SIZE (t) = TYPE_SIZE (type);
18974 TYPE_SIZE_UNIT (t) = TYPE_SIZE_UNIT (type);
18975 TYPE_SIZES_GIMPLIFIED (t) = 1;
18979 /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
18980 a size or position, has had all of its SAVE_EXPRs evaluated.
18981 We add any required statements to *STMT_P. */
18983 void
18984 gimplify_one_sizepos (tree *expr_p, gimple_seq *stmt_p)
18986 tree expr = *expr_p;
18988 /* We don't do anything if the value isn't there, is constant, or contains
18989 A PLACEHOLDER_EXPR. We also don't want to do anything if it's already
18990 a VAR_DECL. If it's a VAR_DECL from another function, the gimplifier
18991 will want to replace it with a new variable, but that will cause problems
18992 if this type is from outside the function. It's OK to have that here. */
18993 if (expr == NULL_TREE
18994 || is_gimple_constant (expr)
18995 || VAR_P (expr)
18996 || CONTAINS_PLACEHOLDER_P (expr))
18997 return;
18999 *expr_p = unshare_expr (expr);
19001 /* SSA names in decl/type fields are a bad idea - they'll get reclaimed
19002 if the def vanishes. */
19003 gimplify_expr (expr_p, stmt_p, NULL, is_gimple_val, fb_rvalue, false);
19005 /* If expr wasn't already is_gimple_sizepos or is_gimple_constant from the
19006 FE, ensure that it is a VAR_DECL, otherwise we might handle some decls
19007 as gimplify_vla_decl even when they would have all sizes INTEGER_CSTs. */
19008 if (is_gimple_constant (*expr_p))
19009 *expr_p = get_initialized_tmp_var (*expr_p, stmt_p, NULL, false);
19012 /* Gimplify the body of statements of FNDECL and return a GIMPLE_BIND node
19013 containing the sequence of corresponding GIMPLE statements. If DO_PARMS
19014 is true, also gimplify the parameters. */
19016 gbind *
19017 gimplify_body (tree fndecl, bool do_parms)
19019 location_t saved_location = input_location;
19020 gimple_seq parm_stmts, parm_cleanup = NULL, seq;
19021 gimple *outer_stmt;
19022 gbind *outer_bind;
19024 timevar_push (TV_TREE_GIMPLIFY);
19026 init_tree_ssa (cfun);
19028 /* Initialize for optimize_insn_for_s{ize,peed}_p possibly called during
19029 gimplification. */
19030 default_rtl_profile ();
19032 gcc_assert (gimplify_ctxp == NULL);
19033 push_gimplify_context (true);
19035 if (flag_openacc || flag_openmp)
19037 gcc_assert (gimplify_omp_ctxp == NULL);
19038 if (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (fndecl)))
19039 gimplify_omp_ctxp = new_omp_context (ORT_IMPLICIT_TARGET);
19042 /* Unshare most shared trees in the body and in that of any nested functions.
19043 It would seem we don't have to do this for nested functions because
19044 they are supposed to be output and then the outer function gimplified
19045 first, but the g++ front end doesn't always do it that way. */
19046 unshare_body (fndecl);
19047 unvisit_body (fndecl);
19049 /* Make sure input_location isn't set to something weird. */
19050 input_location = DECL_SOURCE_LOCATION (fndecl);
19052 /* Resolve callee-copies. This has to be done before processing
19053 the body so that DECL_VALUE_EXPR gets processed correctly. */
19054 parm_stmts = do_parms ? gimplify_parameters (&parm_cleanup) : NULL;
19056 /* Gimplify the function's body. */
19057 seq = NULL;
19058 gimplify_stmt (&DECL_SAVED_TREE (fndecl), &seq);
19059 outer_stmt = gimple_seq_first_nondebug_stmt (seq);
19060 if (!outer_stmt)
19062 outer_stmt = gimple_build_nop ();
19063 gimplify_seq_add_stmt (&seq, outer_stmt);
19066 /* The body must contain exactly one statement, a GIMPLE_BIND. If this is
19067 not the case, wrap everything in a GIMPLE_BIND to make it so. */
19068 if (gimple_code (outer_stmt) == GIMPLE_BIND
19069 && (gimple_seq_first_nondebug_stmt (seq)
19070 == gimple_seq_last_nondebug_stmt (seq)))
19072 outer_bind = as_a <gbind *> (outer_stmt);
19073 if (gimple_seq_first_stmt (seq) != outer_stmt
19074 || gimple_seq_last_stmt (seq) != outer_stmt)
19076 /* If there are debug stmts before or after outer_stmt, move them
19077 inside of outer_bind body. */
19078 gimple_stmt_iterator gsi = gsi_for_stmt (outer_stmt, &seq);
19079 gimple_seq second_seq = NULL;
19080 if (gimple_seq_first_stmt (seq) != outer_stmt
19081 && gimple_seq_last_stmt (seq) != outer_stmt)
19083 second_seq = gsi_split_seq_after (gsi);
19084 gsi_remove (&gsi, false);
19086 else if (gimple_seq_first_stmt (seq) != outer_stmt)
19087 gsi_remove (&gsi, false);
19088 else
19090 gsi_remove (&gsi, false);
19091 second_seq = seq;
19092 seq = NULL;
19094 gimple_seq_add_seq_without_update (&seq,
19095 gimple_bind_body (outer_bind));
19096 gimple_seq_add_seq_without_update (&seq, second_seq);
19097 gimple_bind_set_body (outer_bind, seq);
19100 else
19101 outer_bind = gimple_build_bind (NULL_TREE, seq, NULL);
19103 DECL_SAVED_TREE (fndecl) = NULL_TREE;
19105 /* If we had callee-copies statements, insert them at the beginning
19106 of the function and clear DECL_VALUE_EXPR_P on the parameters. */
19107 if (!gimple_seq_empty_p (parm_stmts))
19109 tree parm;
19111 gimplify_seq_add_seq (&parm_stmts, gimple_bind_body (outer_bind));
19112 if (parm_cleanup)
19114 gtry *g = gimple_build_try (parm_stmts, parm_cleanup,
19115 GIMPLE_TRY_FINALLY);
19116 parm_stmts = NULL;
19117 gimple_seq_add_stmt (&parm_stmts, g);
19119 gimple_bind_set_body (outer_bind, parm_stmts);
19121 for (parm = DECL_ARGUMENTS (current_function_decl);
19122 parm; parm = DECL_CHAIN (parm))
19123 if (DECL_HAS_VALUE_EXPR_P (parm))
19125 DECL_HAS_VALUE_EXPR_P (parm) = 0;
19126 DECL_IGNORED_P (parm) = 0;
19130 if ((flag_openacc || flag_openmp || flag_openmp_simd)
19131 && gimplify_omp_ctxp)
19133 delete_omp_context (gimplify_omp_ctxp);
19134 gimplify_omp_ctxp = NULL;
19137 pop_gimplify_context (outer_bind);
19138 gcc_assert (gimplify_ctxp == NULL);
19140 if (flag_checking && !seen_error ())
19141 verify_gimple_in_seq (gimple_bind_body (outer_bind));
19143 timevar_pop (TV_TREE_GIMPLIFY);
19144 input_location = saved_location;
19146 return outer_bind;
19149 typedef char *char_p; /* For DEF_VEC_P. */
19151 /* Return whether we should exclude FNDECL from instrumentation. */
19153 static bool
19154 flag_instrument_functions_exclude_p (tree fndecl)
19156 vec<char_p> *v;
19158 v = (vec<char_p> *) flag_instrument_functions_exclude_functions;
19159 if (v && v->length () > 0)
19161 const char *name;
19162 int i;
19163 char *s;
19165 name = lang_hooks.decl_printable_name (fndecl, 1);
19166 FOR_EACH_VEC_ELT (*v, i, s)
19167 if (strstr (name, s) != NULL)
19168 return true;
19171 v = (vec<char_p> *) flag_instrument_functions_exclude_files;
19172 if (v && v->length () > 0)
19174 const char *name;
19175 int i;
19176 char *s;
19178 name = DECL_SOURCE_FILE (fndecl);
19179 FOR_EACH_VEC_ELT (*v, i, s)
19180 if (strstr (name, s) != NULL)
19181 return true;
19184 return false;
19187 /* Build a call to the instrumentation function FNCODE and add it to SEQ.
19188 If COND_VAR is not NULL, it is a boolean variable guarding the call to
19189 the instrumentation function. IF STMT is not NULL, it is a statement
19190 to be executed just before the call to the instrumentation function. */
19192 static void
19193 build_instrumentation_call (gimple_seq *seq, enum built_in_function fncode,
19194 tree cond_var, gimple *stmt)
19196 /* The instrumentation hooks aren't going to call the instrumented
19197 function and the address they receive is expected to be matchable
19198 against symbol addresses. Make sure we don't create a trampoline,
19199 in case the current function is nested. */
19200 tree this_fn_addr = build_fold_addr_expr (current_function_decl);
19201 TREE_NO_TRAMPOLINE (this_fn_addr) = 1;
19203 tree label_true, label_false;
19204 if (cond_var)
19206 label_true = create_artificial_label (UNKNOWN_LOCATION);
19207 label_false = create_artificial_label (UNKNOWN_LOCATION);
19208 gcond *cond = gimple_build_cond (EQ_EXPR, cond_var, boolean_false_node,
19209 label_true, label_false);
19210 gimplify_seq_add_stmt (seq, cond);
19211 gimplify_seq_add_stmt (seq, gimple_build_label (label_true));
19212 gimplify_seq_add_stmt (seq, gimple_build_predict (PRED_COLD_LABEL,
19213 NOT_TAKEN));
19216 if (stmt)
19217 gimplify_seq_add_stmt (seq, stmt);
19219 tree x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
19220 gcall *call = gimple_build_call (x, 1, integer_zero_node);
19221 tree tmp_var = create_tmp_var (ptr_type_node, "return_addr");
19222 gimple_call_set_lhs (call, tmp_var);
19223 gimplify_seq_add_stmt (seq, call);
19224 x = builtin_decl_implicit (fncode);
19225 call = gimple_build_call (x, 2, this_fn_addr, tmp_var);
19226 gimplify_seq_add_stmt (seq, call);
19228 if (cond_var)
19229 gimplify_seq_add_stmt (seq, gimple_build_label (label_false));
19232 /* Entry point to the gimplification pass. FNDECL is the FUNCTION_DECL
19233 node for the function we want to gimplify.
19235 Return the sequence of GIMPLE statements corresponding to the body
19236 of FNDECL. */
19238 void
19239 gimplify_function_tree (tree fndecl)
19241 gimple_seq seq;
19242 gbind *bind;
19244 gcc_assert (!gimple_body (fndecl));
19246 if (DECL_STRUCT_FUNCTION (fndecl))
19247 push_cfun (DECL_STRUCT_FUNCTION (fndecl));
19248 else
19249 push_struct_function (fndecl);
19251 /* Tentatively set PROP_gimple_lva here, and reset it in gimplify_va_arg_expr
19252 if necessary. */
19253 cfun->curr_properties |= PROP_gimple_lva;
19255 if (asan_sanitize_use_after_scope ())
19256 asan_poisoned_variables = new hash_set<tree> ();
19257 bind = gimplify_body (fndecl, true);
19258 if (asan_poisoned_variables)
19260 delete asan_poisoned_variables;
19261 asan_poisoned_variables = NULL;
19264 /* The tree body of the function is no longer needed, replace it
19265 with the new GIMPLE body. */
19266 seq = NULL;
19267 gimple_seq_add_stmt (&seq, bind);
19268 gimple_set_body (fndecl, seq);
19270 /* If we're instrumenting function entry/exit, then prepend the call to
19271 the entry hook and wrap the whole function in a TRY_FINALLY_EXPR to
19272 catch the exit hook. */
19273 /* ??? Add some way to ignore exceptions for this TFE. */
19274 if (flag_instrument_function_entry_exit
19275 && !DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT (fndecl)
19276 /* Do not instrument extern inline functions. */
19277 && !(DECL_DECLARED_INLINE_P (fndecl)
19278 && DECL_EXTERNAL (fndecl)
19279 && DECL_DISREGARD_INLINE_LIMITS (fndecl))
19280 && !flag_instrument_functions_exclude_p (fndecl))
19282 gimple_seq body = NULL, cleanup = NULL;
19283 gassign *assign;
19284 tree cond_var;
19286 /* If -finstrument-functions-once is specified, generate:
19288 static volatile bool C.0 = false;
19289 bool tmp_called;
19291 tmp_called = C.0;
19292 if (!tmp_called)
19294 C.0 = true;
19295 [call profiling enter function]
19298 without specific protection for data races. */
19299 if (flag_instrument_function_entry_exit > 1)
19301 tree first_var
19302 = build_decl (DECL_SOURCE_LOCATION (current_function_decl),
19303 VAR_DECL,
19304 create_tmp_var_name ("C"),
19305 boolean_type_node);
19306 DECL_ARTIFICIAL (first_var) = 1;
19307 DECL_IGNORED_P (first_var) = 1;
19308 TREE_STATIC (first_var) = 1;
19309 TREE_THIS_VOLATILE (first_var) = 1;
19310 TREE_USED (first_var) = 1;
19311 DECL_INITIAL (first_var) = boolean_false_node;
19312 varpool_node::add (first_var);
19314 cond_var = create_tmp_var (boolean_type_node, "tmp_called");
19315 assign = gimple_build_assign (cond_var, first_var);
19316 gimplify_seq_add_stmt (&body, assign);
19318 assign = gimple_build_assign (first_var, boolean_true_node);
19321 else
19323 cond_var = NULL_TREE;
19324 assign = NULL;
19327 build_instrumentation_call (&body, BUILT_IN_PROFILE_FUNC_ENTER,
19328 cond_var, assign);
19330 /* If -finstrument-functions-once is specified, generate:
19332 if (!tmp_called)
19333 [call profiling exit function]
19335 without specific protection for data races. */
19336 build_instrumentation_call (&cleanup, BUILT_IN_PROFILE_FUNC_EXIT,
19337 cond_var, NULL);
19339 gimple *tf = gimple_build_try (seq, cleanup, GIMPLE_TRY_FINALLY);
19340 gimplify_seq_add_stmt (&body, tf);
19341 gbind *new_bind = gimple_build_bind (NULL, body, NULL);
19343 /* Replace the current function body with the body
19344 wrapped in the try/finally TF. */
19345 seq = NULL;
19346 gimple_seq_add_stmt (&seq, new_bind);
19347 gimple_set_body (fndecl, seq);
19348 bind = new_bind;
19351 if (sanitize_flags_p (SANITIZE_THREAD)
19352 && param_tsan_instrument_func_entry_exit)
19354 gcall *call = gimple_build_call_internal (IFN_TSAN_FUNC_EXIT, 0);
19355 gimple *tf = gimple_build_try (seq, call, GIMPLE_TRY_FINALLY);
19356 gbind *new_bind = gimple_build_bind (NULL, tf, NULL);
19357 /* Replace the current function body with the body
19358 wrapped in the try/finally TF. */
19359 seq = NULL;
19360 gimple_seq_add_stmt (&seq, new_bind);
19361 gimple_set_body (fndecl, seq);
19364 DECL_SAVED_TREE (fndecl) = NULL_TREE;
19365 cfun->curr_properties |= PROP_gimple_any;
19367 pop_cfun ();
19369 dump_function (TDI_gimple, fndecl);
19372 /* Return a dummy expression of type TYPE in order to keep going after an
19373 error. */
19375 static tree
19376 dummy_object (tree type)
19378 tree t = build_int_cst (build_pointer_type (type), 0);
19379 return build2 (MEM_REF, type, t, t);
19382 /* Gimplify __builtin_va_arg, aka VA_ARG_EXPR, which is not really a
19383 builtin function, but a very special sort of operator. */
19385 enum gimplify_status
19386 gimplify_va_arg_expr (tree *expr_p, gimple_seq *pre_p,
19387 gimple_seq *post_p ATTRIBUTE_UNUSED)
19389 tree promoted_type, have_va_type;
19390 tree valist = TREE_OPERAND (*expr_p, 0);
19391 tree type = TREE_TYPE (*expr_p);
19392 tree t, tag, aptag;
19393 location_t loc = EXPR_LOCATION (*expr_p);
19395 /* Verify that valist is of the proper type. */
19396 have_va_type = TREE_TYPE (valist);
19397 if (have_va_type == error_mark_node)
19398 return GS_ERROR;
19399 have_va_type = targetm.canonical_va_list_type (have_va_type);
19400 if (have_va_type == NULL_TREE
19401 && POINTER_TYPE_P (TREE_TYPE (valist)))
19402 /* Handle 'Case 1: Not an array type' from c-common.cc/build_va_arg. */
19403 have_va_type
19404 = targetm.canonical_va_list_type (TREE_TYPE (TREE_TYPE (valist)));
19405 gcc_assert (have_va_type != NULL_TREE);
19407 /* Generate a diagnostic for requesting data of a type that cannot
19408 be passed through `...' due to type promotion at the call site. */
19409 if ((promoted_type = lang_hooks.types.type_promotes_to (type))
19410 != type)
19412 static bool gave_help;
19413 bool warned;
19414 /* Use the expansion point to handle cases such as passing bool (defined
19415 in a system header) through `...'. */
19416 location_t xloc
19417 = expansion_point_location_if_in_system_header (loc);
19419 /* Unfortunately, this is merely undefined, rather than a constraint
19420 violation, so we cannot make this an error. If this call is never
19421 executed, the program is still strictly conforming. */
19422 auto_diagnostic_group d;
19423 warned = warning_at (xloc, 0,
19424 "%qT is promoted to %qT when passed through %<...%>",
19425 type, promoted_type);
19426 if (!gave_help && warned)
19428 gave_help = true;
19429 inform (xloc, "(so you should pass %qT not %qT to %<va_arg%>)",
19430 promoted_type, type);
19433 /* We can, however, treat "undefined" any way we please.
19434 Call abort to encourage the user to fix the program. */
19435 if (warned)
19436 inform (xloc, "if this code is reached, the program will abort");
19437 /* Before the abort, allow the evaluation of the va_list
19438 expression to exit or longjmp. */
19439 gimplify_and_add (valist, pre_p);
19440 t = build_call_expr_loc (loc,
19441 builtin_decl_implicit (BUILT_IN_TRAP), 0);
19442 gimplify_and_add (t, pre_p);
19444 /* This is dead code, but go ahead and finish so that the
19445 mode of the result comes out right. */
19446 *expr_p = dummy_object (type);
19447 return GS_ALL_DONE;
19450 tag = build_int_cst (build_pointer_type (type), 0);
19451 aptag = build_int_cst (TREE_TYPE (valist), 0);
19453 *expr_p = build_call_expr_internal_loc (loc, IFN_VA_ARG, type, 3,
19454 valist, tag, aptag);
19456 /* Clear the tentatively set PROP_gimple_lva, to indicate that IFN_VA_ARG
19457 needs to be expanded. */
19458 cfun->curr_properties &= ~PROP_gimple_lva;
19460 return GS_OK;
19463 /* Build a new GIMPLE_ASSIGN tuple and append it to the end of *SEQ_P.
19465 DST/SRC are the destination and source respectively. You can pass
19466 ungimplified trees in DST or SRC, in which case they will be
19467 converted to a gimple operand if necessary.
19469 This function returns the newly created GIMPLE_ASSIGN tuple. */
19471 gimple *
19472 gimplify_assign (tree dst, tree src, gimple_seq *seq_p)
19474 tree t = build2 (MODIFY_EXPR, TREE_TYPE (dst), dst, src);
19475 gimplify_and_add (t, seq_p);
19476 ggc_free (t);
19477 return gimple_seq_last_stmt (*seq_p);
19480 inline hashval_t
19481 gimplify_hasher::hash (const elt_t *p)
19483 tree t = p->val;
19484 return iterative_hash_expr (t, 0);
19487 inline bool
19488 gimplify_hasher::equal (const elt_t *p1, const elt_t *p2)
19490 tree t1 = p1->val;
19491 tree t2 = p2->val;
19492 enum tree_code code = TREE_CODE (t1);
19494 if (TREE_CODE (t2) != code
19495 || TREE_TYPE (t1) != TREE_TYPE (t2))
19496 return false;
19498 if (!operand_equal_p (t1, t2, 0))
19499 return false;
19501 /* Only allow them to compare equal if they also hash equal; otherwise
19502 results are nondeterminate, and we fail bootstrap comparison. */
19503 gcc_checking_assert (hash (p1) == hash (p2));
19505 return true;