For obj-c stage-final re-use the checksum from the previous stage
[official-gcc.git] / gcc / gimplify.c
blob39f5b973d18132c7f056bac4fbe0bee7f3afe43f
1 /* Tree lowering pass. This pass converts the GENERIC functions-as-trees
2 tree representation into the GIMPLE form.
3 Copyright (C) 2002-2021 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 "alias.h"
40 #include "fold-const.h"
41 #include "calls.h"
42 #include "varasm.h"
43 #include "stmt.h"
44 #include "expr.h"
45 #include "gimple-fold.h"
46 #include "tree-eh.h"
47 #include "gimplify.h"
48 #include "gimple-iterator.h"
49 #include "stor-layout.h"
50 #include "print-tree.h"
51 #include "tree-iterator.h"
52 #include "tree-inline.h"
53 #include "langhooks.h"
54 #include "tree-cfg.h"
55 #include "tree-ssa.h"
56 #include "omp-general.h"
57 #include "omp-low.h"
58 #include "gimple-low.h"
59 #include "gomp-constants.h"
60 #include "splay-tree.h"
61 #include "gimple-walk.h"
62 #include "langhooks-def.h" /* FIXME: for lhd_set_decl_assembler_name */
63 #include "builtins.h"
64 #include "stringpool.h"
65 #include "attribs.h"
66 #include "asan.h"
67 #include "dbgcnt.h"
68 #include "omp-offload.h"
69 #include "context.h"
70 #include "tree-nested.h"
72 /* Hash set of poisoned variables in a bind expr. */
73 static hash_set<tree> *asan_poisoned_variables = NULL;
75 enum gimplify_omp_var_data
77 GOVD_SEEN = 0x000001,
78 GOVD_EXPLICIT = 0x000002,
79 GOVD_SHARED = 0x000004,
80 GOVD_PRIVATE = 0x000008,
81 GOVD_FIRSTPRIVATE = 0x000010,
82 GOVD_LASTPRIVATE = 0x000020,
83 GOVD_REDUCTION = 0x000040,
84 GOVD_LOCAL = 0x00080,
85 GOVD_MAP = 0x000100,
86 GOVD_DEBUG_PRIVATE = 0x000200,
87 GOVD_PRIVATE_OUTER_REF = 0x000400,
88 GOVD_LINEAR = 0x000800,
89 GOVD_ALIGNED = 0x001000,
91 /* Flag for GOVD_MAP: don't copy back. */
92 GOVD_MAP_TO_ONLY = 0x002000,
94 /* Flag for GOVD_LINEAR or GOVD_LASTPRIVATE: no outer reference. */
95 GOVD_LINEAR_LASTPRIVATE_NO_OUTER = 0x004000,
97 GOVD_MAP_0LEN_ARRAY = 0x008000,
99 /* Flag for GOVD_MAP, if it is always, to or always, tofrom mapping. */
100 GOVD_MAP_ALWAYS_TO = 0x010000,
102 /* Flag for shared vars that are or might be stored to in the region. */
103 GOVD_WRITTEN = 0x020000,
105 /* Flag for GOVD_MAP, if it is a forced mapping. */
106 GOVD_MAP_FORCE = 0x040000,
108 /* Flag for GOVD_MAP: must be present already. */
109 GOVD_MAP_FORCE_PRESENT = 0x080000,
111 /* Flag for GOVD_MAP: only allocate. */
112 GOVD_MAP_ALLOC_ONLY = 0x100000,
114 /* Flag for GOVD_MAP: only copy back. */
115 GOVD_MAP_FROM_ONLY = 0x200000,
117 GOVD_NONTEMPORAL = 0x400000,
119 /* Flag for GOVD_LASTPRIVATE: conditional modifier. */
120 GOVD_LASTPRIVATE_CONDITIONAL = 0x800000,
122 GOVD_CONDTEMP = 0x1000000,
124 /* Flag for GOVD_REDUCTION: inscan seen in {in,ex}clusive clause. */
125 GOVD_REDUCTION_INSCAN = 0x2000000,
127 /* Flag for GOVD_MAP: (struct) vars that have pointer attachments for
128 fields. */
129 GOVD_MAP_HAS_ATTACHMENTS = 0x4000000,
131 /* Flag for GOVD_FIRSTPRIVATE: OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT. */
132 GOVD_FIRSTPRIVATE_IMPLICIT = 0x8000000,
134 GOVD_DATA_SHARE_CLASS = (GOVD_SHARED | GOVD_PRIVATE | GOVD_FIRSTPRIVATE
135 | GOVD_LASTPRIVATE | GOVD_REDUCTION | GOVD_LINEAR
136 | GOVD_LOCAL)
140 enum omp_region_type
142 ORT_WORKSHARE = 0x00,
143 ORT_TASKGROUP = 0x01,
144 ORT_SIMD = 0x04,
146 ORT_PARALLEL = 0x08,
147 ORT_COMBINED_PARALLEL = ORT_PARALLEL | 1,
149 ORT_TASK = 0x10,
150 ORT_UNTIED_TASK = ORT_TASK | 1,
151 ORT_TASKLOOP = ORT_TASK | 2,
152 ORT_UNTIED_TASKLOOP = ORT_UNTIED_TASK | 2,
154 ORT_TEAMS = 0x20,
155 ORT_COMBINED_TEAMS = ORT_TEAMS | 1,
156 ORT_HOST_TEAMS = ORT_TEAMS | 2,
157 ORT_COMBINED_HOST_TEAMS = ORT_COMBINED_TEAMS | 2,
159 /* Data region. */
160 ORT_TARGET_DATA = 0x40,
162 /* Data region with offloading. */
163 ORT_TARGET = 0x80,
164 ORT_COMBINED_TARGET = ORT_TARGET | 1,
165 ORT_IMPLICIT_TARGET = ORT_TARGET | 2,
167 /* OpenACC variants. */
168 ORT_ACC = 0x100, /* A generic OpenACC region. */
169 ORT_ACC_DATA = ORT_ACC | ORT_TARGET_DATA, /* Data construct. */
170 ORT_ACC_PARALLEL = ORT_ACC | ORT_TARGET, /* Parallel construct */
171 ORT_ACC_KERNELS = ORT_ACC | ORT_TARGET | 2, /* Kernels construct. */
172 ORT_ACC_SERIAL = ORT_ACC | ORT_TARGET | 4, /* Serial construct. */
173 ORT_ACC_HOST_DATA = ORT_ACC | ORT_TARGET_DATA | 2, /* Host data. */
175 /* Dummy OpenMP region, used to disable expansion of
176 DECL_VALUE_EXPRs in taskloop pre body. */
177 ORT_NONE = 0x200
180 /* Gimplify hashtable helper. */
182 struct gimplify_hasher : free_ptr_hash <elt_t>
184 static inline hashval_t hash (const elt_t *);
185 static inline bool equal (const elt_t *, const elt_t *);
188 struct gimplify_ctx
190 struct gimplify_ctx *prev_context;
192 vec<gbind *> bind_expr_stack;
193 tree temps;
194 gimple_seq conditional_cleanups;
195 tree exit_label;
196 tree return_temp;
198 vec<tree> case_labels;
199 hash_set<tree> *live_switch_vars;
200 /* The formal temporary table. Should this be persistent? */
201 hash_table<gimplify_hasher> *temp_htab;
203 int conditions;
204 unsigned into_ssa : 1;
205 unsigned allow_rhs_cond_expr : 1;
206 unsigned in_cleanup_point_expr : 1;
207 unsigned keep_stack : 1;
208 unsigned save_stack : 1;
209 unsigned in_switch_expr : 1;
212 enum gimplify_defaultmap_kind
214 GDMK_SCALAR,
215 GDMK_AGGREGATE,
216 GDMK_ALLOCATABLE,
217 GDMK_POINTER
220 struct gimplify_omp_ctx
222 struct gimplify_omp_ctx *outer_context;
223 splay_tree variables;
224 hash_set<tree> *privatized_types;
225 tree clauses;
226 /* Iteration variables in an OMP_FOR. */
227 vec<tree> loop_iter_var;
228 location_t location;
229 enum omp_clause_default_kind default_kind;
230 enum omp_region_type region_type;
231 enum tree_code code;
232 bool combined_loop;
233 bool distribute;
234 bool target_firstprivatize_array_bases;
235 bool add_safelen1;
236 bool order_concurrent;
237 bool has_depend;
238 bool in_for_exprs;
239 int defaultmap[4];
242 static struct gimplify_ctx *gimplify_ctxp;
243 static struct gimplify_omp_ctx *gimplify_omp_ctxp;
244 static bool in_omp_construct;
246 /* Forward declaration. */
247 static enum gimplify_status gimplify_compound_expr (tree *, gimple_seq *, bool);
248 static hash_map<tree, tree> *oacc_declare_returns;
249 static enum gimplify_status gimplify_expr (tree *, gimple_seq *, gimple_seq *,
250 bool (*) (tree), fallback_t, bool);
252 /* Shorter alias name for the above function for use in gimplify.c
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_AGGREGATE] = GOVD_MAP;
465 c->defaultmap[GDMK_ALLOCATABLE] = GOVD_MAP;
466 c->defaultmap[GDMK_POINTER] = GOVD_MAP;
468 return c;
471 /* Destroy an omp construct that deals with variable remapping. */
473 static void
474 delete_omp_context (struct gimplify_omp_ctx *c)
476 splay_tree_delete (c->variables);
477 delete c->privatized_types;
478 c->loop_iter_var.release ();
479 XDELETE (c);
482 static void omp_add_variable (struct gimplify_omp_ctx *, tree, unsigned int);
483 static bool omp_notice_variable (struct gimplify_omp_ctx *, tree, bool);
485 /* Both gimplify the statement T and append it to *SEQ_P. This function
486 behaves exactly as gimplify_stmt, but you don't have to pass T as a
487 reference. */
489 void
490 gimplify_and_add (tree t, gimple_seq *seq_p)
492 gimplify_stmt (&t, seq_p);
495 /* Gimplify statement T into sequence *SEQ_P, and return the first
496 tuple in the sequence of generated tuples for this statement.
497 Return NULL if gimplifying T produced no tuples. */
499 static gimple *
500 gimplify_and_return_first (tree t, gimple_seq *seq_p)
502 gimple_stmt_iterator last = gsi_last (*seq_p);
504 gimplify_and_add (t, seq_p);
506 if (!gsi_end_p (last))
508 gsi_next (&last);
509 return gsi_stmt (last);
511 else
512 return gimple_seq_first_stmt (*seq_p);
515 /* Returns true iff T is a valid RHS for an assignment to an un-renamed
516 LHS, or for a call argument. */
518 static bool
519 is_gimple_mem_rhs (tree t)
521 /* If we're dealing with a renamable type, either source or dest must be
522 a renamed variable. */
523 if (is_gimple_reg_type (TREE_TYPE (t)))
524 return is_gimple_val (t);
525 else
526 return is_gimple_val (t) || is_gimple_lvalue (t);
529 /* Return true if T is a CALL_EXPR or an expression that can be
530 assigned to a temporary. Note that this predicate should only be
531 used during gimplification. See the rationale for this in
532 gimplify_modify_expr. */
534 static bool
535 is_gimple_reg_rhs_or_call (tree t)
537 return (get_gimple_rhs_class (TREE_CODE (t)) != GIMPLE_INVALID_RHS
538 || TREE_CODE (t) == CALL_EXPR);
541 /* Return true if T is a valid memory RHS or a CALL_EXPR. Note that
542 this predicate should only be used during gimplification. See the
543 rationale for this in gimplify_modify_expr. */
545 static bool
546 is_gimple_mem_rhs_or_call (tree t)
548 /* If we're dealing with a renamable type, either source or dest must be
549 a renamed variable. */
550 if (is_gimple_reg_type (TREE_TYPE (t)))
551 return is_gimple_val (t);
552 else
553 return (is_gimple_val (t)
554 || is_gimple_lvalue (t)
555 || TREE_CLOBBER_P (t)
556 || TREE_CODE (t) == CALL_EXPR);
559 /* Create a temporary with a name derived from VAL. Subroutine of
560 lookup_tmp_var; nobody else should call this function. */
562 static inline tree
563 create_tmp_from_val (tree val)
565 /* Drop all qualifiers and address-space information from the value type. */
566 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (val));
567 tree var = create_tmp_var (type, get_name (val));
568 return var;
571 /* Create a temporary to hold the value of VAL. If IS_FORMAL, try to reuse
572 an existing expression temporary. */
574 static tree
575 lookup_tmp_var (tree val, bool is_formal)
577 tree ret;
579 /* If not optimizing, never really reuse a temporary. local-alloc
580 won't allocate any variable that is used in more than one basic
581 block, which means it will go into memory, causing much extra
582 work in reload and final and poorer code generation, outweighing
583 the extra memory allocation here. */
584 if (!optimize || !is_formal || TREE_SIDE_EFFECTS (val))
585 ret = create_tmp_from_val (val);
586 else
588 elt_t elt, *elt_p;
589 elt_t **slot;
591 elt.val = val;
592 if (!gimplify_ctxp->temp_htab)
593 gimplify_ctxp->temp_htab = new hash_table<gimplify_hasher> (1000);
594 slot = gimplify_ctxp->temp_htab->find_slot (&elt, INSERT);
595 if (*slot == NULL)
597 elt_p = XNEW (elt_t);
598 elt_p->val = val;
599 elt_p->temp = ret = create_tmp_from_val (val);
600 *slot = elt_p;
602 else
604 elt_p = *slot;
605 ret = elt_p->temp;
609 return ret;
612 /* Helper for get_formal_tmp_var and get_initialized_tmp_var. */
614 static tree
615 internal_get_tmp_var (tree val, gimple_seq *pre_p, gimple_seq *post_p,
616 bool is_formal, bool allow_ssa)
618 tree t, mod;
620 /* Notice that we explicitly allow VAL to be a CALL_EXPR so that we
621 can create an INIT_EXPR and convert it into a GIMPLE_CALL below. */
622 gimplify_expr (&val, pre_p, post_p, is_gimple_reg_rhs_or_call,
623 fb_rvalue);
625 if (allow_ssa
626 && gimplify_ctxp->into_ssa
627 && is_gimple_reg_type (TREE_TYPE (val)))
629 t = make_ssa_name (TYPE_MAIN_VARIANT (TREE_TYPE (val)));
630 if (! gimple_in_ssa_p (cfun))
632 const char *name = get_name (val);
633 if (name)
634 SET_SSA_NAME_VAR_OR_IDENTIFIER (t, create_tmp_var_name (name));
637 else
638 t = lookup_tmp_var (val, is_formal);
640 mod = build2 (INIT_EXPR, TREE_TYPE (t), t, unshare_expr (val));
642 SET_EXPR_LOCATION (mod, EXPR_LOC_OR_LOC (val, input_location));
644 /* gimplify_modify_expr might want to reduce this further. */
645 gimplify_and_add (mod, pre_p);
646 ggc_free (mod);
648 return t;
651 /* Return a formal temporary variable initialized with VAL. PRE_P is as
652 in gimplify_expr. Only use this function if:
654 1) The value of the unfactored expression represented by VAL will not
655 change between the initialization and use of the temporary, and
656 2) The temporary will not be otherwise modified.
658 For instance, #1 means that this is inappropriate for SAVE_EXPR temps,
659 and #2 means it is inappropriate for && temps.
661 For other cases, use get_initialized_tmp_var instead. */
663 tree
664 get_formal_tmp_var (tree val, gimple_seq *pre_p)
666 return internal_get_tmp_var (val, pre_p, NULL, true, true);
669 /* Return a temporary variable initialized with VAL. PRE_P and POST_P
670 are as in gimplify_expr. */
672 tree
673 get_initialized_tmp_var (tree val, gimple_seq *pre_p,
674 gimple_seq *post_p /* = NULL */,
675 bool allow_ssa /* = true */)
677 return internal_get_tmp_var (val, pre_p, post_p, false, allow_ssa);
680 /* Declare all the variables in VARS in SCOPE. If DEBUG_INFO is true,
681 generate debug info for them; otherwise don't. */
683 void
684 declare_vars (tree vars, gimple *gs, bool debug_info)
686 tree last = vars;
687 if (last)
689 tree temps, block;
691 gbind *scope = as_a <gbind *> (gs);
693 temps = nreverse (last);
695 block = gimple_bind_block (scope);
696 gcc_assert (!block || TREE_CODE (block) == BLOCK);
697 if (!block || !debug_info)
699 DECL_CHAIN (last) = gimple_bind_vars (scope);
700 gimple_bind_set_vars (scope, temps);
702 else
704 /* We need to attach the nodes both to the BIND_EXPR and to its
705 associated BLOCK for debugging purposes. The key point here
706 is that the BLOCK_VARS of the BIND_EXPR_BLOCK of a BIND_EXPR
707 is a subchain of the BIND_EXPR_VARS of the BIND_EXPR. */
708 if (BLOCK_VARS (block))
709 BLOCK_VARS (block) = chainon (BLOCK_VARS (block), temps);
710 else
712 gimple_bind_set_vars (scope,
713 chainon (gimple_bind_vars (scope), temps));
714 BLOCK_VARS (block) = temps;
720 /* For VAR a VAR_DECL of variable size, try to find a constant upper bound
721 for the size and adjust DECL_SIZE/DECL_SIZE_UNIT accordingly. Abort if
722 no such upper bound can be obtained. */
724 static void
725 force_constant_size (tree var)
727 /* The only attempt we make is by querying the maximum size of objects
728 of the variable's type. */
730 HOST_WIDE_INT max_size;
732 gcc_assert (VAR_P (var));
734 max_size = max_int_size_in_bytes (TREE_TYPE (var));
736 gcc_assert (max_size >= 0);
738 DECL_SIZE_UNIT (var)
739 = build_int_cst (TREE_TYPE (DECL_SIZE_UNIT (var)), max_size);
740 DECL_SIZE (var)
741 = build_int_cst (TREE_TYPE (DECL_SIZE (var)), max_size * BITS_PER_UNIT);
744 /* Push the temporary variable TMP into the current binding. */
746 void
747 gimple_add_tmp_var_fn (struct function *fn, tree tmp)
749 gcc_assert (!DECL_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
751 /* Later processing assumes that the object size is constant, which might
752 not be true at this point. Force the use of a constant upper bound in
753 this case. */
754 if (!tree_fits_poly_uint64_p (DECL_SIZE_UNIT (tmp)))
755 force_constant_size (tmp);
757 DECL_CONTEXT (tmp) = fn->decl;
758 DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
760 record_vars_into (tmp, fn->decl);
763 /* Push the temporary variable TMP into the current binding. */
765 void
766 gimple_add_tmp_var (tree tmp)
768 gcc_assert (!DECL_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
770 /* Later processing assumes that the object size is constant, which might
771 not be true at this point. Force the use of a constant upper bound in
772 this case. */
773 if (!tree_fits_poly_uint64_p (DECL_SIZE_UNIT (tmp)))
774 force_constant_size (tmp);
776 DECL_CONTEXT (tmp) = current_function_decl;
777 DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
779 if (gimplify_ctxp)
781 DECL_CHAIN (tmp) = gimplify_ctxp->temps;
782 gimplify_ctxp->temps = tmp;
784 /* Mark temporaries local within the nearest enclosing parallel. */
785 if (gimplify_omp_ctxp)
787 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
788 int flag = GOVD_LOCAL | GOVD_SEEN;
789 while (ctx
790 && (ctx->region_type == ORT_WORKSHARE
791 || ctx->region_type == ORT_TASKGROUP
792 || ctx->region_type == ORT_SIMD
793 || ctx->region_type == ORT_ACC))
795 if (ctx->region_type == ORT_SIMD
796 && TREE_ADDRESSABLE (tmp)
797 && !TREE_STATIC (tmp))
799 if (TREE_CODE (DECL_SIZE_UNIT (tmp)) != INTEGER_CST)
800 ctx->add_safelen1 = true;
801 else if (ctx->in_for_exprs)
802 flag = GOVD_PRIVATE;
803 else
804 flag = GOVD_PRIVATE | GOVD_SEEN;
805 break;
807 ctx = ctx->outer_context;
809 if (ctx)
810 omp_add_variable (ctx, tmp, flag);
813 else if (cfun)
814 record_vars (tmp);
815 else
817 gimple_seq body_seq;
819 /* This case is for nested functions. We need to expose the locals
820 they create. */
821 body_seq = gimple_body (current_function_decl);
822 declare_vars (tmp, gimple_seq_first_stmt (body_seq), false);
828 /* This page contains routines to unshare tree nodes, i.e. to duplicate tree
829 nodes that are referenced more than once in GENERIC functions. This is
830 necessary because gimplification (translation into GIMPLE) is performed
831 by modifying tree nodes in-place, so gimplication of a shared node in a
832 first context could generate an invalid GIMPLE form in a second context.
834 This is achieved with a simple mark/copy/unmark algorithm that walks the
835 GENERIC representation top-down, marks nodes with TREE_VISITED the first
836 time it encounters them, duplicates them if they already have TREE_VISITED
837 set, and finally removes the TREE_VISITED marks it has set.
839 The algorithm works only at the function level, i.e. it generates a GENERIC
840 representation of a function with no nodes shared within the function when
841 passed a GENERIC function (except for nodes that are allowed to be shared).
843 At the global level, it is also necessary to unshare tree nodes that are
844 referenced in more than one function, for the same aforementioned reason.
845 This requires some cooperation from the front-end. There are 2 strategies:
847 1. Manual unsharing. The front-end needs to call unshare_expr on every
848 expression that might end up being shared across functions.
850 2. Deep unsharing. This is an extension of regular unsharing. Instead
851 of calling unshare_expr on expressions that might be shared across
852 functions, the front-end pre-marks them with TREE_VISITED. This will
853 ensure that they are unshared on the first reference within functions
854 when the regular unsharing algorithm runs. The counterpart is that
855 this algorithm must look deeper than for manual unsharing, which is
856 specified by LANG_HOOKS_DEEP_UNSHARING.
858 If there are only few specific cases of node sharing across functions, it is
859 probably easier for a front-end to unshare the expressions manually. On the
860 contrary, if the expressions generated at the global level are as widespread
861 as expressions generated within functions, deep unsharing is very likely the
862 way to go. */
864 /* Similar to copy_tree_r but do not copy SAVE_EXPR or TARGET_EXPR nodes.
865 These nodes model computations that must be done once. If we were to
866 unshare something like SAVE_EXPR(i++), the gimplification process would
867 create wrong code. However, if DATA is non-null, it must hold a pointer
868 set that is used to unshare the subtrees of these nodes. */
870 static tree
871 mostly_copy_tree_r (tree *tp, int *walk_subtrees, void *data)
873 tree t = *tp;
874 enum tree_code code = TREE_CODE (t);
876 /* Do not copy SAVE_EXPR, TARGET_EXPR or BIND_EXPR nodes themselves, but
877 copy their subtrees if we can make sure to do it only once. */
878 if (code == SAVE_EXPR || code == TARGET_EXPR || code == BIND_EXPR)
880 if (data && !((hash_set<tree> *)data)->add (t))
882 else
883 *walk_subtrees = 0;
886 /* Stop at types, decls, constants like copy_tree_r. */
887 else if (TREE_CODE_CLASS (code) == tcc_type
888 || TREE_CODE_CLASS (code) == tcc_declaration
889 || TREE_CODE_CLASS (code) == tcc_constant)
890 *walk_subtrees = 0;
892 /* Cope with the statement expression extension. */
893 else if (code == STATEMENT_LIST)
896 /* Leave the bulk of the work to copy_tree_r itself. */
897 else
898 copy_tree_r (tp, walk_subtrees, NULL);
900 return NULL_TREE;
903 /* Callback for walk_tree to unshare most of the shared trees rooted at *TP.
904 If *TP has been visited already, then *TP is deeply copied by calling
905 mostly_copy_tree_r. DATA is passed to mostly_copy_tree_r unmodified. */
907 static tree
908 copy_if_shared_r (tree *tp, int *walk_subtrees, void *data)
910 tree t = *tp;
911 enum tree_code code = TREE_CODE (t);
913 /* Skip types, decls, and constants. But we do want to look at their
914 types and the bounds of types. Mark them as visited so we properly
915 unmark their subtrees on the unmark pass. If we've already seen them,
916 don't look down further. */
917 if (TREE_CODE_CLASS (code) == tcc_type
918 || TREE_CODE_CLASS (code) == tcc_declaration
919 || TREE_CODE_CLASS (code) == tcc_constant)
921 if (TREE_VISITED (t))
922 *walk_subtrees = 0;
923 else
924 TREE_VISITED (t) = 1;
927 /* If this node has been visited already, unshare it and don't look
928 any deeper. */
929 else if (TREE_VISITED (t))
931 walk_tree (tp, mostly_copy_tree_r, data, NULL);
932 *walk_subtrees = 0;
935 /* Otherwise, mark the node as visited and keep looking. */
936 else
937 TREE_VISITED (t) = 1;
939 return NULL_TREE;
942 /* Unshare most of the shared trees rooted at *TP. DATA is passed to the
943 copy_if_shared_r callback unmodified. */
945 void
946 copy_if_shared (tree *tp, void *data)
948 walk_tree (tp, copy_if_shared_r, data, NULL);
951 /* Unshare all the trees in the body of FNDECL, as well as in the bodies of
952 any nested functions. */
954 static void
955 unshare_body (tree fndecl)
957 struct cgraph_node *cgn = cgraph_node::get (fndecl);
958 /* If the language requires deep unsharing, we need a pointer set to make
959 sure we don't repeatedly unshare subtrees of unshareable nodes. */
960 hash_set<tree> *visited
961 = lang_hooks.deep_unsharing ? new hash_set<tree> : NULL;
963 copy_if_shared (&DECL_SAVED_TREE (fndecl), visited);
964 copy_if_shared (&DECL_SIZE (DECL_RESULT (fndecl)), visited);
965 copy_if_shared (&DECL_SIZE_UNIT (DECL_RESULT (fndecl)), visited);
967 delete visited;
969 if (cgn)
970 for (cgn = first_nested_function (cgn); cgn;
971 cgn = next_nested_function (cgn))
972 unshare_body (cgn->decl);
975 /* Callback for walk_tree to unmark the visited trees rooted at *TP.
976 Subtrees are walked until the first unvisited node is encountered. */
978 static tree
979 unmark_visited_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
981 tree t = *tp;
983 /* If this node has been visited, unmark it and keep looking. */
984 if (TREE_VISITED (t))
985 TREE_VISITED (t) = 0;
987 /* Otherwise, don't look any deeper. */
988 else
989 *walk_subtrees = 0;
991 return NULL_TREE;
994 /* Unmark the visited trees rooted at *TP. */
996 static inline void
997 unmark_visited (tree *tp)
999 walk_tree (tp, unmark_visited_r, NULL, NULL);
1002 /* Likewise, but mark all trees as not visited. */
1004 static void
1005 unvisit_body (tree fndecl)
1007 struct cgraph_node *cgn = cgraph_node::get (fndecl);
1009 unmark_visited (&DECL_SAVED_TREE (fndecl));
1010 unmark_visited (&DECL_SIZE (DECL_RESULT (fndecl)));
1011 unmark_visited (&DECL_SIZE_UNIT (DECL_RESULT (fndecl)));
1013 if (cgn)
1014 for (cgn = first_nested_function (cgn);
1015 cgn; cgn = next_nested_function (cgn))
1016 unvisit_body (cgn->decl);
1019 /* Unconditionally make an unshared copy of EXPR. This is used when using
1020 stored expressions which span multiple functions, such as BINFO_VTABLE,
1021 as the normal unsharing process can't tell that they're shared. */
1023 tree
1024 unshare_expr (tree expr)
1026 walk_tree (&expr, mostly_copy_tree_r, NULL, NULL);
1027 return expr;
1030 /* Worker for unshare_expr_without_location. */
1032 static tree
1033 prune_expr_location (tree *tp, int *walk_subtrees, void *)
1035 if (EXPR_P (*tp))
1036 SET_EXPR_LOCATION (*tp, UNKNOWN_LOCATION);
1037 else
1038 *walk_subtrees = 0;
1039 return NULL_TREE;
1042 /* Similar to unshare_expr but also prune all expression locations
1043 from EXPR. */
1045 tree
1046 unshare_expr_without_location (tree expr)
1048 walk_tree (&expr, mostly_copy_tree_r, NULL, NULL);
1049 if (EXPR_P (expr))
1050 walk_tree (&expr, prune_expr_location, NULL, NULL);
1051 return expr;
1054 /* Return the EXPR_LOCATION of EXPR, if it (maybe recursively) has
1055 one, OR_ELSE otherwise. The location of a STATEMENT_LISTs
1056 comprising at least one DEBUG_BEGIN_STMT followed by exactly one
1057 EXPR is the location of the EXPR. */
1059 static location_t
1060 rexpr_location (tree expr, location_t or_else = UNKNOWN_LOCATION)
1062 if (!expr)
1063 return or_else;
1065 if (EXPR_HAS_LOCATION (expr))
1066 return EXPR_LOCATION (expr);
1068 if (TREE_CODE (expr) != STATEMENT_LIST)
1069 return or_else;
1071 tree_stmt_iterator i = tsi_start (expr);
1073 bool found = false;
1074 while (!tsi_end_p (i) && TREE_CODE (tsi_stmt (i)) == DEBUG_BEGIN_STMT)
1076 found = true;
1077 tsi_next (&i);
1080 if (!found || !tsi_one_before_end_p (i))
1081 return or_else;
1083 return rexpr_location (tsi_stmt (i), or_else);
1086 /* Return TRUE iff EXPR (maybe recursively) has a location; see
1087 rexpr_location for the potential recursion. */
1089 static inline bool
1090 rexpr_has_location (tree expr)
1092 return rexpr_location (expr) != UNKNOWN_LOCATION;
1096 /* WRAPPER is a code such as BIND_EXPR or CLEANUP_POINT_EXPR which can both
1097 contain statements and have a value. Assign its value to a temporary
1098 and give it void_type_node. Return the temporary, or NULL_TREE if
1099 WRAPPER was already void. */
1101 tree
1102 voidify_wrapper_expr (tree wrapper, tree temp)
1104 tree type = TREE_TYPE (wrapper);
1105 if (type && !VOID_TYPE_P (type))
1107 tree *p;
1109 /* Set p to point to the body of the wrapper. Loop until we find
1110 something that isn't a wrapper. */
1111 for (p = &wrapper; p && *p; )
1113 switch (TREE_CODE (*p))
1115 case BIND_EXPR:
1116 TREE_SIDE_EFFECTS (*p) = 1;
1117 TREE_TYPE (*p) = void_type_node;
1118 /* For a BIND_EXPR, the body is operand 1. */
1119 p = &BIND_EXPR_BODY (*p);
1120 break;
1122 case CLEANUP_POINT_EXPR:
1123 case TRY_FINALLY_EXPR:
1124 case TRY_CATCH_EXPR:
1125 TREE_SIDE_EFFECTS (*p) = 1;
1126 TREE_TYPE (*p) = void_type_node;
1127 p = &TREE_OPERAND (*p, 0);
1128 break;
1130 case STATEMENT_LIST:
1132 tree_stmt_iterator i = tsi_last (*p);
1133 TREE_SIDE_EFFECTS (*p) = 1;
1134 TREE_TYPE (*p) = void_type_node;
1135 p = tsi_end_p (i) ? NULL : tsi_stmt_ptr (i);
1137 break;
1139 case COMPOUND_EXPR:
1140 /* Advance to the last statement. Set all container types to
1141 void. */
1142 for (; TREE_CODE (*p) == COMPOUND_EXPR; p = &TREE_OPERAND (*p, 1))
1144 TREE_SIDE_EFFECTS (*p) = 1;
1145 TREE_TYPE (*p) = void_type_node;
1147 break;
1149 case TRANSACTION_EXPR:
1150 TREE_SIDE_EFFECTS (*p) = 1;
1151 TREE_TYPE (*p) = void_type_node;
1152 p = &TRANSACTION_EXPR_BODY (*p);
1153 break;
1155 default:
1156 /* Assume that any tree upon which voidify_wrapper_expr is
1157 directly called is a wrapper, and that its body is op0. */
1158 if (p == &wrapper)
1160 TREE_SIDE_EFFECTS (*p) = 1;
1161 TREE_TYPE (*p) = void_type_node;
1162 p = &TREE_OPERAND (*p, 0);
1163 break;
1165 goto out;
1169 out:
1170 if (p == NULL || IS_EMPTY_STMT (*p))
1171 temp = NULL_TREE;
1172 else if (temp)
1174 /* The wrapper is on the RHS of an assignment that we're pushing
1175 down. */
1176 gcc_assert (TREE_CODE (temp) == INIT_EXPR
1177 || TREE_CODE (temp) == MODIFY_EXPR);
1178 TREE_OPERAND (temp, 1) = *p;
1179 *p = temp;
1181 else
1183 temp = create_tmp_var (type, "retval");
1184 *p = build2 (INIT_EXPR, type, temp, *p);
1187 return temp;
1190 return NULL_TREE;
1193 /* Prepare calls to builtins to SAVE and RESTORE the stack as well as
1194 a temporary through which they communicate. */
1196 static void
1197 build_stack_save_restore (gcall **save, gcall **restore)
1199 tree tmp_var;
1201 *save = gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_SAVE), 0);
1202 tmp_var = create_tmp_var (ptr_type_node, "saved_stack");
1203 gimple_call_set_lhs (*save, tmp_var);
1205 *restore
1206 = gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_RESTORE),
1207 1, tmp_var);
1210 /* Generate IFN_ASAN_MARK call that poisons shadow of a for DECL variable. */
1212 static tree
1213 build_asan_poison_call_expr (tree decl)
1215 /* Do not poison variables that have size equal to zero. */
1216 tree unit_size = DECL_SIZE_UNIT (decl);
1217 if (zerop (unit_size))
1218 return NULL_TREE;
1220 tree base = build_fold_addr_expr (decl);
1222 return build_call_expr_internal_loc (UNKNOWN_LOCATION, IFN_ASAN_MARK,
1223 void_type_node, 3,
1224 build_int_cst (integer_type_node,
1225 ASAN_MARK_POISON),
1226 base, unit_size);
1229 /* Generate IFN_ASAN_MARK call that would poison or unpoison, depending
1230 on POISON flag, shadow memory of a DECL variable. The call will be
1231 put on location identified by IT iterator, where BEFORE flag drives
1232 position where the stmt will be put. */
1234 static void
1235 asan_poison_variable (tree decl, bool poison, gimple_stmt_iterator *it,
1236 bool before)
1238 tree unit_size = DECL_SIZE_UNIT (decl);
1239 tree base = build_fold_addr_expr (decl);
1241 /* Do not poison variables that have size equal to zero. */
1242 if (zerop (unit_size))
1243 return;
1245 /* It's necessary to have all stack variables aligned to ASAN granularity
1246 bytes. */
1247 gcc_assert (!hwasan_sanitize_p () || hwasan_sanitize_stack_p ());
1248 unsigned shadow_granularity
1249 = hwasan_sanitize_p () ? HWASAN_TAG_GRANULE_SIZE : ASAN_SHADOW_GRANULARITY;
1250 if (DECL_ALIGN_UNIT (decl) <= shadow_granularity)
1251 SET_DECL_ALIGN (decl, BITS_PER_UNIT * shadow_granularity);
1253 HOST_WIDE_INT flags = poison ? ASAN_MARK_POISON : ASAN_MARK_UNPOISON;
1255 gimple *g
1256 = gimple_build_call_internal (IFN_ASAN_MARK, 3,
1257 build_int_cst (integer_type_node, flags),
1258 base, unit_size);
1260 if (before)
1261 gsi_insert_before (it, g, GSI_NEW_STMT);
1262 else
1263 gsi_insert_after (it, g, GSI_NEW_STMT);
1266 /* Generate IFN_ASAN_MARK internal call that depending on POISON flag
1267 either poisons or unpoisons a DECL. Created statement is appended
1268 to SEQ_P gimple sequence. */
1270 static void
1271 asan_poison_variable (tree decl, bool poison, gimple_seq *seq_p)
1273 gimple_stmt_iterator it = gsi_last (*seq_p);
1274 bool before = false;
1276 if (gsi_end_p (it))
1277 before = true;
1279 asan_poison_variable (decl, poison, &it, before);
1282 /* Sort pair of VAR_DECLs A and B by DECL_UID. */
1284 static int
1285 sort_by_decl_uid (const void *a, const void *b)
1287 const tree *t1 = (const tree *)a;
1288 const tree *t2 = (const tree *)b;
1290 int uid1 = DECL_UID (*t1);
1291 int uid2 = DECL_UID (*t2);
1293 if (uid1 < uid2)
1294 return -1;
1295 else if (uid1 > uid2)
1296 return 1;
1297 else
1298 return 0;
1301 /* Generate IFN_ASAN_MARK internal call for all VARIABLES
1302 depending on POISON flag. Created statement is appended
1303 to SEQ_P gimple sequence. */
1305 static void
1306 asan_poison_variables (hash_set<tree> *variables, bool poison, gimple_seq *seq_p)
1308 unsigned c = variables->elements ();
1309 if (c == 0)
1310 return;
1312 auto_vec<tree> sorted_variables (c);
1314 for (hash_set<tree>::iterator it = variables->begin ();
1315 it != variables->end (); ++it)
1316 sorted_variables.safe_push (*it);
1318 sorted_variables.qsort (sort_by_decl_uid);
1320 unsigned i;
1321 tree var;
1322 FOR_EACH_VEC_ELT (sorted_variables, i, var)
1324 asan_poison_variable (var, poison, seq_p);
1326 /* Add use_after_scope_memory attribute for the variable in order
1327 to prevent re-written into SSA. */
1328 if (!lookup_attribute (ASAN_USE_AFTER_SCOPE_ATTRIBUTE,
1329 DECL_ATTRIBUTES (var)))
1330 DECL_ATTRIBUTES (var)
1331 = tree_cons (get_identifier (ASAN_USE_AFTER_SCOPE_ATTRIBUTE),
1332 integer_one_node,
1333 DECL_ATTRIBUTES (var));
1337 /* Gimplify a BIND_EXPR. Just voidify and recurse. */
1339 static enum gimplify_status
1340 gimplify_bind_expr (tree *expr_p, gimple_seq *pre_p)
1342 tree bind_expr = *expr_p;
1343 bool old_keep_stack = gimplify_ctxp->keep_stack;
1344 bool old_save_stack = gimplify_ctxp->save_stack;
1345 tree t;
1346 gbind *bind_stmt;
1347 gimple_seq body, cleanup;
1348 gcall *stack_save;
1349 location_t start_locus = 0, end_locus = 0;
1350 tree ret_clauses = NULL;
1352 tree temp = voidify_wrapper_expr (bind_expr, NULL);
1354 /* Mark variables seen in this bind expr. */
1355 for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
1357 if (VAR_P (t))
1359 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
1361 /* Mark variable as local. */
1362 if (ctx && ctx->region_type != ORT_NONE && !DECL_EXTERNAL (t))
1364 if (! DECL_SEEN_IN_BIND_EXPR_P (t)
1365 || splay_tree_lookup (ctx->variables,
1366 (splay_tree_key) t) == NULL)
1368 int flag = GOVD_LOCAL;
1369 if (ctx->region_type == ORT_SIMD
1370 && TREE_ADDRESSABLE (t)
1371 && !TREE_STATIC (t))
1373 if (TREE_CODE (DECL_SIZE_UNIT (t)) != INTEGER_CST)
1374 ctx->add_safelen1 = true;
1375 else
1376 flag = GOVD_PRIVATE;
1378 omp_add_variable (ctx, t, flag | GOVD_SEEN);
1380 /* Static locals inside of target construct or offloaded
1381 routines need to be "omp declare target". */
1382 if (TREE_STATIC (t))
1383 for (; ctx; ctx = ctx->outer_context)
1384 if ((ctx->region_type & ORT_TARGET) != 0)
1386 if (!lookup_attribute ("omp declare target",
1387 DECL_ATTRIBUTES (t)))
1389 tree id = get_identifier ("omp declare target");
1390 DECL_ATTRIBUTES (t)
1391 = tree_cons (id, NULL_TREE, DECL_ATTRIBUTES (t));
1392 varpool_node *node = varpool_node::get (t);
1393 if (node)
1395 node->offloadable = 1;
1396 if (ENABLE_OFFLOADING && !DECL_EXTERNAL (t))
1398 g->have_offload = true;
1399 if (!in_lto_p)
1400 vec_safe_push (offload_vars, t);
1404 break;
1408 DECL_SEEN_IN_BIND_EXPR_P (t) = 1;
1410 if (DECL_HARD_REGISTER (t) && !is_global_var (t) && cfun)
1411 cfun->has_local_explicit_reg_vars = true;
1415 bind_stmt = gimple_build_bind (BIND_EXPR_VARS (bind_expr), NULL,
1416 BIND_EXPR_BLOCK (bind_expr));
1417 gimple_push_bind_expr (bind_stmt);
1419 gimplify_ctxp->keep_stack = false;
1420 gimplify_ctxp->save_stack = false;
1422 /* Gimplify the body into the GIMPLE_BIND tuple's body. */
1423 body = NULL;
1424 gimplify_stmt (&BIND_EXPR_BODY (bind_expr), &body);
1425 gimple_bind_set_body (bind_stmt, body);
1427 /* Source location wise, the cleanup code (stack_restore and clobbers)
1428 belongs to the end of the block, so propagate what we have. The
1429 stack_save operation belongs to the beginning of block, which we can
1430 infer from the bind_expr directly if the block has no explicit
1431 assignment. */
1432 if (BIND_EXPR_BLOCK (bind_expr))
1434 end_locus = BLOCK_SOURCE_END_LOCATION (BIND_EXPR_BLOCK (bind_expr));
1435 start_locus = BLOCK_SOURCE_LOCATION (BIND_EXPR_BLOCK (bind_expr));
1437 if (start_locus == 0)
1438 start_locus = EXPR_LOCATION (bind_expr);
1440 cleanup = NULL;
1441 stack_save = NULL;
1443 /* If the code both contains VLAs and calls alloca, then we cannot reclaim
1444 the stack space allocated to the VLAs. */
1445 if (gimplify_ctxp->save_stack && !gimplify_ctxp->keep_stack)
1447 gcall *stack_restore;
1449 /* Save stack on entry and restore it on exit. Add a try_finally
1450 block to achieve this. */
1451 build_stack_save_restore (&stack_save, &stack_restore);
1453 gimple_set_location (stack_save, start_locus);
1454 gimple_set_location (stack_restore, end_locus);
1456 gimplify_seq_add_stmt (&cleanup, stack_restore);
1459 /* Add clobbers for all variables that go out of scope. */
1460 for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
1462 if (VAR_P (t)
1463 && !is_global_var (t)
1464 && DECL_CONTEXT (t) == current_function_decl)
1466 if (!DECL_HARD_REGISTER (t)
1467 && !TREE_THIS_VOLATILE (t)
1468 && !DECL_HAS_VALUE_EXPR_P (t)
1469 /* Only care for variables that have to be in memory. Others
1470 will be rewritten into SSA names, hence moved to the
1471 top-level. */
1472 && !is_gimple_reg (t)
1473 && flag_stack_reuse != SR_NONE)
1475 tree clobber = build_clobber (TREE_TYPE (t));
1476 gimple *clobber_stmt;
1477 clobber_stmt = gimple_build_assign (t, clobber);
1478 gimple_set_location (clobber_stmt, end_locus);
1479 gimplify_seq_add_stmt (&cleanup, clobber_stmt);
1482 if (flag_openacc && oacc_declare_returns != NULL)
1484 tree key = t;
1485 if (DECL_HAS_VALUE_EXPR_P (key))
1487 key = DECL_VALUE_EXPR (key);
1488 if (TREE_CODE (key) == INDIRECT_REF)
1489 key = TREE_OPERAND (key, 0);
1491 tree *c = oacc_declare_returns->get (key);
1492 if (c != NULL)
1494 if (ret_clauses)
1495 OMP_CLAUSE_CHAIN (*c) = ret_clauses;
1497 ret_clauses = unshare_expr (*c);
1499 oacc_declare_returns->remove (key);
1501 if (oacc_declare_returns->is_empty ())
1503 delete oacc_declare_returns;
1504 oacc_declare_returns = NULL;
1510 if (asan_poisoned_variables != NULL
1511 && asan_poisoned_variables->contains (t))
1513 asan_poisoned_variables->remove (t);
1514 asan_poison_variable (t, true, &cleanup);
1517 if (gimplify_ctxp->live_switch_vars != NULL
1518 && gimplify_ctxp->live_switch_vars->contains (t))
1519 gimplify_ctxp->live_switch_vars->remove (t);
1522 if (ret_clauses)
1524 gomp_target *stmt;
1525 gimple_stmt_iterator si = gsi_start (cleanup);
1527 stmt = gimple_build_omp_target (NULL, GF_OMP_TARGET_KIND_OACC_DECLARE,
1528 ret_clauses);
1529 gsi_insert_seq_before_without_update (&si, stmt, GSI_NEW_STMT);
1532 if (cleanup)
1534 gtry *gs;
1535 gimple_seq new_body;
1537 new_body = NULL;
1538 gs = gimple_build_try (gimple_bind_body (bind_stmt), cleanup,
1539 GIMPLE_TRY_FINALLY);
1541 if (stack_save)
1542 gimplify_seq_add_stmt (&new_body, stack_save);
1543 gimplify_seq_add_stmt (&new_body, gs);
1544 gimple_bind_set_body (bind_stmt, new_body);
1547 /* keep_stack propagates all the way up to the outermost BIND_EXPR. */
1548 if (!gimplify_ctxp->keep_stack)
1549 gimplify_ctxp->keep_stack = old_keep_stack;
1550 gimplify_ctxp->save_stack = old_save_stack;
1552 gimple_pop_bind_expr ();
1554 gimplify_seq_add_stmt (pre_p, bind_stmt);
1556 if (temp)
1558 *expr_p = temp;
1559 return GS_OK;
1562 *expr_p = NULL_TREE;
1563 return GS_ALL_DONE;
1566 /* Maybe add early return predict statement to PRE_P sequence. */
1568 static void
1569 maybe_add_early_return_predict_stmt (gimple_seq *pre_p)
1571 /* If we are not in a conditional context, add PREDICT statement. */
1572 if (gimple_conditional_context ())
1574 gimple *predict = gimple_build_predict (PRED_TREE_EARLY_RETURN,
1575 NOT_TAKEN);
1576 gimplify_seq_add_stmt (pre_p, predict);
1580 /* Gimplify a RETURN_EXPR. If the expression to be returned is not a
1581 GIMPLE value, it is assigned to a new temporary and the statement is
1582 re-written to return the temporary.
1584 PRE_P points to the sequence where side effects that must happen before
1585 STMT should be stored. */
1587 static enum gimplify_status
1588 gimplify_return_expr (tree stmt, gimple_seq *pre_p)
1590 greturn *ret;
1591 tree ret_expr = TREE_OPERAND (stmt, 0);
1592 tree result_decl, result;
1594 if (ret_expr == error_mark_node)
1595 return GS_ERROR;
1597 if (!ret_expr
1598 || TREE_CODE (ret_expr) == RESULT_DECL)
1600 maybe_add_early_return_predict_stmt (pre_p);
1601 greturn *ret = gimple_build_return (ret_expr);
1602 gimple_set_no_warning (ret, TREE_NO_WARNING (stmt));
1603 gimplify_seq_add_stmt (pre_p, ret);
1604 return GS_ALL_DONE;
1607 if (VOID_TYPE_P (TREE_TYPE (TREE_TYPE (current_function_decl))))
1608 result_decl = NULL_TREE;
1609 else if (TREE_CODE (ret_expr) == COMPOUND_EXPR)
1611 /* Used in C++ for handling EH cleanup of the return value if a local
1612 cleanup throws. Assume the front-end knows what it's doing. */
1613 result_decl = DECL_RESULT (current_function_decl);
1614 /* But crash if we end up trying to modify ret_expr below. */
1615 ret_expr = NULL_TREE;
1617 else
1619 result_decl = TREE_OPERAND (ret_expr, 0);
1621 /* See through a return by reference. */
1622 if (TREE_CODE (result_decl) == INDIRECT_REF)
1623 result_decl = TREE_OPERAND (result_decl, 0);
1625 gcc_assert ((TREE_CODE (ret_expr) == MODIFY_EXPR
1626 || TREE_CODE (ret_expr) == INIT_EXPR)
1627 && TREE_CODE (result_decl) == RESULT_DECL);
1630 /* If aggregate_value_p is true, then we can return the bare RESULT_DECL.
1631 Recall that aggregate_value_p is FALSE for any aggregate type that is
1632 returned in registers. If we're returning values in registers, then
1633 we don't want to extend the lifetime of the RESULT_DECL, particularly
1634 across another call. In addition, for those aggregates for which
1635 hard_function_value generates a PARALLEL, we'll die during normal
1636 expansion of structure assignments; there's special code in expand_return
1637 to handle this case that does not exist in expand_expr. */
1638 if (!result_decl)
1639 result = NULL_TREE;
1640 else if (aggregate_value_p (result_decl, TREE_TYPE (current_function_decl)))
1642 if (!poly_int_tree_p (DECL_SIZE (result_decl)))
1644 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (result_decl)))
1645 gimplify_type_sizes (TREE_TYPE (result_decl), pre_p);
1646 /* Note that we don't use gimplify_vla_decl because the RESULT_DECL
1647 should be effectively allocated by the caller, i.e. all calls to
1648 this function must be subject to the Return Slot Optimization. */
1649 gimplify_one_sizepos (&DECL_SIZE (result_decl), pre_p);
1650 gimplify_one_sizepos (&DECL_SIZE_UNIT (result_decl), pre_p);
1652 result = result_decl;
1654 else if (gimplify_ctxp->return_temp)
1655 result = gimplify_ctxp->return_temp;
1656 else
1658 result = create_tmp_reg (TREE_TYPE (result_decl));
1660 /* ??? With complex control flow (usually involving abnormal edges),
1661 we can wind up warning about an uninitialized value for this. Due
1662 to how this variable is constructed and initialized, this is never
1663 true. Give up and never warn. */
1664 TREE_NO_WARNING (result) = 1;
1666 gimplify_ctxp->return_temp = result;
1669 /* Smash the lhs of the MODIFY_EXPR to the temporary we plan to use.
1670 Then gimplify the whole thing. */
1671 if (result != result_decl)
1672 TREE_OPERAND (ret_expr, 0) = result;
1674 gimplify_and_add (TREE_OPERAND (stmt, 0), pre_p);
1676 maybe_add_early_return_predict_stmt (pre_p);
1677 ret = gimple_build_return (result);
1678 gimple_set_no_warning (ret, TREE_NO_WARNING (stmt));
1679 gimplify_seq_add_stmt (pre_p, ret);
1681 return GS_ALL_DONE;
1684 /* Gimplify a variable-length array DECL. */
1686 static void
1687 gimplify_vla_decl (tree decl, gimple_seq *seq_p)
1689 /* This is a variable-sized decl. Simplify its size and mark it
1690 for deferred expansion. */
1691 tree t, addr, ptr_type;
1693 gimplify_one_sizepos (&DECL_SIZE (decl), seq_p);
1694 gimplify_one_sizepos (&DECL_SIZE_UNIT (decl), seq_p);
1696 /* Don't mess with a DECL_VALUE_EXPR set by the front-end. */
1697 if (DECL_HAS_VALUE_EXPR_P (decl))
1698 return;
1700 /* All occurrences of this decl in final gimplified code will be
1701 replaced by indirection. Setting DECL_VALUE_EXPR does two
1702 things: First, it lets the rest of the gimplifier know what
1703 replacement to use. Second, it lets the debug info know
1704 where to find the value. */
1705 ptr_type = build_pointer_type (TREE_TYPE (decl));
1706 addr = create_tmp_var (ptr_type, get_name (decl));
1707 DECL_IGNORED_P (addr) = 0;
1708 t = build_fold_indirect_ref (addr);
1709 TREE_THIS_NOTRAP (t) = 1;
1710 SET_DECL_VALUE_EXPR (decl, t);
1711 DECL_HAS_VALUE_EXPR_P (decl) = 1;
1713 t = build_alloca_call_expr (DECL_SIZE_UNIT (decl), DECL_ALIGN (decl),
1714 max_int_size_in_bytes (TREE_TYPE (decl)));
1715 /* The call has been built for a variable-sized object. */
1716 CALL_ALLOCA_FOR_VAR_P (t) = 1;
1717 t = fold_convert (ptr_type, t);
1718 t = build2 (MODIFY_EXPR, TREE_TYPE (addr), addr, t);
1720 gimplify_and_add (t, seq_p);
1722 /* Record the dynamic allocation associated with DECL if requested. */
1723 if (flag_callgraph_info & CALLGRAPH_INFO_DYNAMIC_ALLOC)
1724 record_dynamic_alloc (decl);
1727 /* A helper function to be called via walk_tree. Mark all labels under *TP
1728 as being forced. To be called for DECL_INITIAL of static variables. */
1730 static tree
1731 force_labels_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
1733 if (TYPE_P (*tp))
1734 *walk_subtrees = 0;
1735 if (TREE_CODE (*tp) == LABEL_DECL)
1737 FORCED_LABEL (*tp) = 1;
1738 cfun->has_forced_label_in_static = 1;
1741 return NULL_TREE;
1744 /* Gimplify a DECL_EXPR node *STMT_P by making any necessary allocation
1745 and initialization explicit. */
1747 static enum gimplify_status
1748 gimplify_decl_expr (tree *stmt_p, gimple_seq *seq_p)
1750 tree stmt = *stmt_p;
1751 tree decl = DECL_EXPR_DECL (stmt);
1753 *stmt_p = NULL_TREE;
1755 if (TREE_TYPE (decl) == error_mark_node)
1756 return GS_ERROR;
1758 if ((TREE_CODE (decl) == TYPE_DECL
1759 || VAR_P (decl))
1760 && !TYPE_SIZES_GIMPLIFIED (TREE_TYPE (decl)))
1762 gimplify_type_sizes (TREE_TYPE (decl), seq_p);
1763 if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE)
1764 gimplify_type_sizes (TREE_TYPE (TREE_TYPE (decl)), seq_p);
1767 /* ??? DECL_ORIGINAL_TYPE is streamed for LTO so it needs to be gimplified
1768 in case its size expressions contain problematic nodes like CALL_EXPR. */
1769 if (TREE_CODE (decl) == TYPE_DECL
1770 && DECL_ORIGINAL_TYPE (decl)
1771 && !TYPE_SIZES_GIMPLIFIED (DECL_ORIGINAL_TYPE (decl)))
1773 gimplify_type_sizes (DECL_ORIGINAL_TYPE (decl), seq_p);
1774 if (TREE_CODE (DECL_ORIGINAL_TYPE (decl)) == REFERENCE_TYPE)
1775 gimplify_type_sizes (TREE_TYPE (DECL_ORIGINAL_TYPE (decl)), seq_p);
1778 if (VAR_P (decl) && !DECL_EXTERNAL (decl))
1780 tree init = DECL_INITIAL (decl);
1781 bool is_vla = false;
1783 poly_uint64 size;
1784 if (!poly_int_tree_p (DECL_SIZE_UNIT (decl), &size)
1785 || (!TREE_STATIC (decl)
1786 && flag_stack_check == GENERIC_STACK_CHECK
1787 && maybe_gt (size,
1788 (unsigned HOST_WIDE_INT) STACK_CHECK_MAX_VAR_SIZE)))
1790 gimplify_vla_decl (decl, seq_p);
1791 is_vla = true;
1794 if (asan_poisoned_variables
1795 && !is_vla
1796 && TREE_ADDRESSABLE (decl)
1797 && !TREE_STATIC (decl)
1798 && !DECL_HAS_VALUE_EXPR_P (decl)
1799 && DECL_ALIGN (decl) <= MAX_SUPPORTED_STACK_ALIGNMENT
1800 && dbg_cnt (asan_use_after_scope)
1801 && !gimplify_omp_ctxp
1802 /* GNAT introduces temporaries to hold return values of calls in
1803 initializers of variables defined in other units, so the
1804 declaration of the variable is discarded completely. We do not
1805 want to issue poison calls for such dropped variables. */
1806 && (DECL_SEEN_IN_BIND_EXPR_P (decl)
1807 || (DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)))
1809 asan_poisoned_variables->add (decl);
1810 asan_poison_variable (decl, false, seq_p);
1811 if (!DECL_ARTIFICIAL (decl) && gimplify_ctxp->live_switch_vars)
1812 gimplify_ctxp->live_switch_vars->add (decl);
1815 /* Some front ends do not explicitly declare all anonymous
1816 artificial variables. We compensate here by declaring the
1817 variables, though it would be better if the front ends would
1818 explicitly declare them. */
1819 if (!DECL_SEEN_IN_BIND_EXPR_P (decl)
1820 && DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)
1821 gimple_add_tmp_var (decl);
1823 if (init && init != error_mark_node)
1825 if (!TREE_STATIC (decl))
1827 DECL_INITIAL (decl) = NULL_TREE;
1828 init = build2 (INIT_EXPR, void_type_node, decl, init);
1829 gimplify_and_add (init, seq_p);
1830 ggc_free (init);
1831 /* Clear TREE_READONLY if we really have an initialization. */
1832 if (!DECL_INITIAL (decl) && !omp_is_reference (decl))
1833 TREE_READONLY (decl) = 0;
1835 else
1836 /* We must still examine initializers for static variables
1837 as they may contain a label address. */
1838 walk_tree (&init, force_labels_r, NULL, NULL);
1842 return GS_ALL_DONE;
1845 /* Gimplify a LOOP_EXPR. Normally this just involves gimplifying the body
1846 and replacing the LOOP_EXPR with goto, but if the loop contains an
1847 EXIT_EXPR, we need to append a label for it to jump to. */
1849 static enum gimplify_status
1850 gimplify_loop_expr (tree *expr_p, gimple_seq *pre_p)
1852 tree saved_label = gimplify_ctxp->exit_label;
1853 tree start_label = create_artificial_label (UNKNOWN_LOCATION);
1855 gimplify_seq_add_stmt (pre_p, gimple_build_label (start_label));
1857 gimplify_ctxp->exit_label = NULL_TREE;
1859 gimplify_and_add (LOOP_EXPR_BODY (*expr_p), pre_p);
1861 gimplify_seq_add_stmt (pre_p, gimple_build_goto (start_label));
1863 if (gimplify_ctxp->exit_label)
1864 gimplify_seq_add_stmt (pre_p,
1865 gimple_build_label (gimplify_ctxp->exit_label));
1867 gimplify_ctxp->exit_label = saved_label;
1869 *expr_p = NULL;
1870 return GS_ALL_DONE;
1873 /* Gimplify a statement list onto a sequence. These may be created either
1874 by an enlightened front-end, or by shortcut_cond_expr. */
1876 static enum gimplify_status
1877 gimplify_statement_list (tree *expr_p, gimple_seq *pre_p)
1879 tree temp = voidify_wrapper_expr (*expr_p, NULL);
1881 tree_stmt_iterator i = tsi_start (*expr_p);
1883 while (!tsi_end_p (i))
1885 gimplify_stmt (tsi_stmt_ptr (i), pre_p);
1886 tsi_delink (&i);
1889 if (temp)
1891 *expr_p = temp;
1892 return GS_OK;
1895 return GS_ALL_DONE;
1898 /* Callback for walk_gimple_seq. */
1900 static tree
1901 warn_switch_unreachable_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
1902 struct walk_stmt_info *wi)
1904 gimple *stmt = gsi_stmt (*gsi_p);
1906 *handled_ops_p = true;
1907 switch (gimple_code (stmt))
1909 case GIMPLE_TRY:
1910 /* A compiler-generated cleanup or a user-written try block.
1911 If it's empty, don't dive into it--that would result in
1912 worse location info. */
1913 if (gimple_try_eval (stmt) == NULL)
1915 wi->info = stmt;
1916 return integer_zero_node;
1918 /* Fall through. */
1919 case GIMPLE_BIND:
1920 case GIMPLE_CATCH:
1921 case GIMPLE_EH_FILTER:
1922 case GIMPLE_TRANSACTION:
1923 /* Walk the sub-statements. */
1924 *handled_ops_p = false;
1925 break;
1927 case GIMPLE_DEBUG:
1928 /* Ignore these. We may generate them before declarations that
1929 are never executed. If there's something to warn about,
1930 there will be non-debug stmts too, and we'll catch those. */
1931 break;
1933 case GIMPLE_CALL:
1934 if (gimple_call_internal_p (stmt, IFN_ASAN_MARK))
1936 *handled_ops_p = false;
1937 break;
1939 /* Fall through. */
1940 default:
1941 /* Save the first "real" statement (not a decl/lexical scope/...). */
1942 wi->info = stmt;
1943 return integer_zero_node;
1945 return NULL_TREE;
1948 /* Possibly warn about unreachable statements between switch's controlling
1949 expression and the first case. SEQ is the body of a switch expression. */
1951 static void
1952 maybe_warn_switch_unreachable (gimple_seq seq)
1954 if (!warn_switch_unreachable
1955 /* This warning doesn't play well with Fortran when optimizations
1956 are on. */
1957 || lang_GNU_Fortran ()
1958 || seq == NULL)
1959 return;
1961 struct walk_stmt_info wi;
1962 memset (&wi, 0, sizeof (wi));
1963 walk_gimple_seq (seq, warn_switch_unreachable_r, NULL, &wi);
1964 gimple *stmt = (gimple *) wi.info;
1966 if (stmt && gimple_code (stmt) != GIMPLE_LABEL)
1968 if (gimple_code (stmt) == GIMPLE_GOTO
1969 && TREE_CODE (gimple_goto_dest (stmt)) == LABEL_DECL
1970 && DECL_ARTIFICIAL (gimple_goto_dest (stmt)))
1971 /* Don't warn for compiler-generated gotos. These occur
1972 in Duff's devices, for example. */;
1973 else
1974 warning_at (gimple_location (stmt), OPT_Wswitch_unreachable,
1975 "statement will never be executed");
1980 /* A label entry that pairs label and a location. */
1981 struct label_entry
1983 tree label;
1984 location_t loc;
1987 /* Find LABEL in vector of label entries VEC. */
1989 static struct label_entry *
1990 find_label_entry (const auto_vec<struct label_entry> *vec, tree label)
1992 unsigned int i;
1993 struct label_entry *l;
1995 FOR_EACH_VEC_ELT (*vec, i, l)
1996 if (l->label == label)
1997 return l;
1998 return NULL;
2001 /* Return true if LABEL, a LABEL_DECL, represents a case label
2002 in a vector of labels CASES. */
2004 static bool
2005 case_label_p (const vec<tree> *cases, tree label)
2007 unsigned int i;
2008 tree l;
2010 FOR_EACH_VEC_ELT (*cases, i, l)
2011 if (CASE_LABEL (l) == label)
2012 return true;
2013 return false;
2016 /* Find the last nondebug statement in a scope STMT. */
2018 static gimple *
2019 last_stmt_in_scope (gimple *stmt)
2021 if (!stmt)
2022 return NULL;
2024 switch (gimple_code (stmt))
2026 case GIMPLE_BIND:
2028 gbind *bind = as_a <gbind *> (stmt);
2029 stmt = gimple_seq_last_nondebug_stmt (gimple_bind_body (bind));
2030 return last_stmt_in_scope (stmt);
2033 case GIMPLE_TRY:
2035 gtry *try_stmt = as_a <gtry *> (stmt);
2036 stmt = gimple_seq_last_nondebug_stmt (gimple_try_eval (try_stmt));
2037 gimple *last_eval = last_stmt_in_scope (stmt);
2038 if (gimple_stmt_may_fallthru (last_eval)
2039 && (last_eval == NULL
2040 || !gimple_call_internal_p (last_eval, IFN_FALLTHROUGH))
2041 && gimple_try_kind (try_stmt) == GIMPLE_TRY_FINALLY)
2043 stmt = gimple_seq_last_nondebug_stmt (gimple_try_cleanup (try_stmt));
2044 return last_stmt_in_scope (stmt);
2046 else
2047 return last_eval;
2050 case GIMPLE_DEBUG:
2051 gcc_unreachable ();
2053 default:
2054 return stmt;
2058 /* Collect interesting labels in LABELS and return the statement preceding
2059 another case label, or a user-defined label. Store a location useful
2060 to give warnings at *PREVLOC (usually the location of the returned
2061 statement or of its surrounding scope). */
2063 static gimple *
2064 collect_fallthrough_labels (gimple_stmt_iterator *gsi_p,
2065 auto_vec <struct label_entry> *labels,
2066 location_t *prevloc)
2068 gimple *prev = NULL;
2070 *prevloc = UNKNOWN_LOCATION;
2073 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_BIND)
2075 /* Recognize the special GIMPLE_BIND added by gimplify_switch_expr,
2076 which starts on a GIMPLE_SWITCH and ends with a break label.
2077 Handle that as a single statement that can fall through. */
2078 gbind *bind = as_a <gbind *> (gsi_stmt (*gsi_p));
2079 gimple *first = gimple_seq_first_stmt (gimple_bind_body (bind));
2080 gimple *last = gimple_seq_last_stmt (gimple_bind_body (bind));
2081 if (last
2082 && gimple_code (first) == GIMPLE_SWITCH
2083 && gimple_code (last) == GIMPLE_LABEL)
2085 tree label = gimple_label_label (as_a <glabel *> (last));
2086 if (SWITCH_BREAK_LABEL_P (label))
2088 prev = bind;
2089 gsi_next (gsi_p);
2090 continue;
2094 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_BIND
2095 || gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_TRY)
2097 /* Nested scope. Only look at the last statement of
2098 the innermost scope. */
2099 location_t bind_loc = gimple_location (gsi_stmt (*gsi_p));
2100 gimple *last = last_stmt_in_scope (gsi_stmt (*gsi_p));
2101 if (last)
2103 prev = last;
2104 /* It might be a label without a location. Use the
2105 location of the scope then. */
2106 if (!gimple_has_location (prev))
2107 *prevloc = bind_loc;
2109 gsi_next (gsi_p);
2110 continue;
2113 /* Ifs are tricky. */
2114 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_COND)
2116 gcond *cond_stmt = as_a <gcond *> (gsi_stmt (*gsi_p));
2117 tree false_lab = gimple_cond_false_label (cond_stmt);
2118 location_t if_loc = gimple_location (cond_stmt);
2120 /* If we have e.g.
2121 if (i > 1) goto <D.2259>; else goto D;
2122 we can't do much with the else-branch. */
2123 if (!DECL_ARTIFICIAL (false_lab))
2124 break;
2126 /* Go on until the false label, then one step back. */
2127 for (; !gsi_end_p (*gsi_p); gsi_next (gsi_p))
2129 gimple *stmt = gsi_stmt (*gsi_p);
2130 if (gimple_code (stmt) == GIMPLE_LABEL
2131 && gimple_label_label (as_a <glabel *> (stmt)) == false_lab)
2132 break;
2135 /* Not found? Oops. */
2136 if (gsi_end_p (*gsi_p))
2137 break;
2139 struct label_entry l = { false_lab, if_loc };
2140 labels->safe_push (l);
2142 /* Go to the last statement of the then branch. */
2143 gsi_prev (gsi_p);
2145 /* if (i != 0) goto <D.1759>; else goto <D.1760>;
2146 <D.1759>:
2147 <stmt>;
2148 goto <D.1761>;
2149 <D.1760>:
2151 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_GOTO
2152 && !gimple_has_location (gsi_stmt (*gsi_p)))
2154 /* Look at the statement before, it might be
2155 attribute fallthrough, in which case don't warn. */
2156 gsi_prev (gsi_p);
2157 bool fallthru_before_dest
2158 = gimple_call_internal_p (gsi_stmt (*gsi_p), IFN_FALLTHROUGH);
2159 gsi_next (gsi_p);
2160 tree goto_dest = gimple_goto_dest (gsi_stmt (*gsi_p));
2161 if (!fallthru_before_dest)
2163 struct label_entry l = { goto_dest, if_loc };
2164 labels->safe_push (l);
2167 /* And move back. */
2168 gsi_next (gsi_p);
2171 /* Remember the last statement. Skip labels that are of no interest
2172 to us. */
2173 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_LABEL)
2175 tree label = gimple_label_label (as_a <glabel *> (gsi_stmt (*gsi_p)));
2176 if (find_label_entry (labels, label))
2177 prev = gsi_stmt (*gsi_p);
2179 else if (gimple_call_internal_p (gsi_stmt (*gsi_p), IFN_ASAN_MARK))
2181 else if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_PREDICT)
2183 else if (!is_gimple_debug (gsi_stmt (*gsi_p)))
2184 prev = gsi_stmt (*gsi_p);
2185 gsi_next (gsi_p);
2187 while (!gsi_end_p (*gsi_p)
2188 /* Stop if we find a case or a user-defined label. */
2189 && (gimple_code (gsi_stmt (*gsi_p)) != GIMPLE_LABEL
2190 || !gimple_has_location (gsi_stmt (*gsi_p))));
2192 if (prev && gimple_has_location (prev))
2193 *prevloc = gimple_location (prev);
2194 return prev;
2197 /* Return true if the switch fallthough warning should occur. LABEL is
2198 the label statement that we're falling through to. */
2200 static bool
2201 should_warn_for_implicit_fallthrough (gimple_stmt_iterator *gsi_p, tree label)
2203 gimple_stmt_iterator gsi = *gsi_p;
2205 /* Don't warn if the label is marked with a "falls through" comment. */
2206 if (FALLTHROUGH_LABEL_P (label))
2207 return false;
2209 /* Don't warn for non-case labels followed by a statement:
2210 case 0:
2211 foo ();
2212 label:
2213 bar ();
2214 as these are likely intentional. */
2215 if (!case_label_p (&gimplify_ctxp->case_labels, label))
2217 tree l;
2218 while (!gsi_end_p (gsi)
2219 && gimple_code (gsi_stmt (gsi)) == GIMPLE_LABEL
2220 && (l = gimple_label_label (as_a <glabel *> (gsi_stmt (gsi))))
2221 && !case_label_p (&gimplify_ctxp->case_labels, l))
2222 gsi_next_nondebug (&gsi);
2223 if (gsi_end_p (gsi) || gimple_code (gsi_stmt (gsi)) != GIMPLE_LABEL)
2224 return false;
2227 /* Don't warn for terminated branches, i.e. when the subsequent case labels
2228 immediately breaks. */
2229 gsi = *gsi_p;
2231 /* Skip all immediately following labels. */
2232 while (!gsi_end_p (gsi)
2233 && (gimple_code (gsi_stmt (gsi)) == GIMPLE_LABEL
2234 || gimple_code (gsi_stmt (gsi)) == GIMPLE_PREDICT))
2235 gsi_next_nondebug (&gsi);
2237 /* { ... something; default:; } */
2238 if (gsi_end_p (gsi)
2239 /* { ... something; default: break; } or
2240 { ... something; default: goto L; } */
2241 || gimple_code (gsi_stmt (gsi)) == GIMPLE_GOTO
2242 /* { ... something; default: return; } */
2243 || gimple_code (gsi_stmt (gsi)) == GIMPLE_RETURN)
2244 return false;
2246 return true;
2249 /* Callback for walk_gimple_seq. */
2251 static tree
2252 warn_implicit_fallthrough_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
2253 struct walk_stmt_info *)
2255 gimple *stmt = gsi_stmt (*gsi_p);
2257 *handled_ops_p = true;
2258 switch (gimple_code (stmt))
2260 case GIMPLE_TRY:
2261 case GIMPLE_BIND:
2262 case GIMPLE_CATCH:
2263 case GIMPLE_EH_FILTER:
2264 case GIMPLE_TRANSACTION:
2265 /* Walk the sub-statements. */
2266 *handled_ops_p = false;
2267 break;
2269 /* Find a sequence of form:
2271 GIMPLE_LABEL
2272 [...]
2273 <may fallthru stmt>
2274 GIMPLE_LABEL
2276 and possibly warn. */
2277 case GIMPLE_LABEL:
2279 /* Found a label. Skip all immediately following labels. */
2280 while (!gsi_end_p (*gsi_p)
2281 && gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_LABEL)
2282 gsi_next_nondebug (gsi_p);
2284 /* There might be no more statements. */
2285 if (gsi_end_p (*gsi_p))
2286 return integer_zero_node;
2288 /* Vector of labels that fall through. */
2289 auto_vec <struct label_entry> labels;
2290 location_t prevloc;
2291 gimple *prev = collect_fallthrough_labels (gsi_p, &labels, &prevloc);
2293 /* There might be no more statements. */
2294 if (gsi_end_p (*gsi_p))
2295 return integer_zero_node;
2297 gimple *next = gsi_stmt (*gsi_p);
2298 tree label;
2299 /* If what follows is a label, then we may have a fallthrough. */
2300 if (gimple_code (next) == GIMPLE_LABEL
2301 && gimple_has_location (next)
2302 && (label = gimple_label_label (as_a <glabel *> (next)))
2303 && prev != NULL)
2305 struct label_entry *l;
2306 bool warned_p = false;
2307 auto_diagnostic_group d;
2308 if (!should_warn_for_implicit_fallthrough (gsi_p, label))
2309 /* Quiet. */;
2310 else if (gimple_code (prev) == GIMPLE_LABEL
2311 && (label = gimple_label_label (as_a <glabel *> (prev)))
2312 && (l = find_label_entry (&labels, label)))
2313 warned_p = warning_at (l->loc, OPT_Wimplicit_fallthrough_,
2314 "this statement may fall through");
2315 else if (!gimple_call_internal_p (prev, IFN_FALLTHROUGH)
2316 /* Try to be clever and don't warn when the statement
2317 can't actually fall through. */
2318 && gimple_stmt_may_fallthru (prev)
2319 && prevloc != UNKNOWN_LOCATION)
2320 warned_p = warning_at (prevloc,
2321 OPT_Wimplicit_fallthrough_,
2322 "this statement may fall through");
2323 if (warned_p)
2324 inform (gimple_location (next), "here");
2326 /* Mark this label as processed so as to prevent multiple
2327 warnings in nested switches. */
2328 FALLTHROUGH_LABEL_P (label) = true;
2330 /* So that next warn_implicit_fallthrough_r will start looking for
2331 a new sequence starting with this label. */
2332 gsi_prev (gsi_p);
2335 break;
2336 default:
2337 break;
2339 return NULL_TREE;
2342 /* Warn when a switch case falls through. */
2344 static void
2345 maybe_warn_implicit_fallthrough (gimple_seq seq)
2347 if (!warn_implicit_fallthrough)
2348 return;
2350 /* This warning is meant for C/C++/ObjC/ObjC++ only. */
2351 if (!(lang_GNU_C ()
2352 || lang_GNU_CXX ()
2353 || lang_GNU_OBJC ()))
2354 return;
2356 struct walk_stmt_info wi;
2357 memset (&wi, 0, sizeof (wi));
2358 walk_gimple_seq (seq, warn_implicit_fallthrough_r, NULL, &wi);
2361 /* Callback for walk_gimple_seq. */
2363 static tree
2364 expand_FALLTHROUGH_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
2365 struct walk_stmt_info *wi)
2367 gimple *stmt = gsi_stmt (*gsi_p);
2369 *handled_ops_p = true;
2370 switch (gimple_code (stmt))
2372 case GIMPLE_TRY:
2373 case GIMPLE_BIND:
2374 case GIMPLE_CATCH:
2375 case GIMPLE_EH_FILTER:
2376 case GIMPLE_TRANSACTION:
2377 /* Walk the sub-statements. */
2378 *handled_ops_p = false;
2379 break;
2380 case GIMPLE_CALL:
2381 if (gimple_call_internal_p (stmt, IFN_FALLTHROUGH))
2383 gsi_remove (gsi_p, true);
2384 if (gsi_end_p (*gsi_p))
2386 *static_cast<location_t *>(wi->info) = gimple_location (stmt);
2387 return integer_zero_node;
2390 bool found = false;
2391 location_t loc = gimple_location (stmt);
2393 gimple_stmt_iterator gsi2 = *gsi_p;
2394 stmt = gsi_stmt (gsi2);
2395 if (gimple_code (stmt) == GIMPLE_GOTO && !gimple_has_location (stmt))
2397 /* Go on until the artificial label. */
2398 tree goto_dest = gimple_goto_dest (stmt);
2399 for (; !gsi_end_p (gsi2); gsi_next (&gsi2))
2401 if (gimple_code (gsi_stmt (gsi2)) == GIMPLE_LABEL
2402 && gimple_label_label (as_a <glabel *> (gsi_stmt (gsi2)))
2403 == goto_dest)
2404 break;
2407 /* Not found? Stop. */
2408 if (gsi_end_p (gsi2))
2409 break;
2411 /* Look one past it. */
2412 gsi_next (&gsi2);
2415 /* We're looking for a case label or default label here. */
2416 while (!gsi_end_p (gsi2))
2418 stmt = gsi_stmt (gsi2);
2419 if (gimple_code (stmt) == GIMPLE_LABEL)
2421 tree label = gimple_label_label (as_a <glabel *> (stmt));
2422 if (gimple_has_location (stmt) && DECL_ARTIFICIAL (label))
2424 found = true;
2425 break;
2428 else if (gimple_call_internal_p (stmt, IFN_ASAN_MARK))
2430 else if (!is_gimple_debug (stmt))
2431 /* Anything else is not expected. */
2432 break;
2433 gsi_next (&gsi2);
2435 if (!found)
2436 pedwarn (loc, 0, "attribute %<fallthrough%> not preceding "
2437 "a case label or default label");
2439 break;
2440 default:
2441 break;
2443 return NULL_TREE;
2446 /* Expand all FALLTHROUGH () calls in SEQ. */
2448 static void
2449 expand_FALLTHROUGH (gimple_seq *seq_p)
2451 struct walk_stmt_info wi;
2452 location_t loc;
2453 memset (&wi, 0, sizeof (wi));
2454 wi.info = (void *) &loc;
2455 walk_gimple_seq_mod (seq_p, expand_FALLTHROUGH_r, NULL, &wi);
2456 if (wi.callback_result == integer_zero_node)
2457 /* We've found [[fallthrough]]; at the end of a switch, which the C++
2458 standard says is ill-formed; see [dcl.attr.fallthrough]. */
2459 pedwarn (loc, 0, "attribute %<fallthrough%> not preceding "
2460 "a case label or default label");
2464 /* Gimplify a SWITCH_EXPR, and collect the vector of labels it can
2465 branch to. */
2467 static enum gimplify_status
2468 gimplify_switch_expr (tree *expr_p, gimple_seq *pre_p)
2470 tree switch_expr = *expr_p;
2471 gimple_seq switch_body_seq = NULL;
2472 enum gimplify_status ret;
2473 tree index_type = TREE_TYPE (switch_expr);
2474 if (index_type == NULL_TREE)
2475 index_type = TREE_TYPE (SWITCH_COND (switch_expr));
2477 ret = gimplify_expr (&SWITCH_COND (switch_expr), pre_p, NULL, is_gimple_val,
2478 fb_rvalue);
2479 if (ret == GS_ERROR || ret == GS_UNHANDLED)
2480 return ret;
2482 if (SWITCH_BODY (switch_expr))
2484 vec<tree> labels;
2485 vec<tree> saved_labels;
2486 hash_set<tree> *saved_live_switch_vars = NULL;
2487 tree default_case = NULL_TREE;
2488 gswitch *switch_stmt;
2490 /* Save old labels, get new ones from body, then restore the old
2491 labels. Save all the things from the switch body to append after. */
2492 saved_labels = gimplify_ctxp->case_labels;
2493 gimplify_ctxp->case_labels.create (8);
2495 /* Do not create live_switch_vars if SWITCH_BODY is not a BIND_EXPR. */
2496 saved_live_switch_vars = gimplify_ctxp->live_switch_vars;
2497 tree_code body_type = TREE_CODE (SWITCH_BODY (switch_expr));
2498 if (body_type == BIND_EXPR || body_type == STATEMENT_LIST)
2499 gimplify_ctxp->live_switch_vars = new hash_set<tree> (4);
2500 else
2501 gimplify_ctxp->live_switch_vars = NULL;
2503 bool old_in_switch_expr = gimplify_ctxp->in_switch_expr;
2504 gimplify_ctxp->in_switch_expr = true;
2506 gimplify_stmt (&SWITCH_BODY (switch_expr), &switch_body_seq);
2508 gimplify_ctxp->in_switch_expr = old_in_switch_expr;
2509 maybe_warn_switch_unreachable (switch_body_seq);
2510 maybe_warn_implicit_fallthrough (switch_body_seq);
2511 /* Only do this for the outermost GIMPLE_SWITCH. */
2512 if (!gimplify_ctxp->in_switch_expr)
2513 expand_FALLTHROUGH (&switch_body_seq);
2515 labels = gimplify_ctxp->case_labels;
2516 gimplify_ctxp->case_labels = saved_labels;
2518 if (gimplify_ctxp->live_switch_vars)
2520 gcc_assert (gimplify_ctxp->live_switch_vars->is_empty ());
2521 delete gimplify_ctxp->live_switch_vars;
2523 gimplify_ctxp->live_switch_vars = saved_live_switch_vars;
2525 preprocess_case_label_vec_for_gimple (labels, index_type,
2526 &default_case);
2528 bool add_bind = false;
2529 if (!default_case)
2531 glabel *new_default;
2533 default_case
2534 = build_case_label (NULL_TREE, NULL_TREE,
2535 create_artificial_label (UNKNOWN_LOCATION));
2536 if (old_in_switch_expr)
2538 SWITCH_BREAK_LABEL_P (CASE_LABEL (default_case)) = 1;
2539 add_bind = true;
2541 new_default = gimple_build_label (CASE_LABEL (default_case));
2542 gimplify_seq_add_stmt (&switch_body_seq, new_default);
2544 else if (old_in_switch_expr)
2546 gimple *last = gimple_seq_last_stmt (switch_body_seq);
2547 if (last && gimple_code (last) == GIMPLE_LABEL)
2549 tree label = gimple_label_label (as_a <glabel *> (last));
2550 if (SWITCH_BREAK_LABEL_P (label))
2551 add_bind = true;
2555 switch_stmt = gimple_build_switch (SWITCH_COND (switch_expr),
2556 default_case, labels);
2557 /* For the benefit of -Wimplicit-fallthrough, if switch_body_seq
2558 ends with a GIMPLE_LABEL holding SWITCH_BREAK_LABEL_P LABEL_DECL,
2559 wrap the GIMPLE_SWITCH up to that GIMPLE_LABEL into a GIMPLE_BIND,
2560 so that we can easily find the start and end of the switch
2561 statement. */
2562 if (add_bind)
2564 gimple_seq bind_body = NULL;
2565 gimplify_seq_add_stmt (&bind_body, switch_stmt);
2566 gimple_seq_add_seq (&bind_body, switch_body_seq);
2567 gbind *bind = gimple_build_bind (NULL_TREE, bind_body, NULL_TREE);
2568 gimple_set_location (bind, EXPR_LOCATION (switch_expr));
2569 gimplify_seq_add_stmt (pre_p, bind);
2571 else
2573 gimplify_seq_add_stmt (pre_p, switch_stmt);
2574 gimplify_seq_add_seq (pre_p, switch_body_seq);
2576 labels.release ();
2578 else
2579 gcc_unreachable ();
2581 return GS_ALL_DONE;
2584 /* Gimplify the LABEL_EXPR pointed to by EXPR_P. */
2586 static enum gimplify_status
2587 gimplify_label_expr (tree *expr_p, gimple_seq *pre_p)
2589 gcc_assert (decl_function_context (LABEL_EXPR_LABEL (*expr_p))
2590 == current_function_decl);
2592 tree label = LABEL_EXPR_LABEL (*expr_p);
2593 glabel *label_stmt = gimple_build_label (label);
2594 gimple_set_location (label_stmt, EXPR_LOCATION (*expr_p));
2595 gimplify_seq_add_stmt (pre_p, label_stmt);
2597 if (lookup_attribute ("cold", DECL_ATTRIBUTES (label)))
2598 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_COLD_LABEL,
2599 NOT_TAKEN));
2600 else if (lookup_attribute ("hot", DECL_ATTRIBUTES (label)))
2601 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_HOT_LABEL,
2602 TAKEN));
2604 return GS_ALL_DONE;
2607 /* Gimplify the CASE_LABEL_EXPR pointed to by EXPR_P. */
2609 static enum gimplify_status
2610 gimplify_case_label_expr (tree *expr_p, gimple_seq *pre_p)
2612 struct gimplify_ctx *ctxp;
2613 glabel *label_stmt;
2615 /* Invalid programs can play Duff's Device type games with, for example,
2616 #pragma omp parallel. At least in the C front end, we don't
2617 detect such invalid branches until after gimplification, in the
2618 diagnose_omp_blocks pass. */
2619 for (ctxp = gimplify_ctxp; ; ctxp = ctxp->prev_context)
2620 if (ctxp->case_labels.exists ())
2621 break;
2623 tree label = CASE_LABEL (*expr_p);
2624 label_stmt = gimple_build_label (label);
2625 gimple_set_location (label_stmt, EXPR_LOCATION (*expr_p));
2626 ctxp->case_labels.safe_push (*expr_p);
2627 gimplify_seq_add_stmt (pre_p, label_stmt);
2629 if (lookup_attribute ("cold", DECL_ATTRIBUTES (label)))
2630 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_COLD_LABEL,
2631 NOT_TAKEN));
2632 else if (lookup_attribute ("hot", DECL_ATTRIBUTES (label)))
2633 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_HOT_LABEL,
2634 TAKEN));
2636 return GS_ALL_DONE;
2639 /* Build a GOTO to the LABEL_DECL pointed to by LABEL_P, building it first
2640 if necessary. */
2642 tree
2643 build_and_jump (tree *label_p)
2645 if (label_p == NULL)
2646 /* If there's nowhere to jump, just fall through. */
2647 return NULL_TREE;
2649 if (*label_p == NULL_TREE)
2651 tree label = create_artificial_label (UNKNOWN_LOCATION);
2652 *label_p = label;
2655 return build1 (GOTO_EXPR, void_type_node, *label_p);
2658 /* Gimplify an EXIT_EXPR by converting to a GOTO_EXPR inside a COND_EXPR.
2659 This also involves building a label to jump to and communicating it to
2660 gimplify_loop_expr through gimplify_ctxp->exit_label. */
2662 static enum gimplify_status
2663 gimplify_exit_expr (tree *expr_p)
2665 tree cond = TREE_OPERAND (*expr_p, 0);
2666 tree expr;
2668 expr = build_and_jump (&gimplify_ctxp->exit_label);
2669 expr = build3 (COND_EXPR, void_type_node, cond, expr, NULL_TREE);
2670 *expr_p = expr;
2672 return GS_OK;
2675 /* *EXPR_P is a COMPONENT_REF being used as an rvalue. If its type is
2676 different from its canonical type, wrap the whole thing inside a
2677 NOP_EXPR and force the type of the COMPONENT_REF to be the canonical
2678 type.
2680 The canonical type of a COMPONENT_REF is the type of the field being
2681 referenced--unless the field is a bit-field which can be read directly
2682 in a smaller mode, in which case the canonical type is the
2683 sign-appropriate type corresponding to that mode. */
2685 static void
2686 canonicalize_component_ref (tree *expr_p)
2688 tree expr = *expr_p;
2689 tree type;
2691 gcc_assert (TREE_CODE (expr) == COMPONENT_REF);
2693 if (INTEGRAL_TYPE_P (TREE_TYPE (expr)))
2694 type = TREE_TYPE (get_unwidened (expr, NULL_TREE));
2695 else
2696 type = TREE_TYPE (TREE_OPERAND (expr, 1));
2698 /* One could argue that all the stuff below is not necessary for
2699 the non-bitfield case and declare it a FE error if type
2700 adjustment would be needed. */
2701 if (TREE_TYPE (expr) != type)
2703 #ifdef ENABLE_TYPES_CHECKING
2704 tree old_type = TREE_TYPE (expr);
2705 #endif
2706 int type_quals;
2708 /* We need to preserve qualifiers and propagate them from
2709 operand 0. */
2710 type_quals = TYPE_QUALS (type)
2711 | TYPE_QUALS (TREE_TYPE (TREE_OPERAND (expr, 0)));
2712 if (TYPE_QUALS (type) != type_quals)
2713 type = build_qualified_type (TYPE_MAIN_VARIANT (type), type_quals);
2715 /* Set the type of the COMPONENT_REF to the underlying type. */
2716 TREE_TYPE (expr) = type;
2718 #ifdef ENABLE_TYPES_CHECKING
2719 /* It is now a FE error, if the conversion from the canonical
2720 type to the original expression type is not useless. */
2721 gcc_assert (useless_type_conversion_p (old_type, type));
2722 #endif
2726 /* If a NOP conversion is changing a pointer to array of foo to a pointer
2727 to foo, embed that change in the ADDR_EXPR by converting
2728 T array[U];
2729 (T *)&array
2731 &array[L]
2732 where L is the lower bound. For simplicity, only do this for constant
2733 lower bound.
2734 The constraint is that the type of &array[L] is trivially convertible
2735 to T *. */
2737 static void
2738 canonicalize_addr_expr (tree *expr_p)
2740 tree expr = *expr_p;
2741 tree addr_expr = TREE_OPERAND (expr, 0);
2742 tree datype, ddatype, pddatype;
2744 /* We simplify only conversions from an ADDR_EXPR to a pointer type. */
2745 if (!POINTER_TYPE_P (TREE_TYPE (expr))
2746 || TREE_CODE (addr_expr) != ADDR_EXPR)
2747 return;
2749 /* The addr_expr type should be a pointer to an array. */
2750 datype = TREE_TYPE (TREE_TYPE (addr_expr));
2751 if (TREE_CODE (datype) != ARRAY_TYPE)
2752 return;
2754 /* The pointer to element type shall be trivially convertible to
2755 the expression pointer type. */
2756 ddatype = TREE_TYPE (datype);
2757 pddatype = build_pointer_type (ddatype);
2758 if (!useless_type_conversion_p (TYPE_MAIN_VARIANT (TREE_TYPE (expr)),
2759 pddatype))
2760 return;
2762 /* The lower bound and element sizes must be constant. */
2763 if (!TYPE_SIZE_UNIT (ddatype)
2764 || TREE_CODE (TYPE_SIZE_UNIT (ddatype)) != INTEGER_CST
2765 || !TYPE_DOMAIN (datype) || !TYPE_MIN_VALUE (TYPE_DOMAIN (datype))
2766 || TREE_CODE (TYPE_MIN_VALUE (TYPE_DOMAIN (datype))) != INTEGER_CST)
2767 return;
2769 /* All checks succeeded. Build a new node to merge the cast. */
2770 *expr_p = build4 (ARRAY_REF, ddatype, TREE_OPERAND (addr_expr, 0),
2771 TYPE_MIN_VALUE (TYPE_DOMAIN (datype)),
2772 NULL_TREE, NULL_TREE);
2773 *expr_p = build1 (ADDR_EXPR, pddatype, *expr_p);
2775 /* We can have stripped a required restrict qualifier above. */
2776 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
2777 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
2780 /* *EXPR_P is a NOP_EXPR or CONVERT_EXPR. Remove it and/or other conversions
2781 underneath as appropriate. */
2783 static enum gimplify_status
2784 gimplify_conversion (tree *expr_p)
2786 location_t loc = EXPR_LOCATION (*expr_p);
2787 gcc_assert (CONVERT_EXPR_P (*expr_p));
2789 /* Then strip away all but the outermost conversion. */
2790 STRIP_SIGN_NOPS (TREE_OPERAND (*expr_p, 0));
2792 /* And remove the outermost conversion if it's useless. */
2793 if (tree_ssa_useless_type_conversion (*expr_p))
2794 *expr_p = TREE_OPERAND (*expr_p, 0);
2796 /* If we still have a conversion at the toplevel,
2797 then canonicalize some constructs. */
2798 if (CONVERT_EXPR_P (*expr_p))
2800 tree sub = TREE_OPERAND (*expr_p, 0);
2802 /* If a NOP conversion is changing the type of a COMPONENT_REF
2803 expression, then canonicalize its type now in order to expose more
2804 redundant conversions. */
2805 if (TREE_CODE (sub) == COMPONENT_REF)
2806 canonicalize_component_ref (&TREE_OPERAND (*expr_p, 0));
2808 /* If a NOP conversion is changing a pointer to array of foo
2809 to a pointer to foo, embed that change in the ADDR_EXPR. */
2810 else if (TREE_CODE (sub) == ADDR_EXPR)
2811 canonicalize_addr_expr (expr_p);
2814 /* If we have a conversion to a non-register type force the
2815 use of a VIEW_CONVERT_EXPR instead. */
2816 if (CONVERT_EXPR_P (*expr_p) && !is_gimple_reg_type (TREE_TYPE (*expr_p)))
2817 *expr_p = fold_build1_loc (loc, VIEW_CONVERT_EXPR, TREE_TYPE (*expr_p),
2818 TREE_OPERAND (*expr_p, 0));
2820 /* Canonicalize CONVERT_EXPR to NOP_EXPR. */
2821 if (TREE_CODE (*expr_p) == CONVERT_EXPR)
2822 TREE_SET_CODE (*expr_p, NOP_EXPR);
2824 return GS_OK;
2827 /* Gimplify a VAR_DECL or PARM_DECL. Return GS_OK if we expanded a
2828 DECL_VALUE_EXPR, and it's worth re-examining things. */
2830 static enum gimplify_status
2831 gimplify_var_or_parm_decl (tree *expr_p)
2833 tree decl = *expr_p;
2835 /* ??? If this is a local variable, and it has not been seen in any
2836 outer BIND_EXPR, then it's probably the result of a duplicate
2837 declaration, for which we've already issued an error. It would
2838 be really nice if the front end wouldn't leak these at all.
2839 Currently the only known culprit is C++ destructors, as seen
2840 in g++.old-deja/g++.jason/binding.C. */
2841 if (VAR_P (decl)
2842 && !DECL_SEEN_IN_BIND_EXPR_P (decl)
2843 && !TREE_STATIC (decl) && !DECL_EXTERNAL (decl)
2844 && decl_function_context (decl) == current_function_decl)
2846 gcc_assert (seen_error ());
2847 return GS_ERROR;
2850 /* When within an OMP context, notice uses of variables. */
2851 if (gimplify_omp_ctxp && omp_notice_variable (gimplify_omp_ctxp, decl, true))
2852 return GS_ALL_DONE;
2854 /* If the decl is an alias for another expression, substitute it now. */
2855 if (DECL_HAS_VALUE_EXPR_P (decl))
2857 *expr_p = unshare_expr (DECL_VALUE_EXPR (decl));
2858 return GS_OK;
2861 return GS_ALL_DONE;
2864 /* Recalculate the value of the TREE_SIDE_EFFECTS flag for T. */
2866 static void
2867 recalculate_side_effects (tree t)
2869 enum tree_code code = TREE_CODE (t);
2870 int len = TREE_OPERAND_LENGTH (t);
2871 int i;
2873 switch (TREE_CODE_CLASS (code))
2875 case tcc_expression:
2876 switch (code)
2878 case INIT_EXPR:
2879 case MODIFY_EXPR:
2880 case VA_ARG_EXPR:
2881 case PREDECREMENT_EXPR:
2882 case PREINCREMENT_EXPR:
2883 case POSTDECREMENT_EXPR:
2884 case POSTINCREMENT_EXPR:
2885 /* All of these have side-effects, no matter what their
2886 operands are. */
2887 return;
2889 default:
2890 break;
2892 /* Fall through. */
2894 case tcc_comparison: /* a comparison expression */
2895 case tcc_unary: /* a unary arithmetic expression */
2896 case tcc_binary: /* a binary arithmetic expression */
2897 case tcc_reference: /* a reference */
2898 case tcc_vl_exp: /* a function call */
2899 TREE_SIDE_EFFECTS (t) = TREE_THIS_VOLATILE (t);
2900 for (i = 0; i < len; ++i)
2902 tree op = TREE_OPERAND (t, i);
2903 if (op && TREE_SIDE_EFFECTS (op))
2904 TREE_SIDE_EFFECTS (t) = 1;
2906 break;
2908 case tcc_constant:
2909 /* No side-effects. */
2910 return;
2912 default:
2913 gcc_unreachable ();
2917 /* Gimplify the COMPONENT_REF, ARRAY_REF, REALPART_EXPR or IMAGPART_EXPR
2918 node *EXPR_P.
2920 compound_lval
2921 : min_lval '[' val ']'
2922 | min_lval '.' ID
2923 | compound_lval '[' val ']'
2924 | compound_lval '.' ID
2926 This is not part of the original SIMPLE definition, which separates
2927 array and member references, but it seems reasonable to handle them
2928 together. Also, this way we don't run into problems with union
2929 aliasing; gcc requires that for accesses through a union to alias, the
2930 union reference must be explicit, which was not always the case when we
2931 were splitting up array and member refs.
2933 PRE_P points to the sequence where side effects that must happen before
2934 *EXPR_P should be stored.
2936 POST_P points to the sequence where side effects that must happen after
2937 *EXPR_P should be stored. */
2939 static enum gimplify_status
2940 gimplify_compound_lval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
2941 fallback_t fallback)
2943 tree *p;
2944 enum gimplify_status ret = GS_ALL_DONE, tret;
2945 int i;
2946 location_t loc = EXPR_LOCATION (*expr_p);
2947 tree expr = *expr_p;
2949 /* Create a stack of the subexpressions so later we can walk them in
2950 order from inner to outer. */
2951 auto_vec<tree, 10> expr_stack;
2953 /* We can handle anything that get_inner_reference can deal with. */
2954 for (p = expr_p; ; p = &TREE_OPERAND (*p, 0))
2956 restart:
2957 /* Fold INDIRECT_REFs now to turn them into ARRAY_REFs. */
2958 if (TREE_CODE (*p) == INDIRECT_REF)
2959 *p = fold_indirect_ref_loc (loc, *p);
2961 if (handled_component_p (*p))
2963 /* Expand DECL_VALUE_EXPR now. In some cases that may expose
2964 additional COMPONENT_REFs. */
2965 else if ((VAR_P (*p) || TREE_CODE (*p) == PARM_DECL)
2966 && gimplify_var_or_parm_decl (p) == GS_OK)
2967 goto restart;
2968 else
2969 break;
2971 expr_stack.safe_push (*p);
2974 gcc_assert (expr_stack.length ());
2976 /* Now EXPR_STACK is a stack of pointers to all the refs we've
2977 walked through and P points to the innermost expression.
2979 Java requires that we elaborated nodes in source order. That
2980 means we must gimplify the inner expression followed by each of
2981 the indices, in order. But we can't gimplify the inner
2982 expression until we deal with any variable bounds, sizes, or
2983 positions in order to deal with PLACEHOLDER_EXPRs.
2985 So we do this in three steps. First we deal with the annotations
2986 for any variables in the components, then we gimplify the base,
2987 then we gimplify any indices, from left to right. */
2988 for (i = expr_stack.length () - 1; i >= 0; i--)
2990 tree t = expr_stack[i];
2992 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
2994 /* Gimplify the low bound and element type size and put them into
2995 the ARRAY_REF. If these values are set, they have already been
2996 gimplified. */
2997 if (TREE_OPERAND (t, 2) == NULL_TREE)
2999 tree low = unshare_expr (array_ref_low_bound (t));
3000 if (!is_gimple_min_invariant (low))
3002 TREE_OPERAND (t, 2) = low;
3003 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
3004 post_p, is_gimple_reg,
3005 fb_rvalue);
3006 ret = MIN (ret, tret);
3009 else
3011 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
3012 is_gimple_reg, fb_rvalue);
3013 ret = MIN (ret, tret);
3016 if (TREE_OPERAND (t, 3) == NULL_TREE)
3018 tree elmt_size = array_ref_element_size (t);
3019 if (!is_gimple_min_invariant (elmt_size))
3021 elmt_size = unshare_expr (elmt_size);
3022 tree elmt_type = TREE_TYPE (TREE_TYPE (TREE_OPERAND (t, 0)));
3023 tree factor = size_int (TYPE_ALIGN_UNIT (elmt_type));
3025 /* Divide the element size by the alignment of the element
3026 type (above). */
3027 elmt_size = size_binop_loc (loc, EXACT_DIV_EXPR,
3028 elmt_size, factor);
3030 TREE_OPERAND (t, 3) = elmt_size;
3031 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p,
3032 post_p, is_gimple_reg,
3033 fb_rvalue);
3034 ret = MIN (ret, tret);
3037 else
3039 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p, post_p,
3040 is_gimple_reg, fb_rvalue);
3041 ret = MIN (ret, tret);
3044 else if (TREE_CODE (t) == COMPONENT_REF)
3046 /* Set the field offset into T and gimplify it. */
3047 if (TREE_OPERAND (t, 2) == NULL_TREE)
3049 tree offset = component_ref_field_offset (t);
3050 if (!is_gimple_min_invariant (offset))
3052 offset = unshare_expr (offset);
3053 tree field = TREE_OPERAND (t, 1);
3054 tree factor
3055 = size_int (DECL_OFFSET_ALIGN (field) / BITS_PER_UNIT);
3057 /* Divide the offset by its alignment. */
3058 offset = size_binop_loc (loc, EXACT_DIV_EXPR,
3059 offset, factor);
3061 TREE_OPERAND (t, 2) = offset;
3062 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
3063 post_p, is_gimple_reg,
3064 fb_rvalue);
3065 ret = MIN (ret, tret);
3068 else
3070 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
3071 is_gimple_reg, fb_rvalue);
3072 ret = MIN (ret, tret);
3077 /* Step 2 is to gimplify the base expression. Make sure lvalue is set
3078 so as to match the min_lval predicate. Failure to do so may result
3079 in the creation of large aggregate temporaries. */
3080 tret = gimplify_expr (p, pre_p, post_p, is_gimple_min_lval,
3081 fallback | fb_lvalue);
3082 ret = MIN (ret, tret);
3084 /* And finally, the indices and operands of ARRAY_REF. During this
3085 loop we also remove any useless conversions. */
3086 for (; expr_stack.length () > 0; )
3088 tree t = expr_stack.pop ();
3090 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
3092 /* Gimplify the dimension. */
3093 if (!is_gimple_min_invariant (TREE_OPERAND (t, 1)))
3095 tret = gimplify_expr (&TREE_OPERAND (t, 1), pre_p, post_p,
3096 is_gimple_val, fb_rvalue);
3097 ret = MIN (ret, tret);
3101 STRIP_USELESS_TYPE_CONVERSION (TREE_OPERAND (t, 0));
3103 /* The innermost expression P may have originally had
3104 TREE_SIDE_EFFECTS set which would have caused all the outer
3105 expressions in *EXPR_P leading to P to also have had
3106 TREE_SIDE_EFFECTS set. */
3107 recalculate_side_effects (t);
3110 /* If the outermost expression is a COMPONENT_REF, canonicalize its type. */
3111 if ((fallback & fb_rvalue) && TREE_CODE (*expr_p) == COMPONENT_REF)
3113 canonicalize_component_ref (expr_p);
3116 expr_stack.release ();
3118 gcc_assert (*expr_p == expr || ret != GS_ALL_DONE);
3120 return ret;
3123 /* Gimplify the self modifying expression pointed to by EXPR_P
3124 (++, --, +=, -=).
3126 PRE_P points to the list where side effects that must happen before
3127 *EXPR_P should be stored.
3129 POST_P points to the list where side effects that must happen after
3130 *EXPR_P should be stored.
3132 WANT_VALUE is nonzero iff we want to use the value of this expression
3133 in another expression.
3135 ARITH_TYPE is the type the computation should be performed in. */
3137 enum gimplify_status
3138 gimplify_self_mod_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
3139 bool want_value, tree arith_type)
3141 enum tree_code code;
3142 tree lhs, lvalue, rhs, t1;
3143 gimple_seq post = NULL, *orig_post_p = post_p;
3144 bool postfix;
3145 enum tree_code arith_code;
3146 enum gimplify_status ret;
3147 location_t loc = EXPR_LOCATION (*expr_p);
3149 code = TREE_CODE (*expr_p);
3151 gcc_assert (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR
3152 || code == PREINCREMENT_EXPR || code == PREDECREMENT_EXPR);
3154 /* Prefix or postfix? */
3155 if (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR)
3156 /* Faster to treat as prefix if result is not used. */
3157 postfix = want_value;
3158 else
3159 postfix = false;
3161 /* For postfix, make sure the inner expression's post side effects
3162 are executed after side effects from this expression. */
3163 if (postfix)
3164 post_p = &post;
3166 /* Add or subtract? */
3167 if (code == PREINCREMENT_EXPR || code == POSTINCREMENT_EXPR)
3168 arith_code = PLUS_EXPR;
3169 else
3170 arith_code = MINUS_EXPR;
3172 /* Gimplify the LHS into a GIMPLE lvalue. */
3173 lvalue = TREE_OPERAND (*expr_p, 0);
3174 ret = gimplify_expr (&lvalue, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
3175 if (ret == GS_ERROR)
3176 return ret;
3178 /* Extract the operands to the arithmetic operation. */
3179 lhs = lvalue;
3180 rhs = TREE_OPERAND (*expr_p, 1);
3182 /* For postfix operator, we evaluate the LHS to an rvalue and then use
3183 that as the result value and in the postqueue operation. */
3184 if (postfix)
3186 ret = gimplify_expr (&lhs, pre_p, post_p, is_gimple_val, fb_rvalue);
3187 if (ret == GS_ERROR)
3188 return ret;
3190 lhs = get_initialized_tmp_var (lhs, pre_p);
3193 /* For POINTERs increment, use POINTER_PLUS_EXPR. */
3194 if (POINTER_TYPE_P (TREE_TYPE (lhs)))
3196 rhs = convert_to_ptrofftype_loc (loc, rhs);
3197 if (arith_code == MINUS_EXPR)
3198 rhs = fold_build1_loc (loc, NEGATE_EXPR, TREE_TYPE (rhs), rhs);
3199 t1 = fold_build2 (POINTER_PLUS_EXPR, TREE_TYPE (*expr_p), lhs, rhs);
3201 else
3202 t1 = fold_convert (TREE_TYPE (*expr_p),
3203 fold_build2 (arith_code, arith_type,
3204 fold_convert (arith_type, lhs),
3205 fold_convert (arith_type, rhs)));
3207 if (postfix)
3209 gimplify_assign (lvalue, t1, pre_p);
3210 gimplify_seq_add_seq (orig_post_p, post);
3211 *expr_p = lhs;
3212 return GS_ALL_DONE;
3214 else
3216 *expr_p = build2 (MODIFY_EXPR, TREE_TYPE (lvalue), lvalue, t1);
3217 return GS_OK;
3221 /* If *EXPR_P has a variable sized type, wrap it in a WITH_SIZE_EXPR. */
3223 static void
3224 maybe_with_size_expr (tree *expr_p)
3226 tree expr = *expr_p;
3227 tree type = TREE_TYPE (expr);
3228 tree size;
3230 /* If we've already wrapped this or the type is error_mark_node, we can't do
3231 anything. */
3232 if (TREE_CODE (expr) == WITH_SIZE_EXPR
3233 || type == error_mark_node)
3234 return;
3236 /* If the size isn't known or is a constant, we have nothing to do. */
3237 size = TYPE_SIZE_UNIT (type);
3238 if (!size || poly_int_tree_p (size))
3239 return;
3241 /* Otherwise, make a WITH_SIZE_EXPR. */
3242 size = unshare_expr (size);
3243 size = SUBSTITUTE_PLACEHOLDER_IN_EXPR (size, expr);
3244 *expr_p = build2 (WITH_SIZE_EXPR, type, expr, size);
3247 /* Helper for gimplify_call_expr. Gimplify a single argument *ARG_P
3248 Store any side-effects in PRE_P. CALL_LOCATION is the location of
3249 the CALL_EXPR. If ALLOW_SSA is set the actual parameter may be
3250 gimplified to an SSA name. */
3252 enum gimplify_status
3253 gimplify_arg (tree *arg_p, gimple_seq *pre_p, location_t call_location,
3254 bool allow_ssa)
3256 bool (*test) (tree);
3257 fallback_t fb;
3259 /* In general, we allow lvalues for function arguments to avoid
3260 extra overhead of copying large aggregates out of even larger
3261 aggregates into temporaries only to copy the temporaries to
3262 the argument list. Make optimizers happy by pulling out to
3263 temporaries those types that fit in registers. */
3264 if (is_gimple_reg_type (TREE_TYPE (*arg_p)))
3265 test = is_gimple_val, fb = fb_rvalue;
3266 else
3268 test = is_gimple_lvalue, fb = fb_either;
3269 /* Also strip a TARGET_EXPR that would force an extra copy. */
3270 if (TREE_CODE (*arg_p) == TARGET_EXPR)
3272 tree init = TARGET_EXPR_INITIAL (*arg_p);
3273 if (init
3274 && !VOID_TYPE_P (TREE_TYPE (init)))
3275 *arg_p = init;
3279 /* If this is a variable sized type, we must remember the size. */
3280 maybe_with_size_expr (arg_p);
3282 /* FIXME diagnostics: This will mess up gcc.dg/Warray-bounds.c. */
3283 /* Make sure arguments have the same location as the function call
3284 itself. */
3285 protected_set_expr_location (*arg_p, call_location);
3287 /* There is a sequence point before a function call. Side effects in
3288 the argument list must occur before the actual call. So, when
3289 gimplifying arguments, force gimplify_expr to use an internal
3290 post queue which is then appended to the end of PRE_P. */
3291 return gimplify_expr (arg_p, pre_p, NULL, test, fb, allow_ssa);
3294 /* Don't fold inside offloading or taskreg regions: it can break code by
3295 adding decl references that weren't in the source. We'll do it during
3296 omplower pass instead. */
3298 static bool
3299 maybe_fold_stmt (gimple_stmt_iterator *gsi)
3301 struct gimplify_omp_ctx *ctx;
3302 for (ctx = gimplify_omp_ctxp; ctx; ctx = ctx->outer_context)
3303 if ((ctx->region_type & (ORT_TARGET | ORT_PARALLEL | ORT_TASK)) != 0)
3304 return false;
3305 else if ((ctx->region_type & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
3306 return false;
3307 /* Delay folding of builtins until the IL is in consistent state
3308 so the diagnostic machinery can do a better job. */
3309 if (gimple_call_builtin_p (gsi_stmt (*gsi)))
3310 return false;
3311 return fold_stmt (gsi);
3314 /* Gimplify the CALL_EXPR node *EXPR_P into the GIMPLE sequence PRE_P.
3315 WANT_VALUE is true if the result of the call is desired. */
3317 static enum gimplify_status
3318 gimplify_call_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
3320 tree fndecl, parms, p, fnptrtype;
3321 enum gimplify_status ret;
3322 int i, nargs;
3323 gcall *call;
3324 bool builtin_va_start_p = false;
3325 location_t loc = EXPR_LOCATION (*expr_p);
3327 gcc_assert (TREE_CODE (*expr_p) == CALL_EXPR);
3329 /* For reliable diagnostics during inlining, it is necessary that
3330 every call_expr be annotated with file and line. */
3331 if (! EXPR_HAS_LOCATION (*expr_p))
3332 SET_EXPR_LOCATION (*expr_p, input_location);
3334 /* Gimplify internal functions created in the FEs. */
3335 if (CALL_EXPR_FN (*expr_p) == NULL_TREE)
3337 if (want_value)
3338 return GS_ALL_DONE;
3340 nargs = call_expr_nargs (*expr_p);
3341 enum internal_fn ifn = CALL_EXPR_IFN (*expr_p);
3342 auto_vec<tree> vargs (nargs);
3344 for (i = 0; i < nargs; i++)
3346 gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
3347 EXPR_LOCATION (*expr_p));
3348 vargs.quick_push (CALL_EXPR_ARG (*expr_p, i));
3351 gcall *call = gimple_build_call_internal_vec (ifn, vargs);
3352 gimple_call_set_nothrow (call, TREE_NOTHROW (*expr_p));
3353 gimplify_seq_add_stmt (pre_p, call);
3354 return GS_ALL_DONE;
3357 /* This may be a call to a builtin function.
3359 Builtin function calls may be transformed into different
3360 (and more efficient) builtin function calls under certain
3361 circumstances. Unfortunately, gimplification can muck things
3362 up enough that the builtin expanders are not aware that certain
3363 transformations are still valid.
3365 So we attempt transformation/gimplification of the call before
3366 we gimplify the CALL_EXPR. At this time we do not manage to
3367 transform all calls in the same manner as the expanders do, but
3368 we do transform most of them. */
3369 fndecl = get_callee_fndecl (*expr_p);
3370 if (fndecl && fndecl_built_in_p (fndecl, BUILT_IN_NORMAL))
3371 switch (DECL_FUNCTION_CODE (fndecl))
3373 CASE_BUILT_IN_ALLOCA:
3374 /* If the call has been built for a variable-sized object, then we
3375 want to restore the stack level when the enclosing BIND_EXPR is
3376 exited to reclaim the allocated space; otherwise, we precisely
3377 need to do the opposite and preserve the latest stack level. */
3378 if (CALL_ALLOCA_FOR_VAR_P (*expr_p))
3379 gimplify_ctxp->save_stack = true;
3380 else
3381 gimplify_ctxp->keep_stack = true;
3382 break;
3384 case BUILT_IN_VA_START:
3386 builtin_va_start_p = TRUE;
3387 if (call_expr_nargs (*expr_p) < 2)
3389 error ("too few arguments to function %<va_start%>");
3390 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
3391 return GS_OK;
3394 if (fold_builtin_next_arg (*expr_p, true))
3396 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
3397 return GS_OK;
3399 break;
3402 case BUILT_IN_EH_RETURN:
3403 cfun->calls_eh_return = true;
3404 break;
3406 case BUILT_IN_CLEAR_PADDING:
3407 if (call_expr_nargs (*expr_p) == 1)
3409 /* Remember the original type of the argument in an internal
3410 dummy second argument, as in GIMPLE pointer conversions are
3411 useless. */
3412 p = CALL_EXPR_ARG (*expr_p, 0);
3413 *expr_p
3414 = build_call_expr_loc (EXPR_LOCATION (*expr_p), fndecl, 2, p,
3415 build_zero_cst (TREE_TYPE (p)));
3416 return GS_OK;
3418 break;
3420 default:
3423 if (fndecl && fndecl_built_in_p (fndecl))
3425 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
3426 if (new_tree && new_tree != *expr_p)
3428 /* There was a transformation of this call which computes the
3429 same value, but in a more efficient way. Return and try
3430 again. */
3431 *expr_p = new_tree;
3432 return GS_OK;
3436 /* Remember the original function pointer type. */
3437 fnptrtype = TREE_TYPE (CALL_EXPR_FN (*expr_p));
3439 if (flag_openmp
3440 && fndecl
3441 && cfun
3442 && (cfun->curr_properties & PROP_gimple_any) == 0)
3444 tree variant = omp_resolve_declare_variant (fndecl);
3445 if (variant != fndecl)
3446 CALL_EXPR_FN (*expr_p) = build1 (ADDR_EXPR, fnptrtype, variant);
3449 /* There is a sequence point before the call, so any side effects in
3450 the calling expression must occur before the actual call. Force
3451 gimplify_expr to use an internal post queue. */
3452 ret = gimplify_expr (&CALL_EXPR_FN (*expr_p), pre_p, NULL,
3453 is_gimple_call_addr, fb_rvalue);
3455 nargs = call_expr_nargs (*expr_p);
3457 /* Get argument types for verification. */
3458 fndecl = get_callee_fndecl (*expr_p);
3459 parms = NULL_TREE;
3460 if (fndecl)
3461 parms = TYPE_ARG_TYPES (TREE_TYPE (fndecl));
3462 else
3463 parms = TYPE_ARG_TYPES (TREE_TYPE (fnptrtype));
3465 if (fndecl && DECL_ARGUMENTS (fndecl))
3466 p = DECL_ARGUMENTS (fndecl);
3467 else if (parms)
3468 p = parms;
3469 else
3470 p = NULL_TREE;
3471 for (i = 0; i < nargs && p; i++, p = TREE_CHAIN (p))
3474 /* If the last argument is __builtin_va_arg_pack () and it is not
3475 passed as a named argument, decrease the number of CALL_EXPR
3476 arguments and set instead the CALL_EXPR_VA_ARG_PACK flag. */
3477 if (!p
3478 && i < nargs
3479 && TREE_CODE (CALL_EXPR_ARG (*expr_p, nargs - 1)) == CALL_EXPR)
3481 tree last_arg = CALL_EXPR_ARG (*expr_p, nargs - 1);
3482 tree last_arg_fndecl = get_callee_fndecl (last_arg);
3484 if (last_arg_fndecl
3485 && fndecl_built_in_p (last_arg_fndecl, BUILT_IN_VA_ARG_PACK))
3487 tree call = *expr_p;
3489 --nargs;
3490 *expr_p = build_call_array_loc (loc, TREE_TYPE (call),
3491 CALL_EXPR_FN (call),
3492 nargs, CALL_EXPR_ARGP (call));
3494 /* Copy all CALL_EXPR flags, location and block, except
3495 CALL_EXPR_VA_ARG_PACK flag. */
3496 CALL_EXPR_STATIC_CHAIN (*expr_p) = CALL_EXPR_STATIC_CHAIN (call);
3497 CALL_EXPR_TAILCALL (*expr_p) = CALL_EXPR_TAILCALL (call);
3498 CALL_EXPR_RETURN_SLOT_OPT (*expr_p)
3499 = CALL_EXPR_RETURN_SLOT_OPT (call);
3500 CALL_FROM_THUNK_P (*expr_p) = CALL_FROM_THUNK_P (call);
3501 SET_EXPR_LOCATION (*expr_p, EXPR_LOCATION (call));
3503 /* Set CALL_EXPR_VA_ARG_PACK. */
3504 CALL_EXPR_VA_ARG_PACK (*expr_p) = 1;
3508 /* If the call returns twice then after building the CFG the call
3509 argument computations will no longer dominate the call because
3510 we add an abnormal incoming edge to the call. So do not use SSA
3511 vars there. */
3512 bool returns_twice = call_expr_flags (*expr_p) & ECF_RETURNS_TWICE;
3514 /* Gimplify the function arguments. */
3515 if (nargs > 0)
3517 for (i = (PUSH_ARGS_REVERSED ? nargs - 1 : 0);
3518 PUSH_ARGS_REVERSED ? i >= 0 : i < nargs;
3519 PUSH_ARGS_REVERSED ? i-- : i++)
3521 enum gimplify_status t;
3523 /* Avoid gimplifying the second argument to va_start, which needs to
3524 be the plain PARM_DECL. */
3525 if ((i != 1) || !builtin_va_start_p)
3527 t = gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
3528 EXPR_LOCATION (*expr_p), ! returns_twice);
3530 if (t == GS_ERROR)
3531 ret = GS_ERROR;
3536 /* Gimplify the static chain. */
3537 if (CALL_EXPR_STATIC_CHAIN (*expr_p))
3539 if (fndecl && !DECL_STATIC_CHAIN (fndecl))
3540 CALL_EXPR_STATIC_CHAIN (*expr_p) = NULL;
3541 else
3543 enum gimplify_status t;
3544 t = gimplify_arg (&CALL_EXPR_STATIC_CHAIN (*expr_p), pre_p,
3545 EXPR_LOCATION (*expr_p), ! returns_twice);
3546 if (t == GS_ERROR)
3547 ret = GS_ERROR;
3551 /* Verify the function result. */
3552 if (want_value && fndecl
3553 && VOID_TYPE_P (TREE_TYPE (TREE_TYPE (fnptrtype))))
3555 error_at (loc, "using result of function returning %<void%>");
3556 ret = GS_ERROR;
3559 /* Try this again in case gimplification exposed something. */
3560 if (ret != GS_ERROR)
3562 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
3564 if (new_tree && new_tree != *expr_p)
3566 /* There was a transformation of this call which computes the
3567 same value, but in a more efficient way. Return and try
3568 again. */
3569 *expr_p = new_tree;
3570 return GS_OK;
3573 else
3575 *expr_p = error_mark_node;
3576 return GS_ERROR;
3579 /* If the function is "const" or "pure", then clear TREE_SIDE_EFFECTS on its
3580 decl. This allows us to eliminate redundant or useless
3581 calls to "const" functions. */
3582 if (TREE_CODE (*expr_p) == CALL_EXPR)
3584 int flags = call_expr_flags (*expr_p);
3585 if (flags & (ECF_CONST | ECF_PURE)
3586 /* An infinite loop is considered a side effect. */
3587 && !(flags & (ECF_LOOPING_CONST_OR_PURE)))
3588 TREE_SIDE_EFFECTS (*expr_p) = 0;
3591 /* If the value is not needed by the caller, emit a new GIMPLE_CALL
3592 and clear *EXPR_P. Otherwise, leave *EXPR_P in its gimplified
3593 form and delegate the creation of a GIMPLE_CALL to
3594 gimplify_modify_expr. This is always possible because when
3595 WANT_VALUE is true, the caller wants the result of this call into
3596 a temporary, which means that we will emit an INIT_EXPR in
3597 internal_get_tmp_var which will then be handled by
3598 gimplify_modify_expr. */
3599 if (!want_value)
3601 /* The CALL_EXPR in *EXPR_P is already in GIMPLE form, so all we
3602 have to do is replicate it as a GIMPLE_CALL tuple. */
3603 gimple_stmt_iterator gsi;
3604 call = gimple_build_call_from_tree (*expr_p, fnptrtype);
3605 notice_special_calls (call);
3606 gimplify_seq_add_stmt (pre_p, call);
3607 gsi = gsi_last (*pre_p);
3608 maybe_fold_stmt (&gsi);
3609 *expr_p = NULL_TREE;
3611 else
3612 /* Remember the original function type. */
3613 CALL_EXPR_FN (*expr_p) = build1 (NOP_EXPR, fnptrtype,
3614 CALL_EXPR_FN (*expr_p));
3616 return ret;
3619 /* Handle shortcut semantics in the predicate operand of a COND_EXPR by
3620 rewriting it into multiple COND_EXPRs, and possibly GOTO_EXPRs.
3622 TRUE_LABEL_P and FALSE_LABEL_P point to the labels to jump to if the
3623 condition is true or false, respectively. If null, we should generate
3624 our own to skip over the evaluation of this specific expression.
3626 LOCUS is the source location of the COND_EXPR.
3628 This function is the tree equivalent of do_jump.
3630 shortcut_cond_r should only be called by shortcut_cond_expr. */
3632 static tree
3633 shortcut_cond_r (tree pred, tree *true_label_p, tree *false_label_p,
3634 location_t locus)
3636 tree local_label = NULL_TREE;
3637 tree t, expr = NULL;
3639 /* OK, it's not a simple case; we need to pull apart the COND_EXPR to
3640 retain the shortcut semantics. Just insert the gotos here;
3641 shortcut_cond_expr will append the real blocks later. */
3642 if (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
3644 location_t new_locus;
3646 /* Turn if (a && b) into
3648 if (a); else goto no;
3649 if (b) goto yes; else goto no;
3650 (no:) */
3652 if (false_label_p == NULL)
3653 false_label_p = &local_label;
3655 /* Keep the original source location on the first 'if'. */
3656 t = shortcut_cond_r (TREE_OPERAND (pred, 0), NULL, false_label_p, locus);
3657 append_to_statement_list (t, &expr);
3659 /* Set the source location of the && on the second 'if'. */
3660 new_locus = rexpr_location (pred, locus);
3661 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
3662 new_locus);
3663 append_to_statement_list (t, &expr);
3665 else if (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
3667 location_t new_locus;
3669 /* Turn if (a || b) into
3671 if (a) goto yes;
3672 if (b) goto yes; else goto no;
3673 (yes:) */
3675 if (true_label_p == NULL)
3676 true_label_p = &local_label;
3678 /* Keep the original source location on the first 'if'. */
3679 t = shortcut_cond_r (TREE_OPERAND (pred, 0), true_label_p, NULL, locus);
3680 append_to_statement_list (t, &expr);
3682 /* Set the source location of the || on the second 'if'. */
3683 new_locus = rexpr_location (pred, locus);
3684 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
3685 new_locus);
3686 append_to_statement_list (t, &expr);
3688 else if (TREE_CODE (pred) == COND_EXPR
3689 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 1)))
3690 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 2))))
3692 location_t new_locus;
3694 /* As long as we're messing with gotos, turn if (a ? b : c) into
3695 if (a)
3696 if (b) goto yes; else goto no;
3697 else
3698 if (c) goto yes; else goto no;
3700 Don't do this if one of the arms has void type, which can happen
3701 in C++ when the arm is throw. */
3703 /* Keep the original source location on the first 'if'. Set the source
3704 location of the ? on the second 'if'. */
3705 new_locus = rexpr_location (pred, locus);
3706 expr = build3 (COND_EXPR, void_type_node, TREE_OPERAND (pred, 0),
3707 shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p,
3708 false_label_p, locus),
3709 shortcut_cond_r (TREE_OPERAND (pred, 2), true_label_p,
3710 false_label_p, new_locus));
3712 else
3714 expr = build3 (COND_EXPR, void_type_node, pred,
3715 build_and_jump (true_label_p),
3716 build_and_jump (false_label_p));
3717 SET_EXPR_LOCATION (expr, locus);
3720 if (local_label)
3722 t = build1 (LABEL_EXPR, void_type_node, local_label);
3723 append_to_statement_list (t, &expr);
3726 return expr;
3729 /* If EXPR is a GOTO_EXPR, return it. If it is a STATEMENT_LIST, skip
3730 any of its leading DEBUG_BEGIN_STMTS and recurse on the subsequent
3731 statement, if it is the last one. Otherwise, return NULL. */
3733 static tree
3734 find_goto (tree expr)
3736 if (!expr)
3737 return NULL_TREE;
3739 if (TREE_CODE (expr) == GOTO_EXPR)
3740 return expr;
3742 if (TREE_CODE (expr) != STATEMENT_LIST)
3743 return NULL_TREE;
3745 tree_stmt_iterator i = tsi_start (expr);
3747 while (!tsi_end_p (i) && TREE_CODE (tsi_stmt (i)) == DEBUG_BEGIN_STMT)
3748 tsi_next (&i);
3750 if (!tsi_one_before_end_p (i))
3751 return NULL_TREE;
3753 return find_goto (tsi_stmt (i));
3756 /* Same as find_goto, except that it returns NULL if the destination
3757 is not a LABEL_DECL. */
3759 static inline tree
3760 find_goto_label (tree expr)
3762 tree dest = find_goto (expr);
3763 if (dest && TREE_CODE (GOTO_DESTINATION (dest)) == LABEL_DECL)
3764 return dest;
3765 return NULL_TREE;
3768 /* Given a conditional expression EXPR with short-circuit boolean
3769 predicates using TRUTH_ANDIF_EXPR or TRUTH_ORIF_EXPR, break the
3770 predicate apart into the equivalent sequence of conditionals. */
3772 static tree
3773 shortcut_cond_expr (tree expr)
3775 tree pred = TREE_OPERAND (expr, 0);
3776 tree then_ = TREE_OPERAND (expr, 1);
3777 tree else_ = TREE_OPERAND (expr, 2);
3778 tree true_label, false_label, end_label, t;
3779 tree *true_label_p;
3780 tree *false_label_p;
3781 bool emit_end, emit_false, jump_over_else;
3782 bool then_se = then_ && TREE_SIDE_EFFECTS (then_);
3783 bool else_se = else_ && TREE_SIDE_EFFECTS (else_);
3785 /* First do simple transformations. */
3786 if (!else_se)
3788 /* If there is no 'else', turn
3789 if (a && b) then c
3790 into
3791 if (a) if (b) then c. */
3792 while (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
3794 /* Keep the original source location on the first 'if'. */
3795 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
3796 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
3797 /* Set the source location of the && on the second 'if'. */
3798 if (rexpr_has_location (pred))
3799 SET_EXPR_LOCATION (expr, rexpr_location (pred));
3800 then_ = shortcut_cond_expr (expr);
3801 then_se = then_ && TREE_SIDE_EFFECTS (then_);
3802 pred = TREE_OPERAND (pred, 0);
3803 expr = build3 (COND_EXPR, void_type_node, pred, then_, NULL_TREE);
3804 SET_EXPR_LOCATION (expr, locus);
3808 if (!then_se)
3810 /* If there is no 'then', turn
3811 if (a || b); else d
3812 into
3813 if (a); else if (b); else d. */
3814 while (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
3816 /* Keep the original source location on the first 'if'. */
3817 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
3818 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
3819 /* Set the source location of the || on the second 'if'. */
3820 if (rexpr_has_location (pred))
3821 SET_EXPR_LOCATION (expr, rexpr_location (pred));
3822 else_ = shortcut_cond_expr (expr);
3823 else_se = else_ && TREE_SIDE_EFFECTS (else_);
3824 pred = TREE_OPERAND (pred, 0);
3825 expr = build3 (COND_EXPR, void_type_node, pred, NULL_TREE, else_);
3826 SET_EXPR_LOCATION (expr, locus);
3830 /* If we're done, great. */
3831 if (TREE_CODE (pred) != TRUTH_ANDIF_EXPR
3832 && TREE_CODE (pred) != TRUTH_ORIF_EXPR)
3833 return expr;
3835 /* Otherwise we need to mess with gotos. Change
3836 if (a) c; else d;
3838 if (a); else goto no;
3839 c; goto end;
3840 no: d; end:
3841 and recursively gimplify the condition. */
3843 true_label = false_label = end_label = NULL_TREE;
3845 /* If our arms just jump somewhere, hijack those labels so we don't
3846 generate jumps to jumps. */
3848 if (tree then_goto = find_goto_label (then_))
3850 true_label = GOTO_DESTINATION (then_goto);
3851 then_ = NULL;
3852 then_se = false;
3855 if (tree else_goto = find_goto_label (else_))
3857 false_label = GOTO_DESTINATION (else_goto);
3858 else_ = NULL;
3859 else_se = false;
3862 /* If we aren't hijacking a label for the 'then' branch, it falls through. */
3863 if (true_label)
3864 true_label_p = &true_label;
3865 else
3866 true_label_p = NULL;
3868 /* The 'else' branch also needs a label if it contains interesting code. */
3869 if (false_label || else_se)
3870 false_label_p = &false_label;
3871 else
3872 false_label_p = NULL;
3874 /* If there was nothing else in our arms, just forward the label(s). */
3875 if (!then_se && !else_se)
3876 return shortcut_cond_r (pred, true_label_p, false_label_p,
3877 EXPR_LOC_OR_LOC (expr, input_location));
3879 /* If our last subexpression already has a terminal label, reuse it. */
3880 if (else_se)
3881 t = expr_last (else_);
3882 else if (then_se)
3883 t = expr_last (then_);
3884 else
3885 t = NULL;
3886 if (t && TREE_CODE (t) == LABEL_EXPR)
3887 end_label = LABEL_EXPR_LABEL (t);
3889 /* If we don't care about jumping to the 'else' branch, jump to the end
3890 if the condition is false. */
3891 if (!false_label_p)
3892 false_label_p = &end_label;
3894 /* We only want to emit these labels if we aren't hijacking them. */
3895 emit_end = (end_label == NULL_TREE);
3896 emit_false = (false_label == NULL_TREE);
3898 /* We only emit the jump over the else clause if we have to--if the
3899 then clause may fall through. Otherwise we can wind up with a
3900 useless jump and a useless label at the end of gimplified code,
3901 which will cause us to think that this conditional as a whole
3902 falls through even if it doesn't. If we then inline a function
3903 which ends with such a condition, that can cause us to issue an
3904 inappropriate warning about control reaching the end of a
3905 non-void function. */
3906 jump_over_else = block_may_fallthru (then_);
3908 pred = shortcut_cond_r (pred, true_label_p, false_label_p,
3909 EXPR_LOC_OR_LOC (expr, input_location));
3911 expr = NULL;
3912 append_to_statement_list (pred, &expr);
3914 append_to_statement_list (then_, &expr);
3915 if (else_se)
3917 if (jump_over_else)
3919 tree last = expr_last (expr);
3920 t = build_and_jump (&end_label);
3921 if (rexpr_has_location (last))
3922 SET_EXPR_LOCATION (t, rexpr_location (last));
3923 append_to_statement_list (t, &expr);
3925 if (emit_false)
3927 t = build1 (LABEL_EXPR, void_type_node, false_label);
3928 append_to_statement_list (t, &expr);
3930 append_to_statement_list (else_, &expr);
3932 if (emit_end && end_label)
3934 t = build1 (LABEL_EXPR, void_type_node, end_label);
3935 append_to_statement_list (t, &expr);
3938 return expr;
3941 /* EXPR is used in a boolean context; make sure it has BOOLEAN_TYPE. */
3943 tree
3944 gimple_boolify (tree expr)
3946 tree type = TREE_TYPE (expr);
3947 location_t loc = EXPR_LOCATION (expr);
3949 if (TREE_CODE (expr) == NE_EXPR
3950 && TREE_CODE (TREE_OPERAND (expr, 0)) == CALL_EXPR
3951 && integer_zerop (TREE_OPERAND (expr, 1)))
3953 tree call = TREE_OPERAND (expr, 0);
3954 tree fn = get_callee_fndecl (call);
3956 /* For __builtin_expect ((long) (x), y) recurse into x as well
3957 if x is truth_value_p. */
3958 if (fn
3959 && fndecl_built_in_p (fn, BUILT_IN_EXPECT)
3960 && call_expr_nargs (call) == 2)
3962 tree arg = CALL_EXPR_ARG (call, 0);
3963 if (arg)
3965 if (TREE_CODE (arg) == NOP_EXPR
3966 && TREE_TYPE (arg) == TREE_TYPE (call))
3967 arg = TREE_OPERAND (arg, 0);
3968 if (truth_value_p (TREE_CODE (arg)))
3970 arg = gimple_boolify (arg);
3971 CALL_EXPR_ARG (call, 0)
3972 = fold_convert_loc (loc, TREE_TYPE (call), arg);
3978 switch (TREE_CODE (expr))
3980 case TRUTH_AND_EXPR:
3981 case TRUTH_OR_EXPR:
3982 case TRUTH_XOR_EXPR:
3983 case TRUTH_ANDIF_EXPR:
3984 case TRUTH_ORIF_EXPR:
3985 /* Also boolify the arguments of truth exprs. */
3986 TREE_OPERAND (expr, 1) = gimple_boolify (TREE_OPERAND (expr, 1));
3987 /* FALLTHRU */
3989 case TRUTH_NOT_EXPR:
3990 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
3992 /* These expressions always produce boolean results. */
3993 if (TREE_CODE (type) != BOOLEAN_TYPE)
3994 TREE_TYPE (expr) = boolean_type_node;
3995 return expr;
3997 case ANNOTATE_EXPR:
3998 switch ((enum annot_expr_kind) TREE_INT_CST_LOW (TREE_OPERAND (expr, 1)))
4000 case annot_expr_ivdep_kind:
4001 case annot_expr_unroll_kind:
4002 case annot_expr_no_vector_kind:
4003 case annot_expr_vector_kind:
4004 case annot_expr_parallel_kind:
4005 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
4006 if (TREE_CODE (type) != BOOLEAN_TYPE)
4007 TREE_TYPE (expr) = boolean_type_node;
4008 return expr;
4009 default:
4010 gcc_unreachable ();
4013 default:
4014 if (COMPARISON_CLASS_P (expr))
4016 /* There expressions always prduce boolean results. */
4017 if (TREE_CODE (type) != BOOLEAN_TYPE)
4018 TREE_TYPE (expr) = boolean_type_node;
4019 return expr;
4021 /* Other expressions that get here must have boolean values, but
4022 might need to be converted to the appropriate mode. */
4023 if (TREE_CODE (type) == BOOLEAN_TYPE)
4024 return expr;
4025 return fold_convert_loc (loc, boolean_type_node, expr);
4029 /* Given a conditional expression *EXPR_P without side effects, gimplify
4030 its operands. New statements are inserted to PRE_P. */
4032 static enum gimplify_status
4033 gimplify_pure_cond_expr (tree *expr_p, gimple_seq *pre_p)
4035 tree expr = *expr_p, cond;
4036 enum gimplify_status ret, tret;
4037 enum tree_code code;
4039 cond = gimple_boolify (COND_EXPR_COND (expr));
4041 /* We need to handle && and || specially, as their gimplification
4042 creates pure cond_expr, thus leading to an infinite cycle otherwise. */
4043 code = TREE_CODE (cond);
4044 if (code == TRUTH_ANDIF_EXPR)
4045 TREE_SET_CODE (cond, TRUTH_AND_EXPR);
4046 else if (code == TRUTH_ORIF_EXPR)
4047 TREE_SET_CODE (cond, TRUTH_OR_EXPR);
4048 ret = gimplify_expr (&cond, pre_p, NULL, is_gimple_condexpr, fb_rvalue);
4049 COND_EXPR_COND (*expr_p) = cond;
4051 tret = gimplify_expr (&COND_EXPR_THEN (expr), pre_p, NULL,
4052 is_gimple_val, fb_rvalue);
4053 ret = MIN (ret, tret);
4054 tret = gimplify_expr (&COND_EXPR_ELSE (expr), pre_p, NULL,
4055 is_gimple_val, fb_rvalue);
4057 return MIN (ret, tret);
4060 /* Return true if evaluating EXPR could trap.
4061 EXPR is GENERIC, while tree_could_trap_p can be called
4062 only on GIMPLE. */
4064 bool
4065 generic_expr_could_trap_p (tree expr)
4067 unsigned i, n;
4069 if (!expr || is_gimple_val (expr))
4070 return false;
4072 if (!EXPR_P (expr) || tree_could_trap_p (expr))
4073 return true;
4075 n = TREE_OPERAND_LENGTH (expr);
4076 for (i = 0; i < n; i++)
4077 if (generic_expr_could_trap_p (TREE_OPERAND (expr, i)))
4078 return true;
4080 return false;
4083 /* Convert the conditional expression pointed to by EXPR_P '(p) ? a : b;'
4084 into
4086 if (p) if (p)
4087 t1 = a; a;
4088 else or else
4089 t1 = b; b;
4092 The second form is used when *EXPR_P is of type void.
4094 PRE_P points to the list where side effects that must happen before
4095 *EXPR_P should be stored. */
4097 static enum gimplify_status
4098 gimplify_cond_expr (tree *expr_p, gimple_seq *pre_p, fallback_t fallback)
4100 tree expr = *expr_p;
4101 tree type = TREE_TYPE (expr);
4102 location_t loc = EXPR_LOCATION (expr);
4103 tree tmp, arm1, arm2;
4104 enum gimplify_status ret;
4105 tree label_true, label_false, label_cont;
4106 bool have_then_clause_p, have_else_clause_p;
4107 gcond *cond_stmt;
4108 enum tree_code pred_code;
4109 gimple_seq seq = NULL;
4111 /* If this COND_EXPR has a value, copy the values into a temporary within
4112 the arms. */
4113 if (!VOID_TYPE_P (type))
4115 tree then_ = TREE_OPERAND (expr, 1), else_ = TREE_OPERAND (expr, 2);
4116 tree result;
4118 /* If either an rvalue is ok or we do not require an lvalue, create the
4119 temporary. But we cannot do that if the type is addressable. */
4120 if (((fallback & fb_rvalue) || !(fallback & fb_lvalue))
4121 && !TREE_ADDRESSABLE (type))
4123 if (gimplify_ctxp->allow_rhs_cond_expr
4124 /* If either branch has side effects or could trap, it can't be
4125 evaluated unconditionally. */
4126 && !TREE_SIDE_EFFECTS (then_)
4127 && !generic_expr_could_trap_p (then_)
4128 && !TREE_SIDE_EFFECTS (else_)
4129 && !generic_expr_could_trap_p (else_))
4130 return gimplify_pure_cond_expr (expr_p, pre_p);
4132 tmp = create_tmp_var (type, "iftmp");
4133 result = tmp;
4136 /* Otherwise, only create and copy references to the values. */
4137 else
4139 type = build_pointer_type (type);
4141 if (!VOID_TYPE_P (TREE_TYPE (then_)))
4142 then_ = build_fold_addr_expr_loc (loc, then_);
4144 if (!VOID_TYPE_P (TREE_TYPE (else_)))
4145 else_ = build_fold_addr_expr_loc (loc, else_);
4147 expr
4148 = build3 (COND_EXPR, type, TREE_OPERAND (expr, 0), then_, else_);
4150 tmp = create_tmp_var (type, "iftmp");
4151 result = build_simple_mem_ref_loc (loc, tmp);
4154 /* Build the new then clause, `tmp = then_;'. But don't build the
4155 assignment if the value is void; in C++ it can be if it's a throw. */
4156 if (!VOID_TYPE_P (TREE_TYPE (then_)))
4157 TREE_OPERAND (expr, 1) = build2 (INIT_EXPR, type, tmp, then_);
4159 /* Similarly, build the new else clause, `tmp = else_;'. */
4160 if (!VOID_TYPE_P (TREE_TYPE (else_)))
4161 TREE_OPERAND (expr, 2) = build2 (INIT_EXPR, type, tmp, else_);
4163 TREE_TYPE (expr) = void_type_node;
4164 recalculate_side_effects (expr);
4166 /* Move the COND_EXPR to the prequeue. */
4167 gimplify_stmt (&expr, pre_p);
4169 *expr_p = result;
4170 return GS_ALL_DONE;
4173 /* Remove any COMPOUND_EXPR so the following cases will be caught. */
4174 STRIP_TYPE_NOPS (TREE_OPERAND (expr, 0));
4175 if (TREE_CODE (TREE_OPERAND (expr, 0)) == COMPOUND_EXPR)
4176 gimplify_compound_expr (&TREE_OPERAND (expr, 0), pre_p, true);
4178 /* Make sure the condition has BOOLEAN_TYPE. */
4179 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
4181 /* Break apart && and || conditions. */
4182 if (TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ANDIF_EXPR
4183 || TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ORIF_EXPR)
4185 expr = shortcut_cond_expr (expr);
4187 if (expr != *expr_p)
4189 *expr_p = expr;
4191 /* We can't rely on gimplify_expr to re-gimplify the expanded
4192 form properly, as cleanups might cause the target labels to be
4193 wrapped in a TRY_FINALLY_EXPR. To prevent that, we need to
4194 set up a conditional context. */
4195 gimple_push_condition ();
4196 gimplify_stmt (expr_p, &seq);
4197 gimple_pop_condition (pre_p);
4198 gimple_seq_add_seq (pre_p, seq);
4200 return GS_ALL_DONE;
4204 /* Now do the normal gimplification. */
4206 /* Gimplify condition. */
4207 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, NULL,
4208 is_gimple_condexpr_for_cond, fb_rvalue);
4209 if (ret == GS_ERROR)
4210 return GS_ERROR;
4211 gcc_assert (TREE_OPERAND (expr, 0) != NULL_TREE);
4213 gimple_push_condition ();
4215 have_then_clause_p = have_else_clause_p = false;
4216 label_true = find_goto_label (TREE_OPERAND (expr, 1));
4217 if (label_true
4218 && DECL_CONTEXT (GOTO_DESTINATION (label_true)) == current_function_decl
4219 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
4220 have different locations, otherwise we end up with incorrect
4221 location information on the branches. */
4222 && (optimize
4223 || !EXPR_HAS_LOCATION (expr)
4224 || !rexpr_has_location (label_true)
4225 || EXPR_LOCATION (expr) == rexpr_location (label_true)))
4227 have_then_clause_p = true;
4228 label_true = GOTO_DESTINATION (label_true);
4230 else
4231 label_true = create_artificial_label (UNKNOWN_LOCATION);
4232 label_false = find_goto_label (TREE_OPERAND (expr, 2));
4233 if (label_false
4234 && DECL_CONTEXT (GOTO_DESTINATION (label_false)) == current_function_decl
4235 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
4236 have different locations, otherwise we end up with incorrect
4237 location information on the branches. */
4238 && (optimize
4239 || !EXPR_HAS_LOCATION (expr)
4240 || !rexpr_has_location (label_false)
4241 || EXPR_LOCATION (expr) == rexpr_location (label_false)))
4243 have_else_clause_p = true;
4244 label_false = GOTO_DESTINATION (label_false);
4246 else
4247 label_false = create_artificial_label (UNKNOWN_LOCATION);
4249 gimple_cond_get_ops_from_tree (COND_EXPR_COND (expr), &pred_code, &arm1,
4250 &arm2);
4251 cond_stmt = gimple_build_cond (pred_code, arm1, arm2, label_true,
4252 label_false);
4253 gimple_set_no_warning (cond_stmt, TREE_NO_WARNING (COND_EXPR_COND (expr)));
4254 gimplify_seq_add_stmt (&seq, cond_stmt);
4255 gimple_stmt_iterator gsi = gsi_last (seq);
4256 maybe_fold_stmt (&gsi);
4258 label_cont = NULL_TREE;
4259 if (!have_then_clause_p)
4261 /* For if (...) {} else { code; } put label_true after
4262 the else block. */
4263 if (TREE_OPERAND (expr, 1) == NULL_TREE
4264 && !have_else_clause_p
4265 && TREE_OPERAND (expr, 2) != NULL_TREE)
4266 label_cont = label_true;
4267 else
4269 gimplify_seq_add_stmt (&seq, gimple_build_label (label_true));
4270 have_then_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 1), &seq);
4271 /* For if (...) { code; } else {} or
4272 if (...) { code; } else goto label; or
4273 if (...) { code; return; } else { ... }
4274 label_cont isn't needed. */
4275 if (!have_else_clause_p
4276 && TREE_OPERAND (expr, 2) != NULL_TREE
4277 && gimple_seq_may_fallthru (seq))
4279 gimple *g;
4280 label_cont = create_artificial_label (UNKNOWN_LOCATION);
4282 g = gimple_build_goto (label_cont);
4284 /* GIMPLE_COND's are very low level; they have embedded
4285 gotos. This particular embedded goto should not be marked
4286 with the location of the original COND_EXPR, as it would
4287 correspond to the COND_EXPR's condition, not the ELSE or the
4288 THEN arms. To avoid marking it with the wrong location, flag
4289 it as "no location". */
4290 gimple_set_do_not_emit_location (g);
4292 gimplify_seq_add_stmt (&seq, g);
4296 if (!have_else_clause_p)
4298 gimplify_seq_add_stmt (&seq, gimple_build_label (label_false));
4299 have_else_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 2), &seq);
4301 if (label_cont)
4302 gimplify_seq_add_stmt (&seq, gimple_build_label (label_cont));
4304 gimple_pop_condition (pre_p);
4305 gimple_seq_add_seq (pre_p, seq);
4307 if (ret == GS_ERROR)
4308 ; /* Do nothing. */
4309 else if (have_then_clause_p || have_else_clause_p)
4310 ret = GS_ALL_DONE;
4311 else
4313 /* Both arms are empty; replace the COND_EXPR with its predicate. */
4314 expr = TREE_OPERAND (expr, 0);
4315 gimplify_stmt (&expr, pre_p);
4318 *expr_p = NULL;
4319 return ret;
4322 /* Prepare the node pointed to by EXPR_P, an is_gimple_addressable expression,
4323 to be marked addressable.
4325 We cannot rely on such an expression being directly markable if a temporary
4326 has been created by the gimplification. In this case, we create another
4327 temporary and initialize it with a copy, which will become a store after we
4328 mark it addressable. This can happen if the front-end passed us something
4329 that it could not mark addressable yet, like a Fortran pass-by-reference
4330 parameter (int) floatvar. */
4332 static void
4333 prepare_gimple_addressable (tree *expr_p, gimple_seq *seq_p)
4335 while (handled_component_p (*expr_p))
4336 expr_p = &TREE_OPERAND (*expr_p, 0);
4337 if (is_gimple_reg (*expr_p))
4339 /* Do not allow an SSA name as the temporary. */
4340 tree var = get_initialized_tmp_var (*expr_p, seq_p, NULL, false);
4341 DECL_NOT_GIMPLE_REG_P (var) = 1;
4342 *expr_p = var;
4346 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
4347 a call to __builtin_memcpy. */
4349 static enum gimplify_status
4350 gimplify_modify_expr_to_memcpy (tree *expr_p, tree size, bool want_value,
4351 gimple_seq *seq_p)
4353 tree t, to, to_ptr, from, from_ptr;
4354 gcall *gs;
4355 location_t loc = EXPR_LOCATION (*expr_p);
4357 to = TREE_OPERAND (*expr_p, 0);
4358 from = TREE_OPERAND (*expr_p, 1);
4360 /* Mark the RHS addressable. Beware that it may not be possible to do so
4361 directly if a temporary has been created by the gimplification. */
4362 prepare_gimple_addressable (&from, seq_p);
4364 mark_addressable (from);
4365 from_ptr = build_fold_addr_expr_loc (loc, from);
4366 gimplify_arg (&from_ptr, seq_p, loc);
4368 mark_addressable (to);
4369 to_ptr = build_fold_addr_expr_loc (loc, to);
4370 gimplify_arg (&to_ptr, seq_p, loc);
4372 t = builtin_decl_implicit (BUILT_IN_MEMCPY);
4374 gs = gimple_build_call (t, 3, to_ptr, from_ptr, size);
4375 gimple_call_set_alloca_for_var (gs, true);
4377 if (want_value)
4379 /* tmp = memcpy() */
4380 t = create_tmp_var (TREE_TYPE (to_ptr));
4381 gimple_call_set_lhs (gs, t);
4382 gimplify_seq_add_stmt (seq_p, gs);
4384 *expr_p = build_simple_mem_ref (t);
4385 return GS_ALL_DONE;
4388 gimplify_seq_add_stmt (seq_p, gs);
4389 *expr_p = NULL;
4390 return GS_ALL_DONE;
4393 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
4394 a call to __builtin_memset. In this case we know that the RHS is
4395 a CONSTRUCTOR with an empty element list. */
4397 static enum gimplify_status
4398 gimplify_modify_expr_to_memset (tree *expr_p, tree size, bool want_value,
4399 gimple_seq *seq_p)
4401 tree t, from, to, to_ptr;
4402 gcall *gs;
4403 location_t loc = EXPR_LOCATION (*expr_p);
4405 /* Assert our assumptions, to abort instead of producing wrong code
4406 silently if they are not met. Beware that the RHS CONSTRUCTOR might
4407 not be immediately exposed. */
4408 from = TREE_OPERAND (*expr_p, 1);
4409 if (TREE_CODE (from) == WITH_SIZE_EXPR)
4410 from = TREE_OPERAND (from, 0);
4412 gcc_assert (TREE_CODE (from) == CONSTRUCTOR
4413 && vec_safe_is_empty (CONSTRUCTOR_ELTS (from)));
4415 /* Now proceed. */
4416 to = TREE_OPERAND (*expr_p, 0);
4418 to_ptr = build_fold_addr_expr_loc (loc, to);
4419 gimplify_arg (&to_ptr, seq_p, loc);
4420 t = builtin_decl_implicit (BUILT_IN_MEMSET);
4422 gs = gimple_build_call (t, 3, to_ptr, integer_zero_node, size);
4424 if (want_value)
4426 /* tmp = memset() */
4427 t = create_tmp_var (TREE_TYPE (to_ptr));
4428 gimple_call_set_lhs (gs, t);
4429 gimplify_seq_add_stmt (seq_p, gs);
4431 *expr_p = build1 (INDIRECT_REF, TREE_TYPE (to), t);
4432 return GS_ALL_DONE;
4435 gimplify_seq_add_stmt (seq_p, gs);
4436 *expr_p = NULL;
4437 return GS_ALL_DONE;
4440 /* A subroutine of gimplify_init_ctor_preeval. Called via walk_tree,
4441 determine, cautiously, if a CONSTRUCTOR overlaps the lhs of an
4442 assignment. Return non-null if we detect a potential overlap. */
4444 struct gimplify_init_ctor_preeval_data
4446 /* The base decl of the lhs object. May be NULL, in which case we
4447 have to assume the lhs is indirect. */
4448 tree lhs_base_decl;
4450 /* The alias set of the lhs object. */
4451 alias_set_type lhs_alias_set;
4454 static tree
4455 gimplify_init_ctor_preeval_1 (tree *tp, int *walk_subtrees, void *xdata)
4457 struct gimplify_init_ctor_preeval_data *data
4458 = (struct gimplify_init_ctor_preeval_data *) xdata;
4459 tree t = *tp;
4461 /* If we find the base object, obviously we have overlap. */
4462 if (data->lhs_base_decl == t)
4463 return t;
4465 /* If the constructor component is indirect, determine if we have a
4466 potential overlap with the lhs. The only bits of information we
4467 have to go on at this point are addressability and alias sets. */
4468 if ((INDIRECT_REF_P (t)
4469 || TREE_CODE (t) == MEM_REF)
4470 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
4471 && alias_sets_conflict_p (data->lhs_alias_set, get_alias_set (t)))
4472 return t;
4474 /* If the constructor component is a call, determine if it can hide a
4475 potential overlap with the lhs through an INDIRECT_REF like above.
4476 ??? Ugh - this is completely broken. In fact this whole analysis
4477 doesn't look conservative. */
4478 if (TREE_CODE (t) == CALL_EXPR)
4480 tree type, fntype = TREE_TYPE (TREE_TYPE (CALL_EXPR_FN (t)));
4482 for (type = TYPE_ARG_TYPES (fntype); type; type = TREE_CHAIN (type))
4483 if (POINTER_TYPE_P (TREE_VALUE (type))
4484 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
4485 && alias_sets_conflict_p (data->lhs_alias_set,
4486 get_alias_set
4487 (TREE_TYPE (TREE_VALUE (type)))))
4488 return t;
4491 if (IS_TYPE_OR_DECL_P (t))
4492 *walk_subtrees = 0;
4493 return NULL;
4496 /* A subroutine of gimplify_init_constructor. Pre-evaluate EXPR,
4497 force values that overlap with the lhs (as described by *DATA)
4498 into temporaries. */
4500 static void
4501 gimplify_init_ctor_preeval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
4502 struct gimplify_init_ctor_preeval_data *data)
4504 enum gimplify_status one;
4506 /* If the value is constant, then there's nothing to pre-evaluate. */
4507 if (TREE_CONSTANT (*expr_p))
4509 /* Ensure it does not have side effects, it might contain a reference to
4510 the object we're initializing. */
4511 gcc_assert (!TREE_SIDE_EFFECTS (*expr_p));
4512 return;
4515 /* If the type has non-trivial constructors, we can't pre-evaluate. */
4516 if (TREE_ADDRESSABLE (TREE_TYPE (*expr_p)))
4517 return;
4519 /* Recurse for nested constructors. */
4520 if (TREE_CODE (*expr_p) == CONSTRUCTOR)
4522 unsigned HOST_WIDE_INT ix;
4523 constructor_elt *ce;
4524 vec<constructor_elt, va_gc> *v = CONSTRUCTOR_ELTS (*expr_p);
4526 FOR_EACH_VEC_SAFE_ELT (v, ix, ce)
4527 gimplify_init_ctor_preeval (&ce->value, pre_p, post_p, data);
4529 return;
4532 /* If this is a variable sized type, we must remember the size. */
4533 maybe_with_size_expr (expr_p);
4535 /* Gimplify the constructor element to something appropriate for the rhs
4536 of a MODIFY_EXPR. Given that we know the LHS is an aggregate, we know
4537 the gimplifier will consider this a store to memory. Doing this
4538 gimplification now means that we won't have to deal with complicated
4539 language-specific trees, nor trees like SAVE_EXPR that can induce
4540 exponential search behavior. */
4541 one = gimplify_expr (expr_p, pre_p, post_p, is_gimple_mem_rhs, fb_rvalue);
4542 if (one == GS_ERROR)
4544 *expr_p = NULL;
4545 return;
4548 /* If we gimplified to a bare decl, we can be sure that it doesn't overlap
4549 with the lhs, since "a = { .x=a }" doesn't make sense. This will
4550 always be true for all scalars, since is_gimple_mem_rhs insists on a
4551 temporary variable for them. */
4552 if (DECL_P (*expr_p))
4553 return;
4555 /* If this is of variable size, we have no choice but to assume it doesn't
4556 overlap since we can't make a temporary for it. */
4557 if (TREE_CODE (TYPE_SIZE (TREE_TYPE (*expr_p))) != INTEGER_CST)
4558 return;
4560 /* Otherwise, we must search for overlap ... */
4561 if (!walk_tree (expr_p, gimplify_init_ctor_preeval_1, data, NULL))
4562 return;
4564 /* ... and if found, force the value into a temporary. */
4565 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
4568 /* A subroutine of gimplify_init_ctor_eval. Create a loop for
4569 a RANGE_EXPR in a CONSTRUCTOR for an array.
4571 var = lower;
4572 loop_entry:
4573 object[var] = value;
4574 if (var == upper)
4575 goto loop_exit;
4576 var = var + 1;
4577 goto loop_entry;
4578 loop_exit:
4580 We increment var _after_ the loop exit check because we might otherwise
4581 fail if upper == TYPE_MAX_VALUE (type for upper).
4583 Note that we never have to deal with SAVE_EXPRs here, because this has
4584 already been taken care of for us, in gimplify_init_ctor_preeval(). */
4586 static void gimplify_init_ctor_eval (tree, vec<constructor_elt, va_gc> *,
4587 gimple_seq *, bool);
4589 static void
4590 gimplify_init_ctor_eval_range (tree object, tree lower, tree upper,
4591 tree value, tree array_elt_type,
4592 gimple_seq *pre_p, bool cleared)
4594 tree loop_entry_label, loop_exit_label, fall_thru_label;
4595 tree var, var_type, cref, tmp;
4597 loop_entry_label = create_artificial_label (UNKNOWN_LOCATION);
4598 loop_exit_label = create_artificial_label (UNKNOWN_LOCATION);
4599 fall_thru_label = create_artificial_label (UNKNOWN_LOCATION);
4601 /* Create and initialize the index variable. */
4602 var_type = TREE_TYPE (upper);
4603 var = create_tmp_var (var_type);
4604 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, lower));
4606 /* Add the loop entry label. */
4607 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_entry_label));
4609 /* Build the reference. */
4610 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
4611 var, NULL_TREE, NULL_TREE);
4613 /* If we are a constructor, just call gimplify_init_ctor_eval to do
4614 the store. Otherwise just assign value to the reference. */
4616 if (TREE_CODE (value) == CONSTRUCTOR)
4617 /* NB we might have to call ourself recursively through
4618 gimplify_init_ctor_eval if the value is a constructor. */
4619 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
4620 pre_p, cleared);
4621 else
4623 if (gimplify_expr (&value, pre_p, NULL, is_gimple_val, fb_rvalue)
4624 != GS_ERROR)
4625 gimplify_seq_add_stmt (pre_p, gimple_build_assign (cref, value));
4628 /* We exit the loop when the index var is equal to the upper bound. */
4629 gimplify_seq_add_stmt (pre_p,
4630 gimple_build_cond (EQ_EXPR, var, upper,
4631 loop_exit_label, fall_thru_label));
4633 gimplify_seq_add_stmt (pre_p, gimple_build_label (fall_thru_label));
4635 /* Otherwise, increment the index var... */
4636 tmp = build2 (PLUS_EXPR, var_type, var,
4637 fold_convert (var_type, integer_one_node));
4638 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, tmp));
4640 /* ...and jump back to the loop entry. */
4641 gimplify_seq_add_stmt (pre_p, gimple_build_goto (loop_entry_label));
4643 /* Add the loop exit label. */
4644 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_exit_label));
4647 /* A subroutine of gimplify_init_constructor. Generate individual
4648 MODIFY_EXPRs for a CONSTRUCTOR. OBJECT is the LHS against which the
4649 assignments should happen. ELTS is the CONSTRUCTOR_ELTS of the
4650 CONSTRUCTOR. CLEARED is true if the entire LHS object has been
4651 zeroed first. */
4653 static void
4654 gimplify_init_ctor_eval (tree object, vec<constructor_elt, va_gc> *elts,
4655 gimple_seq *pre_p, bool cleared)
4657 tree array_elt_type = NULL;
4658 unsigned HOST_WIDE_INT ix;
4659 tree purpose, value;
4661 if (TREE_CODE (TREE_TYPE (object)) == ARRAY_TYPE)
4662 array_elt_type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (object)));
4664 FOR_EACH_CONSTRUCTOR_ELT (elts, ix, purpose, value)
4666 tree cref;
4668 /* NULL values are created above for gimplification errors. */
4669 if (value == NULL)
4670 continue;
4672 if (cleared && initializer_zerop (value))
4673 continue;
4675 /* ??? Here's to hoping the front end fills in all of the indices,
4676 so we don't have to figure out what's missing ourselves. */
4677 gcc_assert (purpose);
4679 /* Skip zero-sized fields, unless value has side-effects. This can
4680 happen with calls to functions returning a empty type, which
4681 we shouldn't discard. As a number of downstream passes don't
4682 expect sets of empty type fields, we rely on the gimplification of
4683 the MODIFY_EXPR we make below to drop the assignment statement. */
4684 if (!TREE_SIDE_EFFECTS (value)
4685 && TREE_CODE (purpose) == FIELD_DECL
4686 && is_empty_type (TREE_TYPE (purpose)))
4687 continue;
4689 /* If we have a RANGE_EXPR, we have to build a loop to assign the
4690 whole range. */
4691 if (TREE_CODE (purpose) == RANGE_EXPR)
4693 tree lower = TREE_OPERAND (purpose, 0);
4694 tree upper = TREE_OPERAND (purpose, 1);
4696 /* If the lower bound is equal to upper, just treat it as if
4697 upper was the index. */
4698 if (simple_cst_equal (lower, upper))
4699 purpose = upper;
4700 else
4702 gimplify_init_ctor_eval_range (object, lower, upper, value,
4703 array_elt_type, pre_p, cleared);
4704 continue;
4708 if (array_elt_type)
4710 /* Do not use bitsizetype for ARRAY_REF indices. */
4711 if (TYPE_DOMAIN (TREE_TYPE (object)))
4712 purpose
4713 = fold_convert (TREE_TYPE (TYPE_DOMAIN (TREE_TYPE (object))),
4714 purpose);
4715 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
4716 purpose, NULL_TREE, NULL_TREE);
4718 else
4720 gcc_assert (TREE_CODE (purpose) == FIELD_DECL);
4721 cref = build3 (COMPONENT_REF, TREE_TYPE (purpose),
4722 unshare_expr (object), purpose, NULL_TREE);
4725 if (TREE_CODE (value) == CONSTRUCTOR
4726 && TREE_CODE (TREE_TYPE (value)) != VECTOR_TYPE)
4727 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
4728 pre_p, cleared);
4729 else
4731 tree init = build2 (INIT_EXPR, TREE_TYPE (cref), cref, value);
4732 gimplify_and_add (init, pre_p);
4733 ggc_free (init);
4738 /* Return the appropriate RHS predicate for this LHS. */
4740 gimple_predicate
4741 rhs_predicate_for (tree lhs)
4743 if (is_gimple_reg (lhs))
4744 return is_gimple_reg_rhs_or_call;
4745 else
4746 return is_gimple_mem_rhs_or_call;
4749 /* Return the initial guess for an appropriate RHS predicate for this LHS,
4750 before the LHS has been gimplified. */
4752 static gimple_predicate
4753 initial_rhs_predicate_for (tree lhs)
4755 if (is_gimple_reg_type (TREE_TYPE (lhs)))
4756 return is_gimple_reg_rhs_or_call;
4757 else
4758 return is_gimple_mem_rhs_or_call;
4761 /* Gimplify a C99 compound literal expression. This just means adding
4762 the DECL_EXPR before the current statement and using its anonymous
4763 decl instead. */
4765 static enum gimplify_status
4766 gimplify_compound_literal_expr (tree *expr_p, gimple_seq *pre_p,
4767 bool (*gimple_test_f) (tree),
4768 fallback_t fallback)
4770 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (*expr_p);
4771 tree decl = DECL_EXPR_DECL (decl_s);
4772 tree init = DECL_INITIAL (decl);
4773 /* Mark the decl as addressable if the compound literal
4774 expression is addressable now, otherwise it is marked too late
4775 after we gimplify the initialization expression. */
4776 if (TREE_ADDRESSABLE (*expr_p))
4777 TREE_ADDRESSABLE (decl) = 1;
4778 /* Otherwise, if we don't need an lvalue and have a literal directly
4779 substitute it. Check if it matches the gimple predicate, as
4780 otherwise we'd generate a new temporary, and we can as well just
4781 use the decl we already have. */
4782 else if (!TREE_ADDRESSABLE (decl)
4783 && !TREE_THIS_VOLATILE (decl)
4784 && init
4785 && (fallback & fb_lvalue) == 0
4786 && gimple_test_f (init))
4788 *expr_p = init;
4789 return GS_OK;
4792 /* If the decl is not addressable, then it is being used in some
4793 expression or on the right hand side of a statement, and it can
4794 be put into a readonly data section. */
4795 if (!TREE_ADDRESSABLE (decl) && (fallback & fb_lvalue) == 0)
4796 TREE_READONLY (decl) = 1;
4798 /* This decl isn't mentioned in the enclosing block, so add it to the
4799 list of temps. FIXME it seems a bit of a kludge to say that
4800 anonymous artificial vars aren't pushed, but everything else is. */
4801 if (DECL_NAME (decl) == NULL_TREE && !DECL_SEEN_IN_BIND_EXPR_P (decl))
4802 gimple_add_tmp_var (decl);
4804 gimplify_and_add (decl_s, pre_p);
4805 *expr_p = decl;
4806 return GS_OK;
4809 /* Optimize embedded COMPOUND_LITERAL_EXPRs within a CONSTRUCTOR,
4810 return a new CONSTRUCTOR if something changed. */
4812 static tree
4813 optimize_compound_literals_in_ctor (tree orig_ctor)
4815 tree ctor = orig_ctor;
4816 vec<constructor_elt, va_gc> *elts = CONSTRUCTOR_ELTS (ctor);
4817 unsigned int idx, num = vec_safe_length (elts);
4819 for (idx = 0; idx < num; idx++)
4821 tree value = (*elts)[idx].value;
4822 tree newval = value;
4823 if (TREE_CODE (value) == CONSTRUCTOR)
4824 newval = optimize_compound_literals_in_ctor (value);
4825 else if (TREE_CODE (value) == COMPOUND_LITERAL_EXPR)
4827 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (value);
4828 tree decl = DECL_EXPR_DECL (decl_s);
4829 tree init = DECL_INITIAL (decl);
4831 if (!TREE_ADDRESSABLE (value)
4832 && !TREE_ADDRESSABLE (decl)
4833 && init
4834 && TREE_CODE (init) == CONSTRUCTOR)
4835 newval = optimize_compound_literals_in_ctor (init);
4837 if (newval == value)
4838 continue;
4840 if (ctor == orig_ctor)
4842 ctor = copy_node (orig_ctor);
4843 CONSTRUCTOR_ELTS (ctor) = vec_safe_copy (elts);
4844 elts = CONSTRUCTOR_ELTS (ctor);
4846 (*elts)[idx].value = newval;
4848 return ctor;
4851 /* A subroutine of gimplify_modify_expr. Break out elements of a
4852 CONSTRUCTOR used as an initializer into separate MODIFY_EXPRs.
4854 Note that we still need to clear any elements that don't have explicit
4855 initializers, so if not all elements are initialized we keep the
4856 original MODIFY_EXPR, we just remove all of the constructor elements.
4858 If NOTIFY_TEMP_CREATION is true, do not gimplify, just return
4859 GS_ERROR if we would have to create a temporary when gimplifying
4860 this constructor. Otherwise, return GS_OK.
4862 If NOTIFY_TEMP_CREATION is false, just do the gimplification. */
4864 static enum gimplify_status
4865 gimplify_init_constructor (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
4866 bool want_value, bool notify_temp_creation)
4868 tree object, ctor, type;
4869 enum gimplify_status ret;
4870 vec<constructor_elt, va_gc> *elts;
4872 gcc_assert (TREE_CODE (TREE_OPERAND (*expr_p, 1)) == CONSTRUCTOR);
4874 if (!notify_temp_creation)
4876 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
4877 is_gimple_lvalue, fb_lvalue);
4878 if (ret == GS_ERROR)
4879 return ret;
4882 object = TREE_OPERAND (*expr_p, 0);
4883 ctor = TREE_OPERAND (*expr_p, 1)
4884 = optimize_compound_literals_in_ctor (TREE_OPERAND (*expr_p, 1));
4885 type = TREE_TYPE (ctor);
4886 elts = CONSTRUCTOR_ELTS (ctor);
4887 ret = GS_ALL_DONE;
4889 switch (TREE_CODE (type))
4891 case RECORD_TYPE:
4892 case UNION_TYPE:
4893 case QUAL_UNION_TYPE:
4894 case ARRAY_TYPE:
4896 /* Use readonly data for initializers of this or smaller size
4897 regardless of the num_nonzero_elements / num_unique_nonzero_elements
4898 ratio. */
4899 const HOST_WIDE_INT min_unique_size = 64;
4900 /* If num_nonzero_elements / num_unique_nonzero_elements ratio
4901 is smaller than this, use readonly data. */
4902 const int unique_nonzero_ratio = 8;
4903 /* True if a single access of the object must be ensured. This is the
4904 case if the target is volatile, the type is non-addressable and more
4905 than one field need to be assigned. */
4906 const bool ensure_single_access
4907 = TREE_THIS_VOLATILE (object)
4908 && !TREE_ADDRESSABLE (type)
4909 && vec_safe_length (elts) > 1;
4910 struct gimplify_init_ctor_preeval_data preeval_data;
4911 HOST_WIDE_INT num_ctor_elements, num_nonzero_elements;
4912 HOST_WIDE_INT num_unique_nonzero_elements;
4913 bool cleared, complete_p, valid_const_initializer;
4915 /* Aggregate types must lower constructors to initialization of
4916 individual elements. The exception is that a CONSTRUCTOR node
4917 with no elements indicates zero-initialization of the whole. */
4918 if (vec_safe_is_empty (elts))
4920 if (notify_temp_creation)
4921 return GS_OK;
4922 break;
4925 /* Fetch information about the constructor to direct later processing.
4926 We might want to make static versions of it in various cases, and
4927 can only do so if it known to be a valid constant initializer. */
4928 valid_const_initializer
4929 = categorize_ctor_elements (ctor, &num_nonzero_elements,
4930 &num_unique_nonzero_elements,
4931 &num_ctor_elements, &complete_p);
4933 /* If a const aggregate variable is being initialized, then it
4934 should never be a lose to promote the variable to be static. */
4935 if (valid_const_initializer
4936 && num_nonzero_elements > 1
4937 && TREE_READONLY (object)
4938 && VAR_P (object)
4939 && !DECL_REGISTER (object)
4940 && (flag_merge_constants >= 2 || !TREE_ADDRESSABLE (object))
4941 /* For ctors that have many repeated nonzero elements
4942 represented through RANGE_EXPRs, prefer initializing
4943 those through runtime loops over copies of large amounts
4944 of data from readonly data section. */
4945 && (num_unique_nonzero_elements
4946 > num_nonzero_elements / unique_nonzero_ratio
4947 || ((unsigned HOST_WIDE_INT) int_size_in_bytes (type)
4948 <= (unsigned HOST_WIDE_INT) min_unique_size)))
4950 if (notify_temp_creation)
4951 return GS_ERROR;
4953 DECL_INITIAL (object) = ctor;
4954 TREE_STATIC (object) = 1;
4955 if (!DECL_NAME (object))
4956 DECL_NAME (object) = create_tmp_var_name ("C");
4957 walk_tree (&DECL_INITIAL (object), force_labels_r, NULL, NULL);
4959 /* ??? C++ doesn't automatically append a .<number> to the
4960 assembler name, and even when it does, it looks at FE private
4961 data structures to figure out what that number should be,
4962 which are not set for this variable. I suppose this is
4963 important for local statics for inline functions, which aren't
4964 "local" in the object file sense. So in order to get a unique
4965 TU-local symbol, we must invoke the lhd version now. */
4966 lhd_set_decl_assembler_name (object);
4968 *expr_p = NULL_TREE;
4969 break;
4972 /* If there are "lots" of initialized elements, even discounting
4973 those that are not address constants (and thus *must* be
4974 computed at runtime), then partition the constructor into
4975 constant and non-constant parts. Block copy the constant
4976 parts in, then generate code for the non-constant parts. */
4977 /* TODO. There's code in cp/typeck.c to do this. */
4979 if (int_size_in_bytes (TREE_TYPE (ctor)) < 0)
4980 /* store_constructor will ignore the clearing of variable-sized
4981 objects. Initializers for such objects must explicitly set
4982 every field that needs to be set. */
4983 cleared = false;
4984 else if (!complete_p)
4985 /* If the constructor isn't complete, clear the whole object
4986 beforehand, unless CONSTRUCTOR_NO_CLEARING is set on it.
4988 ??? This ought not to be needed. For any element not present
4989 in the initializer, we should simply set them to zero. Except
4990 we'd need to *find* the elements that are not present, and that
4991 requires trickery to avoid quadratic compile-time behavior in
4992 large cases or excessive memory use in small cases. */
4993 cleared = !CONSTRUCTOR_NO_CLEARING (ctor);
4994 else if (num_ctor_elements - num_nonzero_elements
4995 > CLEAR_RATIO (optimize_function_for_speed_p (cfun))
4996 && num_nonzero_elements < num_ctor_elements / 4)
4997 /* If there are "lots" of zeros, it's more efficient to clear
4998 the memory and then set the nonzero elements. */
4999 cleared = true;
5000 else if (ensure_single_access && num_nonzero_elements == 0)
5001 /* If a single access to the target must be ensured and all elements
5002 are zero, then it's optimal to clear whatever their number. */
5003 cleared = true;
5004 else
5005 cleared = false;
5007 /* If there are "lots" of initialized elements, and all of them
5008 are valid address constants, then the entire initializer can
5009 be dropped to memory, and then memcpy'd out. Don't do this
5010 for sparse arrays, though, as it's more efficient to follow
5011 the standard CONSTRUCTOR behavior of memset followed by
5012 individual element initialization. Also don't do this for small
5013 all-zero initializers (which aren't big enough to merit
5014 clearing), and don't try to make bitwise copies of
5015 TREE_ADDRESSABLE types. */
5016 if (valid_const_initializer
5017 && complete_p
5018 && !(cleared || num_nonzero_elements == 0)
5019 && !TREE_ADDRESSABLE (type))
5021 HOST_WIDE_INT size = int_size_in_bytes (type);
5022 unsigned int align;
5024 /* ??? We can still get unbounded array types, at least
5025 from the C++ front end. This seems wrong, but attempt
5026 to work around it for now. */
5027 if (size < 0)
5029 size = int_size_in_bytes (TREE_TYPE (object));
5030 if (size >= 0)
5031 TREE_TYPE (ctor) = type = TREE_TYPE (object);
5034 /* Find the maximum alignment we can assume for the object. */
5035 /* ??? Make use of DECL_OFFSET_ALIGN. */
5036 if (DECL_P (object))
5037 align = DECL_ALIGN (object);
5038 else
5039 align = TYPE_ALIGN (type);
5041 /* Do a block move either if the size is so small as to make
5042 each individual move a sub-unit move on average, or if it
5043 is so large as to make individual moves inefficient. */
5044 if (size > 0
5045 && num_nonzero_elements > 1
5046 /* For ctors that have many repeated nonzero elements
5047 represented through RANGE_EXPRs, prefer initializing
5048 those through runtime loops over copies of large amounts
5049 of data from readonly data section. */
5050 && (num_unique_nonzero_elements
5051 > num_nonzero_elements / unique_nonzero_ratio
5052 || size <= min_unique_size)
5053 && (size < num_nonzero_elements
5054 || !can_move_by_pieces (size, align)))
5056 if (notify_temp_creation)
5057 return GS_ERROR;
5059 walk_tree (&ctor, force_labels_r, NULL, NULL);
5060 ctor = tree_output_constant_def (ctor);
5061 if (!useless_type_conversion_p (type, TREE_TYPE (ctor)))
5062 ctor = build1 (VIEW_CONVERT_EXPR, type, ctor);
5063 TREE_OPERAND (*expr_p, 1) = ctor;
5065 /* This is no longer an assignment of a CONSTRUCTOR, but
5066 we still may have processing to do on the LHS. So
5067 pretend we didn't do anything here to let that happen. */
5068 return GS_UNHANDLED;
5072 /* If a single access to the target must be ensured and there are
5073 nonzero elements or the zero elements are not assigned en masse,
5074 initialize the target from a temporary. */
5075 if (ensure_single_access && (num_nonzero_elements > 0 || !cleared))
5077 if (notify_temp_creation)
5078 return GS_ERROR;
5080 tree temp = create_tmp_var (TYPE_MAIN_VARIANT (type));
5081 TREE_OPERAND (*expr_p, 0) = temp;
5082 *expr_p = build2 (COMPOUND_EXPR, TREE_TYPE (*expr_p),
5083 *expr_p,
5084 build2 (MODIFY_EXPR, void_type_node,
5085 object, temp));
5086 return GS_OK;
5089 if (notify_temp_creation)
5090 return GS_OK;
5092 /* If there are nonzero elements and if needed, pre-evaluate to capture
5093 elements overlapping with the lhs into temporaries. We must do this
5094 before clearing to fetch the values before they are zeroed-out. */
5095 if (num_nonzero_elements > 0 && TREE_CODE (*expr_p) != INIT_EXPR)
5097 preeval_data.lhs_base_decl = get_base_address (object);
5098 if (!DECL_P (preeval_data.lhs_base_decl))
5099 preeval_data.lhs_base_decl = NULL;
5100 preeval_data.lhs_alias_set = get_alias_set (object);
5102 gimplify_init_ctor_preeval (&TREE_OPERAND (*expr_p, 1),
5103 pre_p, post_p, &preeval_data);
5106 bool ctor_has_side_effects_p
5107 = TREE_SIDE_EFFECTS (TREE_OPERAND (*expr_p, 1));
5109 if (cleared)
5111 /* Zap the CONSTRUCTOR element list, which simplifies this case.
5112 Note that we still have to gimplify, in order to handle the
5113 case of variable sized types. Avoid shared tree structures. */
5114 CONSTRUCTOR_ELTS (ctor) = NULL;
5115 TREE_SIDE_EFFECTS (ctor) = 0;
5116 object = unshare_expr (object);
5117 gimplify_stmt (expr_p, pre_p);
5120 /* If we have not block cleared the object, or if there are nonzero
5121 elements in the constructor, or if the constructor has side effects,
5122 add assignments to the individual scalar fields of the object. */
5123 if (!cleared
5124 || num_nonzero_elements > 0
5125 || ctor_has_side_effects_p)
5126 gimplify_init_ctor_eval (object, elts, pre_p, cleared);
5128 *expr_p = NULL_TREE;
5130 break;
5132 case COMPLEX_TYPE:
5134 tree r, i;
5136 if (notify_temp_creation)
5137 return GS_OK;
5139 /* Extract the real and imaginary parts out of the ctor. */
5140 gcc_assert (elts->length () == 2);
5141 r = (*elts)[0].value;
5142 i = (*elts)[1].value;
5143 if (r == NULL || i == NULL)
5145 tree zero = build_zero_cst (TREE_TYPE (type));
5146 if (r == NULL)
5147 r = zero;
5148 if (i == NULL)
5149 i = zero;
5152 /* Complex types have either COMPLEX_CST or COMPLEX_EXPR to
5153 represent creation of a complex value. */
5154 if (TREE_CONSTANT (r) && TREE_CONSTANT (i))
5156 ctor = build_complex (type, r, i);
5157 TREE_OPERAND (*expr_p, 1) = ctor;
5159 else
5161 ctor = build2 (COMPLEX_EXPR, type, r, i);
5162 TREE_OPERAND (*expr_p, 1) = ctor;
5163 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 1),
5164 pre_p,
5165 post_p,
5166 rhs_predicate_for (TREE_OPERAND (*expr_p, 0)),
5167 fb_rvalue);
5170 break;
5172 case VECTOR_TYPE:
5174 unsigned HOST_WIDE_INT ix;
5175 constructor_elt *ce;
5177 if (notify_temp_creation)
5178 return GS_OK;
5180 /* Go ahead and simplify constant constructors to VECTOR_CST. */
5181 if (TREE_CONSTANT (ctor))
5183 bool constant_p = true;
5184 tree value;
5186 /* Even when ctor is constant, it might contain non-*_CST
5187 elements, such as addresses or trapping values like
5188 1.0/0.0 - 1.0/0.0. Such expressions don't belong
5189 in VECTOR_CST nodes. */
5190 FOR_EACH_CONSTRUCTOR_VALUE (elts, ix, value)
5191 if (!CONSTANT_CLASS_P (value))
5193 constant_p = false;
5194 break;
5197 if (constant_p)
5199 TREE_OPERAND (*expr_p, 1) = build_vector_from_ctor (type, elts);
5200 break;
5203 TREE_CONSTANT (ctor) = 0;
5206 /* Vector types use CONSTRUCTOR all the way through gimple
5207 compilation as a general initializer. */
5208 FOR_EACH_VEC_SAFE_ELT (elts, ix, ce)
5210 enum gimplify_status tret;
5211 tret = gimplify_expr (&ce->value, pre_p, post_p, is_gimple_val,
5212 fb_rvalue);
5213 if (tret == GS_ERROR)
5214 ret = GS_ERROR;
5215 else if (TREE_STATIC (ctor)
5216 && !initializer_constant_valid_p (ce->value,
5217 TREE_TYPE (ce->value)))
5218 TREE_STATIC (ctor) = 0;
5220 recompute_constructor_flags (ctor);
5221 if (!is_gimple_reg (TREE_OPERAND (*expr_p, 0)))
5222 TREE_OPERAND (*expr_p, 1) = get_formal_tmp_var (ctor, pre_p);
5224 break;
5226 default:
5227 /* So how did we get a CONSTRUCTOR for a scalar type? */
5228 gcc_unreachable ();
5231 if (ret == GS_ERROR)
5232 return GS_ERROR;
5233 /* If we have gimplified both sides of the initializer but have
5234 not emitted an assignment, do so now. */
5235 if (*expr_p)
5237 tree lhs = TREE_OPERAND (*expr_p, 0);
5238 tree rhs = TREE_OPERAND (*expr_p, 1);
5239 if (want_value && object == lhs)
5240 lhs = unshare_expr (lhs);
5241 gassign *init = gimple_build_assign (lhs, rhs);
5242 gimplify_seq_add_stmt (pre_p, init);
5244 if (want_value)
5246 *expr_p = object;
5247 return GS_OK;
5249 else
5251 *expr_p = NULL;
5252 return GS_ALL_DONE;
5256 /* Given a pointer value OP0, return a simplified version of an
5257 indirection through OP0, or NULL_TREE if no simplification is
5258 possible. This may only be applied to a rhs of an expression.
5259 Note that the resulting type may be different from the type pointed
5260 to in the sense that it is still compatible from the langhooks
5261 point of view. */
5263 static tree
5264 gimple_fold_indirect_ref_rhs (tree t)
5266 return gimple_fold_indirect_ref (t);
5269 /* Subroutine of gimplify_modify_expr to do simplifications of
5270 MODIFY_EXPRs based on the code of the RHS. We loop for as long as
5271 something changes. */
5273 static enum gimplify_status
5274 gimplify_modify_expr_rhs (tree *expr_p, tree *from_p, tree *to_p,
5275 gimple_seq *pre_p, gimple_seq *post_p,
5276 bool want_value)
5278 enum gimplify_status ret = GS_UNHANDLED;
5279 bool changed;
5283 changed = false;
5284 switch (TREE_CODE (*from_p))
5286 case VAR_DECL:
5287 /* If we're assigning from a read-only variable initialized with
5288 a constructor and not volatile, do the direct assignment from
5289 the constructor, but only if the target is not volatile either
5290 since this latter assignment might end up being done on a per
5291 field basis. However, if the target is volatile and the type
5292 is aggregate and non-addressable, gimplify_init_constructor
5293 knows that it needs to ensure a single access to the target
5294 and it will return GS_OK only in this case. */
5295 if (TREE_READONLY (*from_p)
5296 && DECL_INITIAL (*from_p)
5297 && TREE_CODE (DECL_INITIAL (*from_p)) == CONSTRUCTOR
5298 && !TREE_THIS_VOLATILE (*from_p)
5299 && (!TREE_THIS_VOLATILE (*to_p)
5300 || (AGGREGATE_TYPE_P (TREE_TYPE (*to_p))
5301 && !TREE_ADDRESSABLE (TREE_TYPE (*to_p)))))
5303 tree old_from = *from_p;
5304 enum gimplify_status subret;
5306 /* Move the constructor into the RHS. */
5307 *from_p = unshare_expr (DECL_INITIAL (*from_p));
5309 /* Let's see if gimplify_init_constructor will need to put
5310 it in memory. */
5311 subret = gimplify_init_constructor (expr_p, NULL, NULL,
5312 false, true);
5313 if (subret == GS_ERROR)
5315 /* If so, revert the change. */
5316 *from_p = old_from;
5318 else
5320 ret = GS_OK;
5321 changed = true;
5324 break;
5325 case INDIRECT_REF:
5327 /* If we have code like
5329 *(const A*)(A*)&x
5331 where the type of "x" is a (possibly cv-qualified variant
5332 of "A"), treat the entire expression as identical to "x".
5333 This kind of code arises in C++ when an object is bound
5334 to a const reference, and if "x" is a TARGET_EXPR we want
5335 to take advantage of the optimization below. */
5336 bool volatile_p = TREE_THIS_VOLATILE (*from_p);
5337 tree t = gimple_fold_indirect_ref_rhs (TREE_OPERAND (*from_p, 0));
5338 if (t)
5340 if (TREE_THIS_VOLATILE (t) != volatile_p)
5342 if (DECL_P (t))
5343 t = build_simple_mem_ref_loc (EXPR_LOCATION (*from_p),
5344 build_fold_addr_expr (t));
5345 if (REFERENCE_CLASS_P (t))
5346 TREE_THIS_VOLATILE (t) = volatile_p;
5348 *from_p = t;
5349 ret = GS_OK;
5350 changed = true;
5352 break;
5355 case TARGET_EXPR:
5357 /* If we are initializing something from a TARGET_EXPR, strip the
5358 TARGET_EXPR and initialize it directly, if possible. This can't
5359 be done if the initializer is void, since that implies that the
5360 temporary is set in some non-trivial way.
5362 ??? What about code that pulls out the temp and uses it
5363 elsewhere? I think that such code never uses the TARGET_EXPR as
5364 an initializer. If I'm wrong, we'll die because the temp won't
5365 have any RTL. In that case, I guess we'll need to replace
5366 references somehow. */
5367 tree init = TARGET_EXPR_INITIAL (*from_p);
5369 if (init
5370 && (TREE_CODE (*expr_p) != MODIFY_EXPR
5371 || !TARGET_EXPR_NO_ELIDE (*from_p))
5372 && !VOID_TYPE_P (TREE_TYPE (init)))
5374 *from_p = init;
5375 ret = GS_OK;
5376 changed = true;
5379 break;
5381 case COMPOUND_EXPR:
5382 /* Remove any COMPOUND_EXPR in the RHS so the following cases will be
5383 caught. */
5384 gimplify_compound_expr (from_p, pre_p, true);
5385 ret = GS_OK;
5386 changed = true;
5387 break;
5389 case CONSTRUCTOR:
5390 /* If we already made some changes, let the front end have a
5391 crack at this before we break it down. */
5392 if (ret != GS_UNHANDLED)
5393 break;
5394 /* If we're initializing from a CONSTRUCTOR, break this into
5395 individual MODIFY_EXPRs. */
5396 return gimplify_init_constructor (expr_p, pre_p, post_p, want_value,
5397 false);
5399 case COND_EXPR:
5400 /* If we're assigning to a non-register type, push the assignment
5401 down into the branches. This is mandatory for ADDRESSABLE types,
5402 since we cannot generate temporaries for such, but it saves a
5403 copy in other cases as well. */
5404 if (!is_gimple_reg_type (TREE_TYPE (*from_p)))
5406 /* This code should mirror the code in gimplify_cond_expr. */
5407 enum tree_code code = TREE_CODE (*expr_p);
5408 tree cond = *from_p;
5409 tree result = *to_p;
5411 ret = gimplify_expr (&result, pre_p, post_p,
5412 is_gimple_lvalue, fb_lvalue);
5413 if (ret != GS_ERROR)
5414 ret = GS_OK;
5416 /* If we are going to write RESULT more than once, clear
5417 TREE_READONLY flag, otherwise we might incorrectly promote
5418 the variable to static const and initialize it at compile
5419 time in one of the branches. */
5420 if (VAR_P (result)
5421 && TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node
5422 && TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
5423 TREE_READONLY (result) = 0;
5424 if (TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node)
5425 TREE_OPERAND (cond, 1)
5426 = build2 (code, void_type_node, result,
5427 TREE_OPERAND (cond, 1));
5428 if (TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
5429 TREE_OPERAND (cond, 2)
5430 = build2 (code, void_type_node, unshare_expr (result),
5431 TREE_OPERAND (cond, 2));
5433 TREE_TYPE (cond) = void_type_node;
5434 recalculate_side_effects (cond);
5436 if (want_value)
5438 gimplify_and_add (cond, pre_p);
5439 *expr_p = unshare_expr (result);
5441 else
5442 *expr_p = cond;
5443 return ret;
5445 break;
5447 case CALL_EXPR:
5448 /* For calls that return in memory, give *to_p as the CALL_EXPR's
5449 return slot so that we don't generate a temporary. */
5450 if (!CALL_EXPR_RETURN_SLOT_OPT (*from_p)
5451 && aggregate_value_p (*from_p, *from_p))
5453 bool use_target;
5455 if (!(rhs_predicate_for (*to_p))(*from_p))
5456 /* If we need a temporary, *to_p isn't accurate. */
5457 use_target = false;
5458 /* It's OK to use the return slot directly unless it's an NRV. */
5459 else if (TREE_CODE (*to_p) == RESULT_DECL
5460 && DECL_NAME (*to_p) == NULL_TREE
5461 && needs_to_live_in_memory (*to_p))
5462 use_target = true;
5463 else if (is_gimple_reg_type (TREE_TYPE (*to_p))
5464 || (DECL_P (*to_p) && DECL_REGISTER (*to_p)))
5465 /* Don't force regs into memory. */
5466 use_target = false;
5467 else if (TREE_CODE (*expr_p) == INIT_EXPR)
5468 /* It's OK to use the target directly if it's being
5469 initialized. */
5470 use_target = true;
5471 else if (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (*to_p)))
5472 != INTEGER_CST)
5473 /* Always use the target and thus RSO for variable-sized types.
5474 GIMPLE cannot deal with a variable-sized assignment
5475 embedded in a call statement. */
5476 use_target = true;
5477 else if (TREE_CODE (*to_p) != SSA_NAME
5478 && (!is_gimple_variable (*to_p)
5479 || needs_to_live_in_memory (*to_p)))
5480 /* Don't use the original target if it's already addressable;
5481 if its address escapes, and the called function uses the
5482 NRV optimization, a conforming program could see *to_p
5483 change before the called function returns; see c++/19317.
5484 When optimizing, the return_slot pass marks more functions
5485 as safe after we have escape info. */
5486 use_target = false;
5487 else
5488 use_target = true;
5490 if (use_target)
5492 CALL_EXPR_RETURN_SLOT_OPT (*from_p) = 1;
5493 mark_addressable (*to_p);
5496 break;
5498 case WITH_SIZE_EXPR:
5499 /* Likewise for calls that return an aggregate of non-constant size,
5500 since we would not be able to generate a temporary at all. */
5501 if (TREE_CODE (TREE_OPERAND (*from_p, 0)) == CALL_EXPR)
5503 *from_p = TREE_OPERAND (*from_p, 0);
5504 /* We don't change ret in this case because the
5505 WITH_SIZE_EXPR might have been added in
5506 gimplify_modify_expr, so returning GS_OK would lead to an
5507 infinite loop. */
5508 changed = true;
5510 break;
5512 /* If we're initializing from a container, push the initialization
5513 inside it. */
5514 case CLEANUP_POINT_EXPR:
5515 case BIND_EXPR:
5516 case STATEMENT_LIST:
5518 tree wrap = *from_p;
5519 tree t;
5521 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_min_lval,
5522 fb_lvalue);
5523 if (ret != GS_ERROR)
5524 ret = GS_OK;
5526 t = voidify_wrapper_expr (wrap, *expr_p);
5527 gcc_assert (t == *expr_p);
5529 if (want_value)
5531 gimplify_and_add (wrap, pre_p);
5532 *expr_p = unshare_expr (*to_p);
5534 else
5535 *expr_p = wrap;
5536 return GS_OK;
5539 case NOP_EXPR:
5540 /* Pull out compound literal expressions from a NOP_EXPR.
5541 Those are created in the C FE to drop qualifiers during
5542 lvalue conversion. */
5543 if ((TREE_CODE (TREE_OPERAND (*from_p, 0)) == COMPOUND_LITERAL_EXPR)
5544 && tree_ssa_useless_type_conversion (*from_p))
5546 *from_p = TREE_OPERAND (*from_p, 0);
5547 ret = GS_OK;
5548 changed = true;
5550 break;
5552 case COMPOUND_LITERAL_EXPR:
5554 tree complit = TREE_OPERAND (*expr_p, 1);
5555 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (complit);
5556 tree decl = DECL_EXPR_DECL (decl_s);
5557 tree init = DECL_INITIAL (decl);
5559 /* struct T x = (struct T) { 0, 1, 2 } can be optimized
5560 into struct T x = { 0, 1, 2 } if the address of the
5561 compound literal has never been taken. */
5562 if (!TREE_ADDRESSABLE (complit)
5563 && !TREE_ADDRESSABLE (decl)
5564 && init)
5566 *expr_p = copy_node (*expr_p);
5567 TREE_OPERAND (*expr_p, 1) = init;
5568 return GS_OK;
5572 default:
5573 break;
5576 while (changed);
5578 return ret;
5582 /* Return true if T looks like a valid GIMPLE statement. */
5584 static bool
5585 is_gimple_stmt (tree t)
5587 const enum tree_code code = TREE_CODE (t);
5589 switch (code)
5591 case NOP_EXPR:
5592 /* The only valid NOP_EXPR is the empty statement. */
5593 return IS_EMPTY_STMT (t);
5595 case BIND_EXPR:
5596 case COND_EXPR:
5597 /* These are only valid if they're void. */
5598 return TREE_TYPE (t) == NULL || VOID_TYPE_P (TREE_TYPE (t));
5600 case SWITCH_EXPR:
5601 case GOTO_EXPR:
5602 case RETURN_EXPR:
5603 case LABEL_EXPR:
5604 case CASE_LABEL_EXPR:
5605 case TRY_CATCH_EXPR:
5606 case TRY_FINALLY_EXPR:
5607 case EH_FILTER_EXPR:
5608 case CATCH_EXPR:
5609 case ASM_EXPR:
5610 case STATEMENT_LIST:
5611 case OACC_PARALLEL:
5612 case OACC_KERNELS:
5613 case OACC_SERIAL:
5614 case OACC_DATA:
5615 case OACC_HOST_DATA:
5616 case OACC_DECLARE:
5617 case OACC_UPDATE:
5618 case OACC_ENTER_DATA:
5619 case OACC_EXIT_DATA:
5620 case OACC_CACHE:
5621 case OMP_PARALLEL:
5622 case OMP_FOR:
5623 case OMP_SIMD:
5624 case OMP_DISTRIBUTE:
5625 case OMP_LOOP:
5626 case OACC_LOOP:
5627 case OMP_SCAN:
5628 case OMP_SECTIONS:
5629 case OMP_SECTION:
5630 case OMP_SINGLE:
5631 case OMP_MASTER:
5632 case OMP_TASKGROUP:
5633 case OMP_ORDERED:
5634 case OMP_CRITICAL:
5635 case OMP_TASK:
5636 case OMP_TARGET:
5637 case OMP_TARGET_DATA:
5638 case OMP_TARGET_UPDATE:
5639 case OMP_TARGET_ENTER_DATA:
5640 case OMP_TARGET_EXIT_DATA:
5641 case OMP_TASKLOOP:
5642 case OMP_TEAMS:
5643 /* These are always void. */
5644 return true;
5646 case CALL_EXPR:
5647 case MODIFY_EXPR:
5648 case PREDICT_EXPR:
5649 /* These are valid regardless of their type. */
5650 return true;
5652 default:
5653 return false;
5658 /* Promote partial stores to COMPLEX variables to total stores. *EXPR_P is
5659 a MODIFY_EXPR with a lhs of a REAL/IMAGPART_EXPR of a gimple register.
5661 IMPORTANT NOTE: This promotion is performed by introducing a load of the
5662 other, unmodified part of the complex object just before the total store.
5663 As a consequence, if the object is still uninitialized, an undefined value
5664 will be loaded into a register, which may result in a spurious exception
5665 if the register is floating-point and the value happens to be a signaling
5666 NaN for example. Then the fully-fledged complex operations lowering pass
5667 followed by a DCE pass are necessary in order to fix things up. */
5669 static enum gimplify_status
5670 gimplify_modify_expr_complex_part (tree *expr_p, gimple_seq *pre_p,
5671 bool want_value)
5673 enum tree_code code, ocode;
5674 tree lhs, rhs, new_rhs, other, realpart, imagpart;
5676 lhs = TREE_OPERAND (*expr_p, 0);
5677 rhs = TREE_OPERAND (*expr_p, 1);
5678 code = TREE_CODE (lhs);
5679 lhs = TREE_OPERAND (lhs, 0);
5681 ocode = code == REALPART_EXPR ? IMAGPART_EXPR : REALPART_EXPR;
5682 other = build1 (ocode, TREE_TYPE (rhs), lhs);
5683 TREE_NO_WARNING (other) = 1;
5684 other = get_formal_tmp_var (other, pre_p);
5686 realpart = code == REALPART_EXPR ? rhs : other;
5687 imagpart = code == REALPART_EXPR ? other : rhs;
5689 if (TREE_CONSTANT (realpart) && TREE_CONSTANT (imagpart))
5690 new_rhs = build_complex (TREE_TYPE (lhs), realpart, imagpart);
5691 else
5692 new_rhs = build2 (COMPLEX_EXPR, TREE_TYPE (lhs), realpart, imagpart);
5694 gimplify_seq_add_stmt (pre_p, gimple_build_assign (lhs, new_rhs));
5695 *expr_p = (want_value) ? rhs : NULL_TREE;
5697 return GS_ALL_DONE;
5700 /* Gimplify the MODIFY_EXPR node pointed to by EXPR_P.
5702 modify_expr
5703 : varname '=' rhs
5704 | '*' ID '=' rhs
5706 PRE_P points to the list where side effects that must happen before
5707 *EXPR_P should be stored.
5709 POST_P points to the list where side effects that must happen after
5710 *EXPR_P should be stored.
5712 WANT_VALUE is nonzero iff we want to use the value of this expression
5713 in another expression. */
5715 static enum gimplify_status
5716 gimplify_modify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
5717 bool want_value)
5719 tree *from_p = &TREE_OPERAND (*expr_p, 1);
5720 tree *to_p = &TREE_OPERAND (*expr_p, 0);
5721 enum gimplify_status ret = GS_UNHANDLED;
5722 gimple *assign;
5723 location_t loc = EXPR_LOCATION (*expr_p);
5724 gimple_stmt_iterator gsi;
5726 gcc_assert (TREE_CODE (*expr_p) == MODIFY_EXPR
5727 || TREE_CODE (*expr_p) == INIT_EXPR);
5729 /* Trying to simplify a clobber using normal logic doesn't work,
5730 so handle it here. */
5731 if (TREE_CLOBBER_P (*from_p))
5733 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
5734 if (ret == GS_ERROR)
5735 return ret;
5736 gcc_assert (!want_value);
5737 if (!VAR_P (*to_p) && TREE_CODE (*to_p) != MEM_REF)
5739 tree addr = get_initialized_tmp_var (build_fold_addr_expr (*to_p),
5740 pre_p, post_p);
5741 *to_p = build_simple_mem_ref_loc (EXPR_LOCATION (*to_p), addr);
5743 gimplify_seq_add_stmt (pre_p, gimple_build_assign (*to_p, *from_p));
5744 *expr_p = NULL;
5745 return GS_ALL_DONE;
5748 /* Insert pointer conversions required by the middle-end that are not
5749 required by the frontend. This fixes middle-end type checking for
5750 for example gcc.dg/redecl-6.c. */
5751 if (POINTER_TYPE_P (TREE_TYPE (*to_p)))
5753 STRIP_USELESS_TYPE_CONVERSION (*from_p);
5754 if (!useless_type_conversion_p (TREE_TYPE (*to_p), TREE_TYPE (*from_p)))
5755 *from_p = fold_convert_loc (loc, TREE_TYPE (*to_p), *from_p);
5758 /* See if any simplifications can be done based on what the RHS is. */
5759 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
5760 want_value);
5761 if (ret != GS_UNHANDLED)
5762 return ret;
5764 /* For empty types only gimplify the left hand side and right hand
5765 side as statements and throw away the assignment. Do this after
5766 gimplify_modify_expr_rhs so we handle TARGET_EXPRs of addressable
5767 types properly. */
5768 if (is_empty_type (TREE_TYPE (*from_p))
5769 && !want_value
5770 /* Don't do this for calls that return addressable types, expand_call
5771 relies on those having a lhs. */
5772 && !(TREE_ADDRESSABLE (TREE_TYPE (*from_p))
5773 && TREE_CODE (*from_p) == CALL_EXPR))
5775 gimplify_stmt (from_p, pre_p);
5776 gimplify_stmt (to_p, pre_p);
5777 *expr_p = NULL_TREE;
5778 return GS_ALL_DONE;
5781 /* If the value being copied is of variable width, compute the length
5782 of the copy into a WITH_SIZE_EXPR. Note that we need to do this
5783 before gimplifying any of the operands so that we can resolve any
5784 PLACEHOLDER_EXPRs in the size. Also note that the RTL expander uses
5785 the size of the expression to be copied, not of the destination, so
5786 that is what we must do here. */
5787 maybe_with_size_expr (from_p);
5789 /* As a special case, we have to temporarily allow for assignments
5790 with a CALL_EXPR on the RHS. Since in GIMPLE a function call is
5791 a toplevel statement, when gimplifying the GENERIC expression
5792 MODIFY_EXPR <a, CALL_EXPR <foo>>, we cannot create the tuple
5793 GIMPLE_ASSIGN <a, GIMPLE_CALL <foo>>.
5795 Instead, we need to create the tuple GIMPLE_CALL <a, foo>. To
5796 prevent gimplify_expr from trying to create a new temporary for
5797 foo's LHS, we tell it that it should only gimplify until it
5798 reaches the CALL_EXPR. On return from gimplify_expr, the newly
5799 created GIMPLE_CALL <foo> will be the last statement in *PRE_P
5800 and all we need to do here is set 'a' to be its LHS. */
5802 /* Gimplify the RHS first for C++17 and bug 71104. */
5803 gimple_predicate initial_pred = initial_rhs_predicate_for (*to_p);
5804 ret = gimplify_expr (from_p, pre_p, post_p, initial_pred, fb_rvalue);
5805 if (ret == GS_ERROR)
5806 return ret;
5808 /* Then gimplify the LHS. */
5809 /* If we gimplified the RHS to a CALL_EXPR and that call may return
5810 twice we have to make sure to gimplify into non-SSA as otherwise
5811 the abnormal edge added later will make those defs not dominate
5812 their uses.
5813 ??? Technically this applies only to the registers used in the
5814 resulting non-register *TO_P. */
5815 bool saved_into_ssa = gimplify_ctxp->into_ssa;
5816 if (saved_into_ssa
5817 && TREE_CODE (*from_p) == CALL_EXPR
5818 && call_expr_flags (*from_p) & ECF_RETURNS_TWICE)
5819 gimplify_ctxp->into_ssa = false;
5820 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
5821 gimplify_ctxp->into_ssa = saved_into_ssa;
5822 if (ret == GS_ERROR)
5823 return ret;
5825 /* Now that the LHS is gimplified, re-gimplify the RHS if our initial
5826 guess for the predicate was wrong. */
5827 gimple_predicate final_pred = rhs_predicate_for (*to_p);
5828 if (final_pred != initial_pred)
5830 ret = gimplify_expr (from_p, pre_p, post_p, final_pred, fb_rvalue);
5831 if (ret == GS_ERROR)
5832 return ret;
5835 /* In case of va_arg internal fn wrappped in a WITH_SIZE_EXPR, add the type
5836 size as argument to the call. */
5837 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
5839 tree call = TREE_OPERAND (*from_p, 0);
5840 tree vlasize = TREE_OPERAND (*from_p, 1);
5842 if (TREE_CODE (call) == CALL_EXPR
5843 && CALL_EXPR_IFN (call) == IFN_VA_ARG)
5845 int nargs = call_expr_nargs (call);
5846 tree type = TREE_TYPE (call);
5847 tree ap = CALL_EXPR_ARG (call, 0);
5848 tree tag = CALL_EXPR_ARG (call, 1);
5849 tree aptag = CALL_EXPR_ARG (call, 2);
5850 tree newcall = build_call_expr_internal_loc (EXPR_LOCATION (call),
5851 IFN_VA_ARG, type,
5852 nargs + 1, ap, tag,
5853 aptag, vlasize);
5854 TREE_OPERAND (*from_p, 0) = newcall;
5858 /* Now see if the above changed *from_p to something we handle specially. */
5859 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
5860 want_value);
5861 if (ret != GS_UNHANDLED)
5862 return ret;
5864 /* If we've got a variable sized assignment between two lvalues (i.e. does
5865 not involve a call), then we can make things a bit more straightforward
5866 by converting the assignment to memcpy or memset. */
5867 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
5869 tree from = TREE_OPERAND (*from_p, 0);
5870 tree size = TREE_OPERAND (*from_p, 1);
5872 if (TREE_CODE (from) == CONSTRUCTOR)
5873 return gimplify_modify_expr_to_memset (expr_p, size, want_value, pre_p);
5875 if (is_gimple_addressable (from))
5877 *from_p = from;
5878 return gimplify_modify_expr_to_memcpy (expr_p, size, want_value,
5879 pre_p);
5883 /* Transform partial stores to non-addressable complex variables into
5884 total stores. This allows us to use real instead of virtual operands
5885 for these variables, which improves optimization. */
5886 if ((TREE_CODE (*to_p) == REALPART_EXPR
5887 || TREE_CODE (*to_p) == IMAGPART_EXPR)
5888 && is_gimple_reg (TREE_OPERAND (*to_p, 0)))
5889 return gimplify_modify_expr_complex_part (expr_p, pre_p, want_value);
5891 /* Try to alleviate the effects of the gimplification creating artificial
5892 temporaries (see for example is_gimple_reg_rhs) on the debug info, but
5893 make sure not to create DECL_DEBUG_EXPR links across functions. */
5894 if (!gimplify_ctxp->into_ssa
5895 && VAR_P (*from_p)
5896 && DECL_IGNORED_P (*from_p)
5897 && DECL_P (*to_p)
5898 && !DECL_IGNORED_P (*to_p)
5899 && decl_function_context (*to_p) == current_function_decl
5900 && decl_function_context (*from_p) == current_function_decl)
5902 if (!DECL_NAME (*from_p) && DECL_NAME (*to_p))
5903 DECL_NAME (*from_p)
5904 = create_tmp_var_name (IDENTIFIER_POINTER (DECL_NAME (*to_p)));
5905 DECL_HAS_DEBUG_EXPR_P (*from_p) = 1;
5906 SET_DECL_DEBUG_EXPR (*from_p, *to_p);
5909 if (want_value && TREE_THIS_VOLATILE (*to_p))
5910 *from_p = get_initialized_tmp_var (*from_p, pre_p, post_p);
5912 if (TREE_CODE (*from_p) == CALL_EXPR)
5914 /* Since the RHS is a CALL_EXPR, we need to create a GIMPLE_CALL
5915 instead of a GIMPLE_ASSIGN. */
5916 gcall *call_stmt;
5917 if (CALL_EXPR_FN (*from_p) == NULL_TREE)
5919 /* Gimplify internal functions created in the FEs. */
5920 int nargs = call_expr_nargs (*from_p), i;
5921 enum internal_fn ifn = CALL_EXPR_IFN (*from_p);
5922 auto_vec<tree> vargs (nargs);
5924 for (i = 0; i < nargs; i++)
5926 gimplify_arg (&CALL_EXPR_ARG (*from_p, i), pre_p,
5927 EXPR_LOCATION (*from_p));
5928 vargs.quick_push (CALL_EXPR_ARG (*from_p, i));
5930 call_stmt = gimple_build_call_internal_vec (ifn, vargs);
5931 gimple_call_set_nothrow (call_stmt, TREE_NOTHROW (*from_p));
5932 gimple_set_location (call_stmt, EXPR_LOCATION (*expr_p));
5934 else
5936 tree fnptrtype = TREE_TYPE (CALL_EXPR_FN (*from_p));
5937 CALL_EXPR_FN (*from_p) = TREE_OPERAND (CALL_EXPR_FN (*from_p), 0);
5938 STRIP_USELESS_TYPE_CONVERSION (CALL_EXPR_FN (*from_p));
5939 tree fndecl = get_callee_fndecl (*from_p);
5940 if (fndecl
5941 && fndecl_built_in_p (fndecl, BUILT_IN_EXPECT)
5942 && call_expr_nargs (*from_p) == 3)
5943 call_stmt = gimple_build_call_internal (IFN_BUILTIN_EXPECT, 3,
5944 CALL_EXPR_ARG (*from_p, 0),
5945 CALL_EXPR_ARG (*from_p, 1),
5946 CALL_EXPR_ARG (*from_p, 2));
5947 else
5949 call_stmt = gimple_build_call_from_tree (*from_p, fnptrtype);
5952 notice_special_calls (call_stmt);
5953 if (!gimple_call_noreturn_p (call_stmt) || !should_remove_lhs_p (*to_p))
5954 gimple_call_set_lhs (call_stmt, *to_p);
5955 else if (TREE_CODE (*to_p) == SSA_NAME)
5956 /* The above is somewhat premature, avoid ICEing later for a
5957 SSA name w/o a definition. We may have uses in the GIMPLE IL.
5958 ??? This doesn't make it a default-def. */
5959 SSA_NAME_DEF_STMT (*to_p) = gimple_build_nop ();
5961 assign = call_stmt;
5963 else
5965 assign = gimple_build_assign (*to_p, *from_p);
5966 gimple_set_location (assign, EXPR_LOCATION (*expr_p));
5967 if (COMPARISON_CLASS_P (*from_p))
5968 gimple_set_no_warning (assign, TREE_NO_WARNING (*from_p));
5971 if (gimplify_ctxp->into_ssa && is_gimple_reg (*to_p))
5973 /* We should have got an SSA name from the start. */
5974 gcc_assert (TREE_CODE (*to_p) == SSA_NAME
5975 || ! gimple_in_ssa_p (cfun));
5978 gimplify_seq_add_stmt (pre_p, assign);
5979 gsi = gsi_last (*pre_p);
5980 maybe_fold_stmt (&gsi);
5982 if (want_value)
5984 *expr_p = TREE_THIS_VOLATILE (*to_p) ? *from_p : unshare_expr (*to_p);
5985 return GS_OK;
5987 else
5988 *expr_p = NULL;
5990 return GS_ALL_DONE;
5993 /* Gimplify a comparison between two variable-sized objects. Do this
5994 with a call to BUILT_IN_MEMCMP. */
5996 static enum gimplify_status
5997 gimplify_variable_sized_compare (tree *expr_p)
5999 location_t loc = EXPR_LOCATION (*expr_p);
6000 tree op0 = TREE_OPERAND (*expr_p, 0);
6001 tree op1 = TREE_OPERAND (*expr_p, 1);
6002 tree t, arg, dest, src, expr;
6004 arg = TYPE_SIZE_UNIT (TREE_TYPE (op0));
6005 arg = unshare_expr (arg);
6006 arg = SUBSTITUTE_PLACEHOLDER_IN_EXPR (arg, op0);
6007 src = build_fold_addr_expr_loc (loc, op1);
6008 dest = build_fold_addr_expr_loc (loc, op0);
6009 t = builtin_decl_implicit (BUILT_IN_MEMCMP);
6010 t = build_call_expr_loc (loc, t, 3, dest, src, arg);
6012 expr
6013 = build2 (TREE_CODE (*expr_p), TREE_TYPE (*expr_p), t, integer_zero_node);
6014 SET_EXPR_LOCATION (expr, loc);
6015 *expr_p = expr;
6017 return GS_OK;
6020 /* Gimplify a comparison between two aggregate objects of integral scalar
6021 mode as a comparison between the bitwise equivalent scalar values. */
6023 static enum gimplify_status
6024 gimplify_scalar_mode_aggregate_compare (tree *expr_p)
6026 location_t loc = EXPR_LOCATION (*expr_p);
6027 tree op0 = TREE_OPERAND (*expr_p, 0);
6028 tree op1 = TREE_OPERAND (*expr_p, 1);
6030 tree type = TREE_TYPE (op0);
6031 tree scalar_type = lang_hooks.types.type_for_mode (TYPE_MODE (type), 1);
6033 op0 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op0);
6034 op1 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op1);
6036 *expr_p
6037 = fold_build2_loc (loc, TREE_CODE (*expr_p), TREE_TYPE (*expr_p), op0, op1);
6039 return GS_OK;
6042 /* Gimplify an expression sequence. This function gimplifies each
6043 expression and rewrites the original expression with the last
6044 expression of the sequence in GIMPLE form.
6046 PRE_P points to the list where the side effects for all the
6047 expressions in the sequence will be emitted.
6049 WANT_VALUE is true when the result of the last COMPOUND_EXPR is used. */
6051 static enum gimplify_status
6052 gimplify_compound_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
6054 tree t = *expr_p;
6058 tree *sub_p = &TREE_OPERAND (t, 0);
6060 if (TREE_CODE (*sub_p) == COMPOUND_EXPR)
6061 gimplify_compound_expr (sub_p, pre_p, false);
6062 else
6063 gimplify_stmt (sub_p, pre_p);
6065 t = TREE_OPERAND (t, 1);
6067 while (TREE_CODE (t) == COMPOUND_EXPR);
6069 *expr_p = t;
6070 if (want_value)
6071 return GS_OK;
6072 else
6074 gimplify_stmt (expr_p, pre_p);
6075 return GS_ALL_DONE;
6079 /* Gimplify a SAVE_EXPR node. EXPR_P points to the expression to
6080 gimplify. After gimplification, EXPR_P will point to a new temporary
6081 that holds the original value of the SAVE_EXPR node.
6083 PRE_P points to the list where side effects that must happen before
6084 *EXPR_P should be stored. */
6086 static enum gimplify_status
6087 gimplify_save_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6089 enum gimplify_status ret = GS_ALL_DONE;
6090 tree val;
6092 gcc_assert (TREE_CODE (*expr_p) == SAVE_EXPR);
6093 val = TREE_OPERAND (*expr_p, 0);
6095 /* If the SAVE_EXPR has not been resolved, then evaluate it once. */
6096 if (!SAVE_EXPR_RESOLVED_P (*expr_p))
6098 /* The operand may be a void-valued expression. It is
6099 being executed only for its side-effects. */
6100 if (TREE_TYPE (val) == void_type_node)
6102 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
6103 is_gimple_stmt, fb_none);
6104 val = NULL;
6106 else
6107 /* The temporary may not be an SSA name as later abnormal and EH
6108 control flow may invalidate use/def domination. When in SSA
6109 form then assume there are no such issues and SAVE_EXPRs only
6110 appear via GENERIC foldings. */
6111 val = get_initialized_tmp_var (val, pre_p, post_p,
6112 gimple_in_ssa_p (cfun));
6114 TREE_OPERAND (*expr_p, 0) = val;
6115 SAVE_EXPR_RESOLVED_P (*expr_p) = 1;
6118 *expr_p = val;
6120 return ret;
6123 /* Rewrite the ADDR_EXPR node pointed to by EXPR_P
6125 unary_expr
6126 : ...
6127 | '&' varname
6130 PRE_P points to the list where side effects that must happen before
6131 *EXPR_P should be stored.
6133 POST_P points to the list where side effects that must happen after
6134 *EXPR_P should be stored. */
6136 static enum gimplify_status
6137 gimplify_addr_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6139 tree expr = *expr_p;
6140 tree op0 = TREE_OPERAND (expr, 0);
6141 enum gimplify_status ret;
6142 location_t loc = EXPR_LOCATION (*expr_p);
6144 switch (TREE_CODE (op0))
6146 case INDIRECT_REF:
6147 do_indirect_ref:
6148 /* Check if we are dealing with an expression of the form '&*ptr'.
6149 While the front end folds away '&*ptr' into 'ptr', these
6150 expressions may be generated internally by the compiler (e.g.,
6151 builtins like __builtin_va_end). */
6152 /* Caution: the silent array decomposition semantics we allow for
6153 ADDR_EXPR means we can't always discard the pair. */
6154 /* Gimplification of the ADDR_EXPR operand may drop
6155 cv-qualification conversions, so make sure we add them if
6156 needed. */
6158 tree op00 = TREE_OPERAND (op0, 0);
6159 tree t_expr = TREE_TYPE (expr);
6160 tree t_op00 = TREE_TYPE (op00);
6162 if (!useless_type_conversion_p (t_expr, t_op00))
6163 op00 = fold_convert_loc (loc, TREE_TYPE (expr), op00);
6164 *expr_p = op00;
6165 ret = GS_OK;
6167 break;
6169 case VIEW_CONVERT_EXPR:
6170 /* Take the address of our operand and then convert it to the type of
6171 this ADDR_EXPR.
6173 ??? The interactions of VIEW_CONVERT_EXPR and aliasing is not at
6174 all clear. The impact of this transformation is even less clear. */
6176 /* If the operand is a useless conversion, look through it. Doing so
6177 guarantees that the ADDR_EXPR and its operand will remain of the
6178 same type. */
6179 if (tree_ssa_useless_type_conversion (TREE_OPERAND (op0, 0)))
6180 op0 = TREE_OPERAND (op0, 0);
6182 *expr_p = fold_convert_loc (loc, TREE_TYPE (expr),
6183 build_fold_addr_expr_loc (loc,
6184 TREE_OPERAND (op0, 0)));
6185 ret = GS_OK;
6186 break;
6188 case MEM_REF:
6189 if (integer_zerop (TREE_OPERAND (op0, 1)))
6190 goto do_indirect_ref;
6192 /* fall through */
6194 default:
6195 /* If we see a call to a declared builtin or see its address
6196 being taken (we can unify those cases here) then we can mark
6197 the builtin for implicit generation by GCC. */
6198 if (TREE_CODE (op0) == FUNCTION_DECL
6199 && fndecl_built_in_p (op0, BUILT_IN_NORMAL)
6200 && builtin_decl_declared_p (DECL_FUNCTION_CODE (op0)))
6201 set_builtin_decl_implicit_p (DECL_FUNCTION_CODE (op0), true);
6203 /* We use fb_either here because the C frontend sometimes takes
6204 the address of a call that returns a struct; see
6205 gcc.dg/c99-array-lval-1.c. The gimplifier will correctly make
6206 the implied temporary explicit. */
6208 /* Make the operand addressable. */
6209 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, post_p,
6210 is_gimple_addressable, fb_either);
6211 if (ret == GS_ERROR)
6212 break;
6214 /* Then mark it. Beware that it may not be possible to do so directly
6215 if a temporary has been created by the gimplification. */
6216 prepare_gimple_addressable (&TREE_OPERAND (expr, 0), pre_p);
6218 op0 = TREE_OPERAND (expr, 0);
6220 /* For various reasons, the gimplification of the expression
6221 may have made a new INDIRECT_REF. */
6222 if (TREE_CODE (op0) == INDIRECT_REF
6223 || (TREE_CODE (op0) == MEM_REF
6224 && integer_zerop (TREE_OPERAND (op0, 1))))
6225 goto do_indirect_ref;
6227 mark_addressable (TREE_OPERAND (expr, 0));
6229 /* The FEs may end up building ADDR_EXPRs early on a decl with
6230 an incomplete type. Re-build ADDR_EXPRs in canonical form
6231 here. */
6232 if (!types_compatible_p (TREE_TYPE (op0), TREE_TYPE (TREE_TYPE (expr))))
6233 *expr_p = build_fold_addr_expr (op0);
6235 /* Make sure TREE_CONSTANT and TREE_SIDE_EFFECTS are set properly. */
6236 recompute_tree_invariant_for_addr_expr (*expr_p);
6238 /* If we re-built the ADDR_EXPR add a conversion to the original type
6239 if required. */
6240 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
6241 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
6243 break;
6246 return ret;
6249 /* Gimplify the operands of an ASM_EXPR. Input operands should be a gimple
6250 value; output operands should be a gimple lvalue. */
6252 static enum gimplify_status
6253 gimplify_asm_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6255 tree expr;
6256 int noutputs;
6257 const char **oconstraints;
6258 int i;
6259 tree link;
6260 const char *constraint;
6261 bool allows_mem, allows_reg, is_inout;
6262 enum gimplify_status ret, tret;
6263 gasm *stmt;
6264 vec<tree, va_gc> *inputs;
6265 vec<tree, va_gc> *outputs;
6266 vec<tree, va_gc> *clobbers;
6267 vec<tree, va_gc> *labels;
6268 tree link_next;
6270 expr = *expr_p;
6271 noutputs = list_length (ASM_OUTPUTS (expr));
6272 oconstraints = (const char **) alloca ((noutputs) * sizeof (const char *));
6274 inputs = NULL;
6275 outputs = NULL;
6276 clobbers = NULL;
6277 labels = NULL;
6279 ret = GS_ALL_DONE;
6280 link_next = NULL_TREE;
6281 for (i = 0, link = ASM_OUTPUTS (expr); link; ++i, link = link_next)
6283 bool ok;
6284 size_t constraint_len;
6286 link_next = TREE_CHAIN (link);
6288 oconstraints[i]
6289 = constraint
6290 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
6291 constraint_len = strlen (constraint);
6292 if (constraint_len == 0)
6293 continue;
6295 ok = parse_output_constraint (&constraint, i, 0, 0,
6296 &allows_mem, &allows_reg, &is_inout);
6297 if (!ok)
6299 ret = GS_ERROR;
6300 is_inout = false;
6303 /* If we can't make copies, we can only accept memory.
6304 Similarly for VLAs. */
6305 tree outtype = TREE_TYPE (TREE_VALUE (link));
6306 if (outtype != error_mark_node
6307 && (TREE_ADDRESSABLE (outtype)
6308 || !COMPLETE_TYPE_P (outtype)
6309 || !tree_fits_poly_uint64_p (TYPE_SIZE_UNIT (outtype))))
6311 if (allows_mem)
6312 allows_reg = 0;
6313 else
6315 error ("impossible constraint in %<asm%>");
6316 error ("non-memory output %d must stay in memory", i);
6317 return GS_ERROR;
6321 if (!allows_reg && allows_mem)
6322 mark_addressable (TREE_VALUE (link));
6324 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6325 is_inout ? is_gimple_min_lval : is_gimple_lvalue,
6326 fb_lvalue | fb_mayfail);
6327 if (tret == GS_ERROR)
6329 error ("invalid lvalue in %<asm%> output %d", i);
6330 ret = tret;
6333 /* If the constraint does not allow memory make sure we gimplify
6334 it to a register if it is not already but its base is. This
6335 happens for complex and vector components. */
6336 if (!allows_mem)
6338 tree op = TREE_VALUE (link);
6339 if (! is_gimple_val (op)
6340 && is_gimple_reg_type (TREE_TYPE (op))
6341 && is_gimple_reg (get_base_address (op)))
6343 tree tem = create_tmp_reg (TREE_TYPE (op));
6344 tree ass;
6345 if (is_inout)
6347 ass = build2 (MODIFY_EXPR, TREE_TYPE (tem),
6348 tem, unshare_expr (op));
6349 gimplify_and_add (ass, pre_p);
6351 ass = build2 (MODIFY_EXPR, TREE_TYPE (tem), op, tem);
6352 gimplify_and_add (ass, post_p);
6354 TREE_VALUE (link) = tem;
6355 tret = GS_OK;
6359 vec_safe_push (outputs, link);
6360 TREE_CHAIN (link) = NULL_TREE;
6362 if (is_inout)
6364 /* An input/output operand. To give the optimizers more
6365 flexibility, split it into separate input and output
6366 operands. */
6367 tree input;
6368 /* Buffer big enough to format a 32-bit UINT_MAX into. */
6369 char buf[11];
6371 /* Turn the in/out constraint into an output constraint. */
6372 char *p = xstrdup (constraint);
6373 p[0] = '=';
6374 TREE_VALUE (TREE_PURPOSE (link)) = build_string (constraint_len, p);
6376 /* And add a matching input constraint. */
6377 if (allows_reg)
6379 sprintf (buf, "%u", i);
6381 /* If there are multiple alternatives in the constraint,
6382 handle each of them individually. Those that allow register
6383 will be replaced with operand number, the others will stay
6384 unchanged. */
6385 if (strchr (p, ',') != NULL)
6387 size_t len = 0, buflen = strlen (buf);
6388 char *beg, *end, *str, *dst;
6390 for (beg = p + 1;;)
6392 end = strchr (beg, ',');
6393 if (end == NULL)
6394 end = strchr (beg, '\0');
6395 if ((size_t) (end - beg) < buflen)
6396 len += buflen + 1;
6397 else
6398 len += end - beg + 1;
6399 if (*end)
6400 beg = end + 1;
6401 else
6402 break;
6405 str = (char *) alloca (len);
6406 for (beg = p + 1, dst = str;;)
6408 const char *tem;
6409 bool mem_p, reg_p, inout_p;
6411 end = strchr (beg, ',');
6412 if (end)
6413 *end = '\0';
6414 beg[-1] = '=';
6415 tem = beg - 1;
6416 parse_output_constraint (&tem, i, 0, 0,
6417 &mem_p, &reg_p, &inout_p);
6418 if (dst != str)
6419 *dst++ = ',';
6420 if (reg_p)
6422 memcpy (dst, buf, buflen);
6423 dst += buflen;
6425 else
6427 if (end)
6428 len = end - beg;
6429 else
6430 len = strlen (beg);
6431 memcpy (dst, beg, len);
6432 dst += len;
6434 if (end)
6435 beg = end + 1;
6436 else
6437 break;
6439 *dst = '\0';
6440 input = build_string (dst - str, str);
6442 else
6443 input = build_string (strlen (buf), buf);
6445 else
6446 input = build_string (constraint_len - 1, constraint + 1);
6448 free (p);
6450 input = build_tree_list (build_tree_list (NULL_TREE, input),
6451 unshare_expr (TREE_VALUE (link)));
6452 ASM_INPUTS (expr) = chainon (ASM_INPUTS (expr), input);
6456 link_next = NULL_TREE;
6457 for (link = ASM_INPUTS (expr); link; ++i, link = link_next)
6459 link_next = TREE_CHAIN (link);
6460 constraint = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
6461 parse_input_constraint (&constraint, 0, 0, noutputs, 0,
6462 oconstraints, &allows_mem, &allows_reg);
6464 /* If we can't make copies, we can only accept memory. */
6465 tree intype = TREE_TYPE (TREE_VALUE (link));
6466 if (intype != error_mark_node
6467 && (TREE_ADDRESSABLE (intype)
6468 || !COMPLETE_TYPE_P (intype)
6469 || !tree_fits_poly_uint64_p (TYPE_SIZE_UNIT (intype))))
6471 if (allows_mem)
6472 allows_reg = 0;
6473 else
6475 error ("impossible constraint in %<asm%>");
6476 error ("non-memory input %d must stay in memory", i);
6477 return GS_ERROR;
6481 /* If the operand is a memory input, it should be an lvalue. */
6482 if (!allows_reg && allows_mem)
6484 tree inputv = TREE_VALUE (link);
6485 STRIP_NOPS (inputv);
6486 if (TREE_CODE (inputv) == PREDECREMENT_EXPR
6487 || TREE_CODE (inputv) == PREINCREMENT_EXPR
6488 || TREE_CODE (inputv) == POSTDECREMENT_EXPR
6489 || TREE_CODE (inputv) == POSTINCREMENT_EXPR
6490 || TREE_CODE (inputv) == MODIFY_EXPR)
6491 TREE_VALUE (link) = error_mark_node;
6492 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6493 is_gimple_lvalue, fb_lvalue | fb_mayfail);
6494 if (tret != GS_ERROR)
6496 /* Unlike output operands, memory inputs are not guaranteed
6497 to be lvalues by the FE, and while the expressions are
6498 marked addressable there, if it is e.g. a statement
6499 expression, temporaries in it might not end up being
6500 addressable. They might be already used in the IL and thus
6501 it is too late to make them addressable now though. */
6502 tree x = TREE_VALUE (link);
6503 while (handled_component_p (x))
6504 x = TREE_OPERAND (x, 0);
6505 if (TREE_CODE (x) == MEM_REF
6506 && TREE_CODE (TREE_OPERAND (x, 0)) == ADDR_EXPR)
6507 x = TREE_OPERAND (TREE_OPERAND (x, 0), 0);
6508 if ((VAR_P (x)
6509 || TREE_CODE (x) == PARM_DECL
6510 || TREE_CODE (x) == RESULT_DECL)
6511 && !TREE_ADDRESSABLE (x)
6512 && is_gimple_reg (x))
6514 warning_at (EXPR_LOC_OR_LOC (TREE_VALUE (link),
6515 input_location), 0,
6516 "memory input %d is not directly addressable",
6518 prepare_gimple_addressable (&TREE_VALUE (link), pre_p);
6521 mark_addressable (TREE_VALUE (link));
6522 if (tret == GS_ERROR)
6524 error_at (EXPR_LOC_OR_LOC (TREE_VALUE (link), input_location),
6525 "memory input %d is not directly addressable", i);
6526 ret = tret;
6529 else
6531 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6532 is_gimple_asm_val, fb_rvalue);
6533 if (tret == GS_ERROR)
6534 ret = tret;
6537 TREE_CHAIN (link) = NULL_TREE;
6538 vec_safe_push (inputs, link);
6541 link_next = NULL_TREE;
6542 for (link = ASM_CLOBBERS (expr); link; ++i, link = link_next)
6544 link_next = TREE_CHAIN (link);
6545 TREE_CHAIN (link) = NULL_TREE;
6546 vec_safe_push (clobbers, link);
6549 link_next = NULL_TREE;
6550 for (link = ASM_LABELS (expr); link; ++i, link = link_next)
6552 link_next = TREE_CHAIN (link);
6553 TREE_CHAIN (link) = NULL_TREE;
6554 vec_safe_push (labels, link);
6557 /* Do not add ASMs with errors to the gimple IL stream. */
6558 if (ret != GS_ERROR)
6560 stmt = gimple_build_asm_vec (TREE_STRING_POINTER (ASM_STRING (expr)),
6561 inputs, outputs, clobbers, labels);
6563 gimple_asm_set_volatile (stmt, ASM_VOLATILE_P (expr) || noutputs == 0);
6564 gimple_asm_set_input (stmt, ASM_INPUT_P (expr));
6565 gimple_asm_set_inline (stmt, ASM_INLINE_P (expr));
6567 gimplify_seq_add_stmt (pre_p, stmt);
6570 return ret;
6573 /* Gimplify a CLEANUP_POINT_EXPR. Currently this works by adding
6574 GIMPLE_WITH_CLEANUP_EXPRs to the prequeue as we encounter cleanups while
6575 gimplifying the body, and converting them to TRY_FINALLY_EXPRs when we
6576 return to this function.
6578 FIXME should we complexify the prequeue handling instead? Or use flags
6579 for all the cleanups and let the optimizer tighten them up? The current
6580 code seems pretty fragile; it will break on a cleanup within any
6581 non-conditional nesting. But any such nesting would be broken, anyway;
6582 we can't write a TRY_FINALLY_EXPR that starts inside a nesting construct
6583 and continues out of it. We can do that at the RTL level, though, so
6584 having an optimizer to tighten up try/finally regions would be a Good
6585 Thing. */
6587 static enum gimplify_status
6588 gimplify_cleanup_point_expr (tree *expr_p, gimple_seq *pre_p)
6590 gimple_stmt_iterator iter;
6591 gimple_seq body_sequence = NULL;
6593 tree temp = voidify_wrapper_expr (*expr_p, NULL);
6595 /* We only care about the number of conditions between the innermost
6596 CLEANUP_POINT_EXPR and the cleanup. So save and reset the count and
6597 any cleanups collected outside the CLEANUP_POINT_EXPR. */
6598 int old_conds = gimplify_ctxp->conditions;
6599 gimple_seq old_cleanups = gimplify_ctxp->conditional_cleanups;
6600 bool old_in_cleanup_point_expr = gimplify_ctxp->in_cleanup_point_expr;
6601 gimplify_ctxp->conditions = 0;
6602 gimplify_ctxp->conditional_cleanups = NULL;
6603 gimplify_ctxp->in_cleanup_point_expr = true;
6605 gimplify_stmt (&TREE_OPERAND (*expr_p, 0), &body_sequence);
6607 gimplify_ctxp->conditions = old_conds;
6608 gimplify_ctxp->conditional_cleanups = old_cleanups;
6609 gimplify_ctxp->in_cleanup_point_expr = old_in_cleanup_point_expr;
6611 for (iter = gsi_start (body_sequence); !gsi_end_p (iter); )
6613 gimple *wce = gsi_stmt (iter);
6615 if (gimple_code (wce) == GIMPLE_WITH_CLEANUP_EXPR)
6617 if (gsi_one_before_end_p (iter))
6619 /* Note that gsi_insert_seq_before and gsi_remove do not
6620 scan operands, unlike some other sequence mutators. */
6621 if (!gimple_wce_cleanup_eh_only (wce))
6622 gsi_insert_seq_before_without_update (&iter,
6623 gimple_wce_cleanup (wce),
6624 GSI_SAME_STMT);
6625 gsi_remove (&iter, true);
6626 break;
6628 else
6630 gtry *gtry;
6631 gimple_seq seq;
6632 enum gimple_try_flags kind;
6634 if (gimple_wce_cleanup_eh_only (wce))
6635 kind = GIMPLE_TRY_CATCH;
6636 else
6637 kind = GIMPLE_TRY_FINALLY;
6638 seq = gsi_split_seq_after (iter);
6640 gtry = gimple_build_try (seq, gimple_wce_cleanup (wce), kind);
6641 /* Do not use gsi_replace here, as it may scan operands.
6642 We want to do a simple structural modification only. */
6643 gsi_set_stmt (&iter, gtry);
6644 iter = gsi_start (gtry->eval);
6647 else
6648 gsi_next (&iter);
6651 gimplify_seq_add_seq (pre_p, body_sequence);
6652 if (temp)
6654 *expr_p = temp;
6655 return GS_OK;
6657 else
6659 *expr_p = NULL;
6660 return GS_ALL_DONE;
6664 /* Insert a cleanup marker for gimplify_cleanup_point_expr. CLEANUP
6665 is the cleanup action required. EH_ONLY is true if the cleanup should
6666 only be executed if an exception is thrown, not on normal exit.
6667 If FORCE_UNCOND is true perform the cleanup unconditionally; this is
6668 only valid for clobbers. */
6670 static void
6671 gimple_push_cleanup (tree var, tree cleanup, bool eh_only, gimple_seq *pre_p,
6672 bool force_uncond = false)
6674 gimple *wce;
6675 gimple_seq cleanup_stmts = NULL;
6677 /* Errors can result in improperly nested cleanups. Which results in
6678 confusion when trying to resolve the GIMPLE_WITH_CLEANUP_EXPR. */
6679 if (seen_error ())
6680 return;
6682 if (gimple_conditional_context ())
6684 /* If we're in a conditional context, this is more complex. We only
6685 want to run the cleanup if we actually ran the initialization that
6686 necessitates it, but we want to run it after the end of the
6687 conditional context. So we wrap the try/finally around the
6688 condition and use a flag to determine whether or not to actually
6689 run the destructor. Thus
6691 test ? f(A()) : 0
6693 becomes (approximately)
6695 flag = 0;
6696 try {
6697 if (test) { A::A(temp); flag = 1; val = f(temp); }
6698 else { val = 0; }
6699 } finally {
6700 if (flag) A::~A(temp);
6704 if (force_uncond)
6706 gimplify_stmt (&cleanup, &cleanup_stmts);
6707 wce = gimple_build_wce (cleanup_stmts);
6708 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, wce);
6710 else
6712 tree flag = create_tmp_var (boolean_type_node, "cleanup");
6713 gassign *ffalse = gimple_build_assign (flag, boolean_false_node);
6714 gassign *ftrue = gimple_build_assign (flag, boolean_true_node);
6716 cleanup = build3 (COND_EXPR, void_type_node, flag, cleanup, NULL);
6717 gimplify_stmt (&cleanup, &cleanup_stmts);
6718 wce = gimple_build_wce (cleanup_stmts);
6720 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, ffalse);
6721 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, wce);
6722 gimplify_seq_add_stmt (pre_p, ftrue);
6724 /* Because of this manipulation, and the EH edges that jump
6725 threading cannot redirect, the temporary (VAR) will appear
6726 to be used uninitialized. Don't warn. */
6727 TREE_NO_WARNING (var) = 1;
6730 else
6732 gimplify_stmt (&cleanup, &cleanup_stmts);
6733 wce = gimple_build_wce (cleanup_stmts);
6734 gimple_wce_set_cleanup_eh_only (wce, eh_only);
6735 gimplify_seq_add_stmt (pre_p, wce);
6739 /* Gimplify a TARGET_EXPR which doesn't appear on the rhs of an INIT_EXPR. */
6741 static enum gimplify_status
6742 gimplify_target_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6744 tree targ = *expr_p;
6745 tree temp = TARGET_EXPR_SLOT (targ);
6746 tree init = TARGET_EXPR_INITIAL (targ);
6747 enum gimplify_status ret;
6749 bool unpoison_empty_seq = false;
6750 gimple_stmt_iterator unpoison_it;
6752 if (init)
6754 tree cleanup = NULL_TREE;
6756 /* TARGET_EXPR temps aren't part of the enclosing block, so add it
6757 to the temps list. Handle also variable length TARGET_EXPRs. */
6758 if (!poly_int_tree_p (DECL_SIZE (temp)))
6760 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (temp)))
6761 gimplify_type_sizes (TREE_TYPE (temp), pre_p);
6762 gimplify_vla_decl (temp, pre_p);
6764 else
6766 /* Save location where we need to place unpoisoning. It's possible
6767 that a variable will be converted to needs_to_live_in_memory. */
6768 unpoison_it = gsi_last (*pre_p);
6769 unpoison_empty_seq = gsi_end_p (unpoison_it);
6771 gimple_add_tmp_var (temp);
6774 /* If TARGET_EXPR_INITIAL is void, then the mere evaluation of the
6775 expression is supposed to initialize the slot. */
6776 if (VOID_TYPE_P (TREE_TYPE (init)))
6777 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
6778 else
6780 tree init_expr = build2 (INIT_EXPR, void_type_node, temp, init);
6781 init = init_expr;
6782 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
6783 init = NULL;
6784 ggc_free (init_expr);
6786 if (ret == GS_ERROR)
6788 /* PR c++/28266 Make sure this is expanded only once. */
6789 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
6790 return GS_ERROR;
6792 if (init)
6793 gimplify_and_add (init, pre_p);
6795 /* If needed, push the cleanup for the temp. */
6796 if (TARGET_EXPR_CLEANUP (targ))
6798 if (CLEANUP_EH_ONLY (targ))
6799 gimple_push_cleanup (temp, TARGET_EXPR_CLEANUP (targ),
6800 CLEANUP_EH_ONLY (targ), pre_p);
6801 else
6802 cleanup = TARGET_EXPR_CLEANUP (targ);
6805 /* Add a clobber for the temporary going out of scope, like
6806 gimplify_bind_expr. */
6807 if (gimplify_ctxp->in_cleanup_point_expr
6808 && needs_to_live_in_memory (temp))
6810 if (flag_stack_reuse == SR_ALL)
6812 tree clobber = build_clobber (TREE_TYPE (temp));
6813 clobber = build2 (MODIFY_EXPR, TREE_TYPE (temp), temp, clobber);
6814 gimple_push_cleanup (temp, clobber, false, pre_p, true);
6816 if (asan_poisoned_variables
6817 && DECL_ALIGN (temp) <= MAX_SUPPORTED_STACK_ALIGNMENT
6818 && !TREE_STATIC (temp)
6819 && dbg_cnt (asan_use_after_scope)
6820 && !gimplify_omp_ctxp)
6822 tree asan_cleanup = build_asan_poison_call_expr (temp);
6823 if (asan_cleanup)
6825 if (unpoison_empty_seq)
6826 unpoison_it = gsi_start (*pre_p);
6828 asan_poison_variable (temp, false, &unpoison_it,
6829 unpoison_empty_seq);
6830 gimple_push_cleanup (temp, asan_cleanup, false, pre_p);
6834 if (cleanup)
6835 gimple_push_cleanup (temp, cleanup, false, pre_p);
6837 /* Only expand this once. */
6838 TREE_OPERAND (targ, 3) = init;
6839 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
6841 else
6842 /* We should have expanded this before. */
6843 gcc_assert (DECL_SEEN_IN_BIND_EXPR_P (temp));
6845 *expr_p = temp;
6846 return GS_OK;
6849 /* Gimplification of expression trees. */
6851 /* Gimplify an expression which appears at statement context. The
6852 corresponding GIMPLE statements are added to *SEQ_P. If *SEQ_P is
6853 NULL, a new sequence is allocated.
6855 Return true if we actually added a statement to the queue. */
6857 bool
6858 gimplify_stmt (tree *stmt_p, gimple_seq *seq_p)
6860 gimple_seq_node last;
6862 last = gimple_seq_last (*seq_p);
6863 gimplify_expr (stmt_p, seq_p, NULL, is_gimple_stmt, fb_none);
6864 return last != gimple_seq_last (*seq_p);
6867 /* Add FIRSTPRIVATE entries for DECL in the OpenMP the surrounding parallels
6868 to CTX. If entries already exist, force them to be some flavor of private.
6869 If there is no enclosing parallel, do nothing. */
6871 void
6872 omp_firstprivatize_variable (struct gimplify_omp_ctx *ctx, tree decl)
6874 splay_tree_node n;
6876 if (decl == NULL || !DECL_P (decl) || ctx->region_type == ORT_NONE)
6877 return;
6881 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
6882 if (n != NULL)
6884 if (n->value & GOVD_SHARED)
6885 n->value = GOVD_FIRSTPRIVATE | (n->value & GOVD_SEEN);
6886 else if (n->value & GOVD_MAP)
6887 n->value |= GOVD_MAP_TO_ONLY;
6888 else
6889 return;
6891 else if ((ctx->region_type & ORT_TARGET) != 0)
6893 if (ctx->defaultmap[GDMK_SCALAR] & GOVD_FIRSTPRIVATE)
6894 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
6895 else
6896 omp_add_variable (ctx, decl, GOVD_MAP | GOVD_MAP_TO_ONLY);
6898 else if (ctx->region_type != ORT_WORKSHARE
6899 && ctx->region_type != ORT_TASKGROUP
6900 && ctx->region_type != ORT_SIMD
6901 && ctx->region_type != ORT_ACC
6902 && !(ctx->region_type & ORT_TARGET_DATA))
6903 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
6905 ctx = ctx->outer_context;
6907 while (ctx);
6910 /* Similarly for each of the type sizes of TYPE. */
6912 static void
6913 omp_firstprivatize_type_sizes (struct gimplify_omp_ctx *ctx, tree type)
6915 if (type == NULL || type == error_mark_node)
6916 return;
6917 type = TYPE_MAIN_VARIANT (type);
6919 if (ctx->privatized_types->add (type))
6920 return;
6922 switch (TREE_CODE (type))
6924 case INTEGER_TYPE:
6925 case ENUMERAL_TYPE:
6926 case BOOLEAN_TYPE:
6927 case REAL_TYPE:
6928 case FIXED_POINT_TYPE:
6929 omp_firstprivatize_variable (ctx, TYPE_MIN_VALUE (type));
6930 omp_firstprivatize_variable (ctx, TYPE_MAX_VALUE (type));
6931 break;
6933 case ARRAY_TYPE:
6934 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
6935 omp_firstprivatize_type_sizes (ctx, TYPE_DOMAIN (type));
6936 break;
6938 case RECORD_TYPE:
6939 case UNION_TYPE:
6940 case QUAL_UNION_TYPE:
6942 tree field;
6943 for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
6944 if (TREE_CODE (field) == FIELD_DECL)
6946 omp_firstprivatize_variable (ctx, DECL_FIELD_OFFSET (field));
6947 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (field));
6950 break;
6952 case POINTER_TYPE:
6953 case REFERENCE_TYPE:
6954 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
6955 break;
6957 default:
6958 break;
6961 omp_firstprivatize_variable (ctx, TYPE_SIZE (type));
6962 omp_firstprivatize_variable (ctx, TYPE_SIZE_UNIT (type));
6963 lang_hooks.types.omp_firstprivatize_type_sizes (ctx, type);
6966 /* Add an entry for DECL in the OMP context CTX with FLAGS. */
6968 static void
6969 omp_add_variable (struct gimplify_omp_ctx *ctx, tree decl, unsigned int flags)
6971 splay_tree_node n;
6972 unsigned int nflags;
6973 tree t;
6975 if (error_operand_p (decl) || ctx->region_type == ORT_NONE)
6976 return;
6978 /* Never elide decls whose type has TREE_ADDRESSABLE set. This means
6979 there are constructors involved somewhere. Exception is a shared clause,
6980 there is nothing privatized in that case. */
6981 if ((flags & GOVD_SHARED) == 0
6982 && (TREE_ADDRESSABLE (TREE_TYPE (decl))
6983 || TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (decl))))
6984 flags |= GOVD_SEEN;
6986 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
6987 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
6989 /* We shouldn't be re-adding the decl with the same data
6990 sharing class. */
6991 gcc_assert ((n->value & GOVD_DATA_SHARE_CLASS & flags) == 0);
6992 nflags = n->value | flags;
6993 /* The only combination of data sharing classes we should see is
6994 FIRSTPRIVATE and LASTPRIVATE. However, OpenACC permits
6995 reduction variables to be used in data sharing clauses. */
6996 gcc_assert ((ctx->region_type & ORT_ACC) != 0
6997 || ((nflags & GOVD_DATA_SHARE_CLASS)
6998 == (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE))
6999 || (flags & GOVD_DATA_SHARE_CLASS) == 0);
7000 n->value = nflags;
7001 return;
7004 /* When adding a variable-sized variable, we have to handle all sorts
7005 of additional bits of data: the pointer replacement variable, and
7006 the parameters of the type. */
7007 if (DECL_SIZE (decl) && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
7009 /* Add the pointer replacement variable as PRIVATE if the variable
7010 replacement is private, else FIRSTPRIVATE since we'll need the
7011 address of the original variable either for SHARED, or for the
7012 copy into or out of the context. */
7013 if (!(flags & GOVD_LOCAL) && ctx->region_type != ORT_TASKGROUP)
7015 if (flags & GOVD_MAP)
7016 nflags = GOVD_MAP | GOVD_MAP_TO_ONLY | GOVD_EXPLICIT;
7017 else if (flags & GOVD_PRIVATE)
7018 nflags = GOVD_PRIVATE;
7019 else if (((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0
7020 && (flags & GOVD_FIRSTPRIVATE))
7021 || (ctx->region_type == ORT_TARGET_DATA
7022 && (flags & GOVD_DATA_SHARE_CLASS) == 0))
7023 nflags = GOVD_PRIVATE | GOVD_EXPLICIT;
7024 else
7025 nflags = GOVD_FIRSTPRIVATE;
7026 nflags |= flags & GOVD_SEEN;
7027 t = DECL_VALUE_EXPR (decl);
7028 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
7029 t = TREE_OPERAND (t, 0);
7030 gcc_assert (DECL_P (t));
7031 omp_add_variable (ctx, t, nflags);
7034 /* Add all of the variable and type parameters (which should have
7035 been gimplified to a formal temporary) as FIRSTPRIVATE. */
7036 omp_firstprivatize_variable (ctx, DECL_SIZE_UNIT (decl));
7037 omp_firstprivatize_variable (ctx, DECL_SIZE (decl));
7038 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
7040 /* The variable-sized variable itself is never SHARED, only some form
7041 of PRIVATE. The sharing would take place via the pointer variable
7042 which we remapped above. */
7043 if (flags & GOVD_SHARED)
7044 flags = GOVD_SHARED | GOVD_DEBUG_PRIVATE
7045 | (flags & (GOVD_SEEN | GOVD_EXPLICIT));
7047 /* We're going to make use of the TYPE_SIZE_UNIT at least in the
7048 alloca statement we generate for the variable, so make sure it
7049 is available. This isn't automatically needed for the SHARED
7050 case, since we won't be allocating local storage then.
7051 For local variables TYPE_SIZE_UNIT might not be gimplified yet,
7052 in this case omp_notice_variable will be called later
7053 on when it is gimplified. */
7054 else if (! (flags & (GOVD_LOCAL | GOVD_MAP))
7055 && DECL_P (TYPE_SIZE_UNIT (TREE_TYPE (decl))))
7056 omp_notice_variable (ctx, TYPE_SIZE_UNIT (TREE_TYPE (decl)), true);
7058 else if ((flags & (GOVD_MAP | GOVD_LOCAL)) == 0
7059 && lang_hooks.decls.omp_privatize_by_reference (decl))
7061 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
7063 /* Similar to the direct variable sized case above, we'll need the
7064 size of references being privatized. */
7065 if ((flags & GOVD_SHARED) == 0)
7067 t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
7068 if (t && DECL_P (t))
7069 omp_notice_variable (ctx, t, true);
7073 if (n != NULL)
7074 n->value |= flags;
7075 else
7076 splay_tree_insert (ctx->variables, (splay_tree_key)decl, flags);
7078 /* For reductions clauses in OpenACC loop directives, by default create a
7079 copy clause on the enclosing parallel construct for carrying back the
7080 results. */
7081 if (ctx->region_type == ORT_ACC && (flags & GOVD_REDUCTION))
7083 struct gimplify_omp_ctx *outer_ctx = ctx->outer_context;
7084 while (outer_ctx)
7086 n = splay_tree_lookup (outer_ctx->variables, (splay_tree_key)decl);
7087 if (n != NULL)
7089 /* Ignore local variables and explicitly declared clauses. */
7090 if (n->value & (GOVD_LOCAL | GOVD_EXPLICIT))
7091 break;
7092 else if (outer_ctx->region_type == ORT_ACC_KERNELS)
7094 /* According to the OpenACC spec, such a reduction variable
7095 should already have a copy map on a kernels construct,
7096 verify that here. */
7097 gcc_assert (!(n->value & GOVD_FIRSTPRIVATE)
7098 && (n->value & GOVD_MAP));
7100 else if (outer_ctx->region_type == ORT_ACC_PARALLEL)
7102 /* Remove firstprivate and make it a copy map. */
7103 n->value &= ~GOVD_FIRSTPRIVATE;
7104 n->value |= GOVD_MAP;
7107 else if (outer_ctx->region_type == ORT_ACC_PARALLEL)
7109 splay_tree_insert (outer_ctx->variables, (splay_tree_key)decl,
7110 GOVD_MAP | GOVD_SEEN);
7111 break;
7113 outer_ctx = outer_ctx->outer_context;
7118 /* Notice a threadprivate variable DECL used in OMP context CTX.
7119 This just prints out diagnostics about threadprivate variable uses
7120 in untied tasks. If DECL2 is non-NULL, prevent this warning
7121 on that variable. */
7123 static bool
7124 omp_notice_threadprivate_variable (struct gimplify_omp_ctx *ctx, tree decl,
7125 tree decl2)
7127 splay_tree_node n;
7128 struct gimplify_omp_ctx *octx;
7130 for (octx = ctx; octx; octx = octx->outer_context)
7131 if ((octx->region_type & ORT_TARGET) != 0
7132 || octx->order_concurrent)
7134 n = splay_tree_lookup (octx->variables, (splay_tree_key)decl);
7135 if (n == NULL)
7137 if (octx->order_concurrent)
7139 error ("threadprivate variable %qE used in a region with"
7140 " %<order(concurrent)%> clause", DECL_NAME (decl));
7141 inform (octx->location, "enclosing region");
7143 else
7145 error ("threadprivate variable %qE used in target region",
7146 DECL_NAME (decl));
7147 inform (octx->location, "enclosing target region");
7149 splay_tree_insert (octx->variables, (splay_tree_key)decl, 0);
7151 if (decl2)
7152 splay_tree_insert (octx->variables, (splay_tree_key)decl2, 0);
7155 if (ctx->region_type != ORT_UNTIED_TASK)
7156 return false;
7157 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7158 if (n == NULL)
7160 error ("threadprivate variable %qE used in untied task",
7161 DECL_NAME (decl));
7162 inform (ctx->location, "enclosing task");
7163 splay_tree_insert (ctx->variables, (splay_tree_key)decl, 0);
7165 if (decl2)
7166 splay_tree_insert (ctx->variables, (splay_tree_key)decl2, 0);
7167 return false;
7170 /* Return true if global var DECL is device resident. */
7172 static bool
7173 device_resident_p (tree decl)
7175 tree attr = lookup_attribute ("oacc declare target", DECL_ATTRIBUTES (decl));
7177 if (!attr)
7178 return false;
7180 for (tree t = TREE_VALUE (attr); t; t = TREE_PURPOSE (t))
7182 tree c = TREE_VALUE (t);
7183 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_DEVICE_RESIDENT)
7184 return true;
7187 return false;
7190 /* Return true if DECL has an ACC DECLARE attribute. */
7192 static bool
7193 is_oacc_declared (tree decl)
7195 tree t = TREE_CODE (decl) == MEM_REF ? TREE_OPERAND (decl, 0) : decl;
7196 tree declared = lookup_attribute ("oacc declare target", DECL_ATTRIBUTES (t));
7197 return declared != NULL_TREE;
7200 /* Determine outer default flags for DECL mentioned in an OMP region
7201 but not declared in an enclosing clause.
7203 ??? Some compiler-generated variables (like SAVE_EXPRs) could be
7204 remapped firstprivate instead of shared. To some extent this is
7205 addressed in omp_firstprivatize_type_sizes, but not
7206 effectively. */
7208 static unsigned
7209 omp_default_clause (struct gimplify_omp_ctx *ctx, tree decl,
7210 bool in_code, unsigned flags)
7212 enum omp_clause_default_kind default_kind = ctx->default_kind;
7213 enum omp_clause_default_kind kind;
7215 kind = lang_hooks.decls.omp_predetermined_sharing (decl);
7216 if (ctx->region_type & ORT_TASK)
7218 tree detach_clause = omp_find_clause (ctx->clauses, OMP_CLAUSE_DETACH);
7220 /* The event-handle specified by a detach clause should always be firstprivate,
7221 regardless of the current default. */
7222 if (detach_clause && OMP_CLAUSE_DECL (detach_clause) == decl)
7223 kind = OMP_CLAUSE_DEFAULT_FIRSTPRIVATE;
7225 if (kind != OMP_CLAUSE_DEFAULT_UNSPECIFIED)
7226 default_kind = kind;
7227 else if (VAR_P (decl) && TREE_STATIC (decl) && DECL_IN_CONSTANT_POOL (decl))
7228 default_kind = OMP_CLAUSE_DEFAULT_SHARED;
7230 switch (default_kind)
7232 case OMP_CLAUSE_DEFAULT_NONE:
7234 const char *rtype;
7236 if (ctx->region_type & ORT_PARALLEL)
7237 rtype = "parallel";
7238 else if ((ctx->region_type & ORT_TASKLOOP) == ORT_TASKLOOP)
7239 rtype = "taskloop";
7240 else if (ctx->region_type & ORT_TASK)
7241 rtype = "task";
7242 else if (ctx->region_type & ORT_TEAMS)
7243 rtype = "teams";
7244 else
7245 gcc_unreachable ();
7247 error ("%qE not specified in enclosing %qs",
7248 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)), rtype);
7249 inform (ctx->location, "enclosing %qs", rtype);
7251 /* FALLTHRU */
7252 case OMP_CLAUSE_DEFAULT_SHARED:
7253 flags |= GOVD_SHARED;
7254 break;
7255 case OMP_CLAUSE_DEFAULT_PRIVATE:
7256 flags |= GOVD_PRIVATE;
7257 break;
7258 case OMP_CLAUSE_DEFAULT_FIRSTPRIVATE:
7259 flags |= GOVD_FIRSTPRIVATE;
7260 break;
7261 case OMP_CLAUSE_DEFAULT_UNSPECIFIED:
7262 /* decl will be either GOVD_FIRSTPRIVATE or GOVD_SHARED. */
7263 gcc_assert ((ctx->region_type & ORT_TASK) != 0);
7264 if (struct gimplify_omp_ctx *octx = ctx->outer_context)
7266 omp_notice_variable (octx, decl, in_code);
7267 for (; octx; octx = octx->outer_context)
7269 splay_tree_node n2;
7271 n2 = splay_tree_lookup (octx->variables, (splay_tree_key) decl);
7272 if ((octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)) != 0
7273 && (n2 == NULL || (n2->value & GOVD_DATA_SHARE_CLASS) == 0))
7274 continue;
7275 if (n2 && (n2->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED)
7277 flags |= GOVD_FIRSTPRIVATE;
7278 goto found_outer;
7280 if ((octx->region_type & (ORT_PARALLEL | ORT_TEAMS)) != 0)
7282 flags |= GOVD_SHARED;
7283 goto found_outer;
7288 if (TREE_CODE (decl) == PARM_DECL
7289 || (!is_global_var (decl)
7290 && DECL_CONTEXT (decl) == current_function_decl))
7291 flags |= GOVD_FIRSTPRIVATE;
7292 else
7293 flags |= GOVD_SHARED;
7294 found_outer:
7295 break;
7297 default:
7298 gcc_unreachable ();
7301 return flags;
7305 /* Determine outer default flags for DECL mentioned in an OACC region
7306 but not declared in an enclosing clause. */
7308 static unsigned
7309 oacc_default_clause (struct gimplify_omp_ctx *ctx, tree decl, unsigned flags)
7311 const char *rkind;
7312 bool on_device = false;
7313 bool is_private = false;
7314 bool declared = is_oacc_declared (decl);
7315 tree type = TREE_TYPE (decl);
7317 if (lang_hooks.decls.omp_privatize_by_reference (decl))
7318 type = TREE_TYPE (type);
7320 /* For Fortran COMMON blocks, only used variables in those blocks are
7321 transfered and remapped. The block itself will have a private clause to
7322 avoid transfering the data twice.
7323 The hook evaluates to false by default. For a variable in Fortran's COMMON
7324 or EQUIVALENCE block, returns 'true' (as we have shared=false) - as only
7325 the variables in such a COMMON/EQUIVALENCE block shall be privatized not
7326 the whole block. For C++ and Fortran, it can also be true under certain
7327 other conditions, if DECL_HAS_VALUE_EXPR. */
7328 if (RECORD_OR_UNION_TYPE_P (type))
7329 is_private = lang_hooks.decls.omp_disregard_value_expr (decl, false);
7331 if ((ctx->region_type & (ORT_ACC_PARALLEL | ORT_ACC_KERNELS)) != 0
7332 && is_global_var (decl)
7333 && device_resident_p (decl)
7334 && !is_private)
7336 on_device = true;
7337 flags |= GOVD_MAP_TO_ONLY;
7340 switch (ctx->region_type)
7342 case ORT_ACC_KERNELS:
7343 rkind = "kernels";
7345 if (is_private)
7346 flags |= GOVD_FIRSTPRIVATE;
7347 else if (AGGREGATE_TYPE_P (type))
7349 /* Aggregates default to 'present_or_copy', or 'present'. */
7350 if (ctx->default_kind != OMP_CLAUSE_DEFAULT_PRESENT)
7351 flags |= GOVD_MAP;
7352 else
7353 flags |= GOVD_MAP | GOVD_MAP_FORCE_PRESENT;
7355 else
7356 /* Scalars default to 'copy'. */
7357 flags |= GOVD_MAP | GOVD_MAP_FORCE;
7359 break;
7361 case ORT_ACC_PARALLEL:
7362 case ORT_ACC_SERIAL:
7363 rkind = ctx->region_type == ORT_ACC_PARALLEL ? "parallel" : "serial";
7365 if (is_private)
7366 flags |= GOVD_FIRSTPRIVATE;
7367 else if (on_device || declared)
7368 flags |= GOVD_MAP;
7369 else if (AGGREGATE_TYPE_P (type))
7371 /* Aggregates default to 'present_or_copy', or 'present'. */
7372 if (ctx->default_kind != OMP_CLAUSE_DEFAULT_PRESENT)
7373 flags |= GOVD_MAP;
7374 else
7375 flags |= GOVD_MAP | GOVD_MAP_FORCE_PRESENT;
7377 else
7378 /* Scalars default to 'firstprivate'. */
7379 flags |= GOVD_FIRSTPRIVATE;
7381 break;
7383 default:
7384 gcc_unreachable ();
7387 if (DECL_ARTIFICIAL (decl))
7388 ; /* We can get compiler-generated decls, and should not complain
7389 about them. */
7390 else if (ctx->default_kind == OMP_CLAUSE_DEFAULT_NONE)
7392 error ("%qE not specified in enclosing OpenACC %qs construct",
7393 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)), rkind);
7394 inform (ctx->location, "enclosing OpenACC %qs construct", rkind);
7396 else if (ctx->default_kind == OMP_CLAUSE_DEFAULT_PRESENT)
7397 ; /* Handled above. */
7398 else
7399 gcc_checking_assert (ctx->default_kind == OMP_CLAUSE_DEFAULT_SHARED);
7401 return flags;
7404 /* Record the fact that DECL was used within the OMP context CTX.
7405 IN_CODE is true when real code uses DECL, and false when we should
7406 merely emit default(none) errors. Return true if DECL is going to
7407 be remapped and thus DECL shouldn't be gimplified into its
7408 DECL_VALUE_EXPR (if any). */
7410 static bool
7411 omp_notice_variable (struct gimplify_omp_ctx *ctx, tree decl, bool in_code)
7413 splay_tree_node n;
7414 unsigned flags = in_code ? GOVD_SEEN : 0;
7415 bool ret = false, shared;
7417 if (error_operand_p (decl))
7418 return false;
7420 if (ctx->region_type == ORT_NONE)
7421 return lang_hooks.decls.omp_disregard_value_expr (decl, false);
7423 if (is_global_var (decl))
7425 /* Threadprivate variables are predetermined. */
7426 if (DECL_THREAD_LOCAL_P (decl))
7427 return omp_notice_threadprivate_variable (ctx, decl, NULL_TREE);
7429 if (DECL_HAS_VALUE_EXPR_P (decl))
7431 if (ctx->region_type & ORT_ACC)
7432 /* For OpenACC, defer expansion of value to avoid transfering
7433 privatized common block data instead of im-/explicitly transfered
7434 variables which are in common blocks. */
7436 else
7438 tree value = get_base_address (DECL_VALUE_EXPR (decl));
7440 if (value && DECL_P (value) && DECL_THREAD_LOCAL_P (value))
7441 return omp_notice_threadprivate_variable (ctx, decl, value);
7445 if (gimplify_omp_ctxp->outer_context == NULL
7446 && VAR_P (decl)
7447 && oacc_get_fn_attrib (current_function_decl))
7449 location_t loc = DECL_SOURCE_LOCATION (decl);
7451 if (lookup_attribute ("omp declare target link",
7452 DECL_ATTRIBUTES (decl)))
7454 error_at (loc,
7455 "%qE with %<link%> clause used in %<routine%> function",
7456 DECL_NAME (decl));
7457 return false;
7459 else if (!lookup_attribute ("omp declare target",
7460 DECL_ATTRIBUTES (decl)))
7462 error_at (loc,
7463 "%qE requires a %<declare%> directive for use "
7464 "in a %<routine%> function", DECL_NAME (decl));
7465 return false;
7470 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7471 if ((ctx->region_type & ORT_TARGET) != 0)
7473 if (ctx->region_type & ORT_ACC)
7474 /* For OpenACC, as remarked above, defer expansion. */
7475 shared = false;
7476 else
7477 shared = true;
7479 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
7480 if (n == NULL)
7482 unsigned nflags = flags;
7483 if ((ctx->region_type & ORT_ACC) == 0)
7485 bool is_declare_target = false;
7486 if (is_global_var (decl)
7487 && varpool_node::get_create (decl)->offloadable)
7489 struct gimplify_omp_ctx *octx;
7490 for (octx = ctx->outer_context;
7491 octx; octx = octx->outer_context)
7493 n = splay_tree_lookup (octx->variables,
7494 (splay_tree_key)decl);
7495 if (n
7496 && (n->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED
7497 && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
7498 break;
7500 is_declare_target = octx == NULL;
7502 if (!is_declare_target)
7504 int gdmk;
7505 enum omp_clause_defaultmap_kind kind;
7506 if (TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE
7507 || (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
7508 && (TREE_CODE (TREE_TYPE (TREE_TYPE (decl)))
7509 == POINTER_TYPE)))
7510 gdmk = GDMK_POINTER;
7511 else if (lang_hooks.decls.omp_scalar_p (decl))
7512 gdmk = GDMK_SCALAR;
7513 else
7514 gdmk = GDMK_AGGREGATE;
7515 kind = lang_hooks.decls.omp_predetermined_mapping (decl);
7516 if (kind != OMP_CLAUSE_DEFAULTMAP_CATEGORY_UNSPECIFIED)
7518 if (kind == OMP_CLAUSE_DEFAULTMAP_FIRSTPRIVATE)
7519 nflags |= GOVD_FIRSTPRIVATE;
7520 else if (kind == OMP_CLAUSE_DEFAULTMAP_TO)
7521 nflags |= GOVD_MAP | GOVD_MAP_TO_ONLY;
7522 else
7523 gcc_unreachable ();
7525 else if (ctx->defaultmap[gdmk] == 0)
7527 tree d = lang_hooks.decls.omp_report_decl (decl);
7528 error ("%qE not specified in enclosing %<target%>",
7529 DECL_NAME (d));
7530 inform (ctx->location, "enclosing %<target%>");
7532 else if (ctx->defaultmap[gdmk]
7533 & (GOVD_MAP_0LEN_ARRAY | GOVD_FIRSTPRIVATE))
7534 nflags |= ctx->defaultmap[gdmk];
7535 else
7537 gcc_assert (ctx->defaultmap[gdmk] & GOVD_MAP);
7538 nflags |= ctx->defaultmap[gdmk] & ~GOVD_MAP;
7543 struct gimplify_omp_ctx *octx = ctx->outer_context;
7544 if ((ctx->region_type & ORT_ACC) && octx)
7546 /* Look in outer OpenACC contexts, to see if there's a
7547 data attribute for this variable. */
7548 omp_notice_variable (octx, decl, in_code);
7550 for (; octx; octx = octx->outer_context)
7552 if (!(octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)))
7553 break;
7554 splay_tree_node n2
7555 = splay_tree_lookup (octx->variables,
7556 (splay_tree_key) decl);
7557 if (n2)
7559 if (octx->region_type == ORT_ACC_HOST_DATA)
7560 error ("variable %qE declared in enclosing "
7561 "%<host_data%> region", DECL_NAME (decl));
7562 nflags |= GOVD_MAP;
7563 if (octx->region_type == ORT_ACC_DATA
7564 && (n2->value & GOVD_MAP_0LEN_ARRAY))
7565 nflags |= GOVD_MAP_0LEN_ARRAY;
7566 goto found_outer;
7571 if ((nflags & ~(GOVD_MAP_TO_ONLY | GOVD_MAP_FROM_ONLY
7572 | GOVD_MAP_ALLOC_ONLY)) == flags)
7574 tree type = TREE_TYPE (decl);
7576 if (gimplify_omp_ctxp->target_firstprivatize_array_bases
7577 && lang_hooks.decls.omp_privatize_by_reference (decl))
7578 type = TREE_TYPE (type);
7579 if (!lang_hooks.types.omp_mappable_type (type))
7581 error ("%qD referenced in target region does not have "
7582 "a mappable type", decl);
7583 nflags |= GOVD_MAP | GOVD_EXPLICIT;
7585 else
7587 if ((ctx->region_type & ORT_ACC) != 0)
7588 nflags = oacc_default_clause (ctx, decl, flags);
7589 else
7590 nflags |= GOVD_MAP;
7593 found_outer:
7594 omp_add_variable (ctx, decl, nflags);
7596 else
7598 /* If nothing changed, there's nothing left to do. */
7599 if ((n->value & flags) == flags)
7600 return ret;
7601 flags |= n->value;
7602 n->value = flags;
7604 goto do_outer;
7607 if (n == NULL)
7609 if (ctx->region_type == ORT_WORKSHARE
7610 || ctx->region_type == ORT_TASKGROUP
7611 || ctx->region_type == ORT_SIMD
7612 || ctx->region_type == ORT_ACC
7613 || (ctx->region_type & ORT_TARGET_DATA) != 0)
7614 goto do_outer;
7616 flags = omp_default_clause (ctx, decl, in_code, flags);
7618 if ((flags & GOVD_PRIVATE)
7619 && lang_hooks.decls.omp_private_outer_ref (decl))
7620 flags |= GOVD_PRIVATE_OUTER_REF;
7622 omp_add_variable (ctx, decl, flags);
7624 shared = (flags & GOVD_SHARED) != 0;
7625 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
7626 goto do_outer;
7629 /* Don't mark as GOVD_SEEN addressable temporaries seen only in simd
7630 lb, b or incr expressions, those shouldn't be turned into simd arrays. */
7631 if (ctx->region_type == ORT_SIMD
7632 && ctx->in_for_exprs
7633 && ((n->value & (GOVD_PRIVATE | GOVD_SEEN | GOVD_EXPLICIT))
7634 == GOVD_PRIVATE))
7635 flags &= ~GOVD_SEEN;
7637 if ((n->value & (GOVD_SEEN | GOVD_LOCAL)) == 0
7638 && (flags & (GOVD_SEEN | GOVD_LOCAL)) == GOVD_SEEN
7639 && DECL_SIZE (decl))
7641 if (TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
7643 splay_tree_node n2;
7644 tree t = DECL_VALUE_EXPR (decl);
7645 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
7646 t = TREE_OPERAND (t, 0);
7647 gcc_assert (DECL_P (t));
7648 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
7649 n2->value |= GOVD_SEEN;
7651 else if (lang_hooks.decls.omp_privatize_by_reference (decl)
7652 && TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)))
7653 && (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl))))
7654 != INTEGER_CST))
7656 splay_tree_node n2;
7657 tree t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
7658 gcc_assert (DECL_P (t));
7659 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
7660 if (n2)
7661 omp_notice_variable (ctx, t, true);
7665 if (ctx->region_type & ORT_ACC)
7666 /* For OpenACC, as remarked above, defer expansion. */
7667 shared = false;
7668 else
7669 shared = ((flags | n->value) & GOVD_SHARED) != 0;
7670 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
7672 /* If nothing changed, there's nothing left to do. */
7673 if ((n->value & flags) == flags)
7674 return ret;
7675 flags |= n->value;
7676 n->value = flags;
7678 do_outer:
7679 /* If the variable is private in the current context, then we don't
7680 need to propagate anything to an outer context. */
7681 if ((flags & GOVD_PRIVATE) && !(flags & GOVD_PRIVATE_OUTER_REF))
7682 return ret;
7683 if ((flags & (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7684 == (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7685 return ret;
7686 if ((flags & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
7687 | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7688 == (GOVD_LASTPRIVATE | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7689 return ret;
7690 if (ctx->outer_context
7691 && omp_notice_variable (ctx->outer_context, decl, in_code))
7692 return true;
7693 return ret;
7696 /* Verify that DECL is private within CTX. If there's specific information
7697 to the contrary in the innermost scope, generate an error. */
7699 static bool
7700 omp_is_private (struct gimplify_omp_ctx *ctx, tree decl, int simd)
7702 splay_tree_node n;
7704 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7705 if (n != NULL)
7707 if (n->value & GOVD_SHARED)
7709 if (ctx == gimplify_omp_ctxp)
7711 if (simd)
7712 error ("iteration variable %qE is predetermined linear",
7713 DECL_NAME (decl));
7714 else
7715 error ("iteration variable %qE should be private",
7716 DECL_NAME (decl));
7717 n->value = GOVD_PRIVATE;
7718 return true;
7720 else
7721 return false;
7723 else if ((n->value & GOVD_EXPLICIT) != 0
7724 && (ctx == gimplify_omp_ctxp
7725 || (ctx->region_type == ORT_COMBINED_PARALLEL
7726 && gimplify_omp_ctxp->outer_context == ctx)))
7728 if ((n->value & GOVD_FIRSTPRIVATE) != 0)
7729 error ("iteration variable %qE should not be firstprivate",
7730 DECL_NAME (decl));
7731 else if ((n->value & GOVD_REDUCTION) != 0)
7732 error ("iteration variable %qE should not be reduction",
7733 DECL_NAME (decl));
7734 else if (simd != 1 && (n->value & GOVD_LINEAR) != 0)
7735 error ("iteration variable %qE should not be linear",
7736 DECL_NAME (decl));
7738 return (ctx == gimplify_omp_ctxp
7739 || (ctx->region_type == ORT_COMBINED_PARALLEL
7740 && gimplify_omp_ctxp->outer_context == ctx));
7743 if (ctx->region_type != ORT_WORKSHARE
7744 && ctx->region_type != ORT_TASKGROUP
7745 && ctx->region_type != ORT_SIMD
7746 && ctx->region_type != ORT_ACC)
7747 return false;
7748 else if (ctx->outer_context)
7749 return omp_is_private (ctx->outer_context, decl, simd);
7750 return false;
7753 /* Return true if DECL is private within a parallel region
7754 that binds to the current construct's context or in parallel
7755 region's REDUCTION clause. */
7757 static bool
7758 omp_check_private (struct gimplify_omp_ctx *ctx, tree decl, bool copyprivate)
7760 splay_tree_node n;
7764 ctx = ctx->outer_context;
7765 if (ctx == NULL)
7767 if (is_global_var (decl))
7768 return false;
7770 /* References might be private, but might be shared too,
7771 when checking for copyprivate, assume they might be
7772 private, otherwise assume they might be shared. */
7773 if (copyprivate)
7774 return true;
7776 if (lang_hooks.decls.omp_privatize_by_reference (decl))
7777 return false;
7779 /* Treat C++ privatized non-static data members outside
7780 of the privatization the same. */
7781 if (omp_member_access_dummy_var (decl))
7782 return false;
7784 return true;
7787 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
7789 if ((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0
7790 && (n == NULL || (n->value & GOVD_DATA_SHARE_CLASS) == 0))
7791 continue;
7793 if (n != NULL)
7795 if ((n->value & GOVD_LOCAL) != 0
7796 && omp_member_access_dummy_var (decl))
7797 return false;
7798 return (n->value & GOVD_SHARED) == 0;
7801 while (ctx->region_type == ORT_WORKSHARE
7802 || ctx->region_type == ORT_TASKGROUP
7803 || ctx->region_type == ORT_SIMD
7804 || ctx->region_type == ORT_ACC);
7805 return false;
7808 /* Callback for walk_tree to find a DECL_EXPR for the given DECL. */
7810 static tree
7811 find_decl_expr (tree *tp, int *walk_subtrees, void *data)
7813 tree t = *tp;
7815 /* If this node has been visited, unmark it and keep looking. */
7816 if (TREE_CODE (t) == DECL_EXPR && DECL_EXPR_DECL (t) == (tree) data)
7817 return t;
7819 if (IS_TYPE_OR_DECL_P (t))
7820 *walk_subtrees = 0;
7821 return NULL_TREE;
7825 /* Gimplify the affinity clause but effectively ignore it.
7826 Generate:
7827 var = begin;
7828 if ((step > 1) ? var <= end : var > end)
7829 locatator_var_expr; */
7831 static void
7832 gimplify_omp_affinity (tree *list_p, gimple_seq *pre_p)
7834 tree last_iter = NULL_TREE;
7835 tree last_bind = NULL_TREE;
7836 tree label = NULL_TREE;
7837 tree *last_body = NULL;
7838 for (tree c = *list_p; c; c = OMP_CLAUSE_CHAIN (c))
7839 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_AFFINITY)
7841 tree t = OMP_CLAUSE_DECL (c);
7842 if (TREE_CODE (t) == TREE_LIST
7843 && TREE_PURPOSE (t)
7844 && TREE_CODE (TREE_PURPOSE (t)) == TREE_VEC)
7846 if (TREE_VALUE (t) == null_pointer_node)
7847 continue;
7848 if (TREE_PURPOSE (t) != last_iter)
7850 if (last_bind)
7852 append_to_statement_list (label, last_body);
7853 gimplify_and_add (last_bind, pre_p);
7854 last_bind = NULL_TREE;
7856 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
7858 if (gimplify_expr (&TREE_VEC_ELT (it, 1), pre_p, NULL,
7859 is_gimple_val, fb_rvalue) == GS_ERROR
7860 || gimplify_expr (&TREE_VEC_ELT (it, 2), pre_p, NULL,
7861 is_gimple_val, fb_rvalue) == GS_ERROR
7862 || gimplify_expr (&TREE_VEC_ELT (it, 3), pre_p, NULL,
7863 is_gimple_val, fb_rvalue) == GS_ERROR
7864 || (gimplify_expr (&TREE_VEC_ELT (it, 4), pre_p, NULL,
7865 is_gimple_val, fb_rvalue)
7866 == GS_ERROR))
7867 return;
7869 last_iter = TREE_PURPOSE (t);
7870 tree block = TREE_VEC_ELT (TREE_PURPOSE (t), 5);
7871 last_bind = build3 (BIND_EXPR, void_type_node, BLOCK_VARS (block),
7872 NULL, block);
7873 last_body = &BIND_EXPR_BODY (last_bind);
7874 tree cond = NULL_TREE;
7875 location_t loc = OMP_CLAUSE_LOCATION (c);
7876 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
7878 tree var = TREE_VEC_ELT (it, 0);
7879 tree begin = TREE_VEC_ELT (it, 1);
7880 tree end = TREE_VEC_ELT (it, 2);
7881 tree step = TREE_VEC_ELT (it, 3);
7882 loc = DECL_SOURCE_LOCATION (var);
7883 tree tem = build2_loc (loc, MODIFY_EXPR, void_type_node,
7884 var, begin);
7885 append_to_statement_list_force (tem, last_body);
7887 tree cond1 = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
7888 step, build_zero_cst (TREE_TYPE (step)));
7889 tree cond2 = fold_build2_loc (loc, LE_EXPR, boolean_type_node,
7890 var, end);
7891 tree cond3 = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
7892 var, end);
7893 cond1 = fold_build3_loc (loc, COND_EXPR, boolean_type_node,
7894 cond1, cond2, cond3);
7895 if (cond)
7896 cond = fold_build2_loc (loc, TRUTH_AND_EXPR,
7897 boolean_type_node, cond, cond1);
7898 else
7899 cond = cond1;
7901 tree cont_label = create_artificial_label (loc);
7902 label = build1 (LABEL_EXPR, void_type_node, cont_label);
7903 tree tem = fold_build3_loc (loc, COND_EXPR, void_type_node, cond,
7904 void_node,
7905 build_and_jump (&cont_label));
7906 append_to_statement_list_force (tem, last_body);
7908 if (TREE_CODE (TREE_VALUE (t)) == COMPOUND_EXPR)
7910 append_to_statement_list (TREE_OPERAND (TREE_VALUE (t), 0),
7911 last_body);
7912 TREE_VALUE (t) = TREE_OPERAND (TREE_VALUE (t), 1);
7914 if (error_operand_p (TREE_VALUE (t)))
7915 return;
7916 append_to_statement_list_force (TREE_VALUE (t), last_body);
7917 TREE_VALUE (t) = null_pointer_node;
7919 else
7921 if (last_bind)
7923 append_to_statement_list (label, last_body);
7924 gimplify_and_add (last_bind, pre_p);
7925 last_bind = NULL_TREE;
7927 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
7929 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
7930 NULL, is_gimple_val, fb_rvalue);
7931 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
7933 if (error_operand_p (OMP_CLAUSE_DECL (c)))
7934 return;
7935 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
7936 is_gimple_val, fb_rvalue) == GS_ERROR)
7937 return;
7938 gimplify_and_add (OMP_CLAUSE_DECL (c), pre_p);
7941 if (last_bind)
7943 append_to_statement_list (label, last_body);
7944 gimplify_and_add (last_bind, pre_p);
7946 return;
7949 /* If *LIST_P contains any OpenMP depend clauses with iterators,
7950 lower all the depend clauses by populating corresponding depend
7951 array. Returns 0 if there are no such depend clauses, or
7952 2 if all depend clauses should be removed, 1 otherwise. */
7954 static int
7955 gimplify_omp_depend (tree *list_p, gimple_seq *pre_p)
7957 tree c;
7958 gimple *g;
7959 size_t n[4] = { 0, 0, 0, 0 };
7960 bool unused[4];
7961 tree counts[4] = { NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE };
7962 tree last_iter = NULL_TREE, last_count = NULL_TREE;
7963 size_t i, j;
7964 location_t first_loc = UNKNOWN_LOCATION;
7966 for (c = *list_p; c; c = OMP_CLAUSE_CHAIN (c))
7967 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND)
7969 switch (OMP_CLAUSE_DEPEND_KIND (c))
7971 case OMP_CLAUSE_DEPEND_IN:
7972 i = 2;
7973 break;
7974 case OMP_CLAUSE_DEPEND_OUT:
7975 case OMP_CLAUSE_DEPEND_INOUT:
7976 i = 0;
7977 break;
7978 case OMP_CLAUSE_DEPEND_MUTEXINOUTSET:
7979 i = 1;
7980 break;
7981 case OMP_CLAUSE_DEPEND_DEPOBJ:
7982 i = 3;
7983 break;
7984 case OMP_CLAUSE_DEPEND_SOURCE:
7985 case OMP_CLAUSE_DEPEND_SINK:
7986 continue;
7987 default:
7988 gcc_unreachable ();
7990 tree t = OMP_CLAUSE_DECL (c);
7991 if (first_loc == UNKNOWN_LOCATION)
7992 first_loc = OMP_CLAUSE_LOCATION (c);
7993 if (TREE_CODE (t) == TREE_LIST
7994 && TREE_PURPOSE (t)
7995 && TREE_CODE (TREE_PURPOSE (t)) == TREE_VEC)
7997 if (TREE_PURPOSE (t) != last_iter)
7999 tree tcnt = size_one_node;
8000 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8002 if (gimplify_expr (&TREE_VEC_ELT (it, 1), pre_p, NULL,
8003 is_gimple_val, fb_rvalue) == GS_ERROR
8004 || gimplify_expr (&TREE_VEC_ELT (it, 2), pre_p, NULL,
8005 is_gimple_val, fb_rvalue) == GS_ERROR
8006 || gimplify_expr (&TREE_VEC_ELT (it, 3), pre_p, NULL,
8007 is_gimple_val, fb_rvalue) == GS_ERROR
8008 || (gimplify_expr (&TREE_VEC_ELT (it, 4), pre_p, NULL,
8009 is_gimple_val, fb_rvalue)
8010 == GS_ERROR))
8011 return 2;
8012 tree var = TREE_VEC_ELT (it, 0);
8013 tree begin = TREE_VEC_ELT (it, 1);
8014 tree end = TREE_VEC_ELT (it, 2);
8015 tree step = TREE_VEC_ELT (it, 3);
8016 tree orig_step = TREE_VEC_ELT (it, 4);
8017 tree type = TREE_TYPE (var);
8018 tree stype = TREE_TYPE (step);
8019 location_t loc = DECL_SOURCE_LOCATION (var);
8020 tree endmbegin;
8021 /* Compute count for this iterator as
8022 orig_step > 0
8023 ? (begin < end ? (end - begin + (step - 1)) / step : 0)
8024 : (begin > end ? (end - begin + (step + 1)) / step : 0)
8025 and compute product of those for the entire depend
8026 clause. */
8027 if (POINTER_TYPE_P (type))
8028 endmbegin = fold_build2_loc (loc, POINTER_DIFF_EXPR,
8029 stype, end, begin);
8030 else
8031 endmbegin = fold_build2_loc (loc, MINUS_EXPR, type,
8032 end, begin);
8033 tree stepm1 = fold_build2_loc (loc, MINUS_EXPR, stype,
8034 step,
8035 build_int_cst (stype, 1));
8036 tree stepp1 = fold_build2_loc (loc, PLUS_EXPR, stype, step,
8037 build_int_cst (stype, 1));
8038 tree pos = fold_build2_loc (loc, PLUS_EXPR, stype,
8039 unshare_expr (endmbegin),
8040 stepm1);
8041 pos = fold_build2_loc (loc, TRUNC_DIV_EXPR, stype,
8042 pos, step);
8043 tree neg = fold_build2_loc (loc, PLUS_EXPR, stype,
8044 endmbegin, stepp1);
8045 if (TYPE_UNSIGNED (stype))
8047 neg = fold_build1_loc (loc, NEGATE_EXPR, stype, neg);
8048 step = fold_build1_loc (loc, NEGATE_EXPR, stype, step);
8050 neg = fold_build2_loc (loc, TRUNC_DIV_EXPR, stype,
8051 neg, step);
8052 step = NULL_TREE;
8053 tree cond = fold_build2_loc (loc, LT_EXPR,
8054 boolean_type_node,
8055 begin, end);
8056 pos = fold_build3_loc (loc, COND_EXPR, stype, cond, pos,
8057 build_int_cst (stype, 0));
8058 cond = fold_build2_loc (loc, LT_EXPR, boolean_type_node,
8059 end, begin);
8060 neg = fold_build3_loc (loc, COND_EXPR, stype, cond, neg,
8061 build_int_cst (stype, 0));
8062 tree osteptype = TREE_TYPE (orig_step);
8063 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8064 orig_step,
8065 build_int_cst (osteptype, 0));
8066 tree cnt = fold_build3_loc (loc, COND_EXPR, stype,
8067 cond, pos, neg);
8068 cnt = fold_convert_loc (loc, sizetype, cnt);
8069 if (gimplify_expr (&cnt, pre_p, NULL, is_gimple_val,
8070 fb_rvalue) == GS_ERROR)
8071 return 2;
8072 tcnt = size_binop_loc (loc, MULT_EXPR, tcnt, cnt);
8074 if (gimplify_expr (&tcnt, pre_p, NULL, is_gimple_val,
8075 fb_rvalue) == GS_ERROR)
8076 return 2;
8077 last_iter = TREE_PURPOSE (t);
8078 last_count = tcnt;
8080 if (counts[i] == NULL_TREE)
8081 counts[i] = last_count;
8082 else
8083 counts[i] = size_binop_loc (OMP_CLAUSE_LOCATION (c),
8084 PLUS_EXPR, counts[i], last_count);
8086 else
8087 n[i]++;
8089 for (i = 0; i < 4; i++)
8090 if (counts[i])
8091 break;
8092 if (i == 4)
8093 return 0;
8095 tree total = size_zero_node;
8096 for (i = 0; i < 4; i++)
8098 unused[i] = counts[i] == NULL_TREE && n[i] == 0;
8099 if (counts[i] == NULL_TREE)
8100 counts[i] = size_zero_node;
8101 if (n[i])
8102 counts[i] = size_binop (PLUS_EXPR, counts[i], size_int (n[i]));
8103 if (gimplify_expr (&counts[i], pre_p, NULL, is_gimple_val,
8104 fb_rvalue) == GS_ERROR)
8105 return 2;
8106 total = size_binop (PLUS_EXPR, total, counts[i]);
8109 if (gimplify_expr (&total, pre_p, NULL, is_gimple_val, fb_rvalue)
8110 == GS_ERROR)
8111 return 2;
8112 bool is_old = unused[1] && unused[3];
8113 tree totalpx = size_binop (PLUS_EXPR, unshare_expr (total),
8114 size_int (is_old ? 1 : 4));
8115 tree type = build_array_type (ptr_type_node, build_index_type (totalpx));
8116 tree array = create_tmp_var_raw (type);
8117 TREE_ADDRESSABLE (array) = 1;
8118 if (!poly_int_tree_p (totalpx))
8120 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (array)))
8121 gimplify_type_sizes (TREE_TYPE (array), pre_p);
8122 if (gimplify_omp_ctxp)
8124 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8125 while (ctx
8126 && (ctx->region_type == ORT_WORKSHARE
8127 || ctx->region_type == ORT_TASKGROUP
8128 || ctx->region_type == ORT_SIMD
8129 || ctx->region_type == ORT_ACC))
8130 ctx = ctx->outer_context;
8131 if (ctx)
8132 omp_add_variable (ctx, array, GOVD_LOCAL | GOVD_SEEN);
8134 gimplify_vla_decl (array, pre_p);
8136 else
8137 gimple_add_tmp_var (array);
8138 tree r = build4 (ARRAY_REF, ptr_type_node, array, size_int (0), NULL_TREE,
8139 NULL_TREE);
8140 tree tem;
8141 if (!is_old)
8143 tem = build2 (MODIFY_EXPR, void_type_node, r,
8144 build_int_cst (ptr_type_node, 0));
8145 gimplify_and_add (tem, pre_p);
8146 r = build4 (ARRAY_REF, ptr_type_node, array, size_int (1), NULL_TREE,
8147 NULL_TREE);
8149 tem = build2 (MODIFY_EXPR, void_type_node, r,
8150 fold_convert (ptr_type_node, total));
8151 gimplify_and_add (tem, pre_p);
8152 for (i = 1; i < (is_old ? 2 : 4); i++)
8154 r = build4 (ARRAY_REF, ptr_type_node, array, size_int (i + !is_old),
8155 NULL_TREE, NULL_TREE);
8156 tem = build2 (MODIFY_EXPR, void_type_node, r, counts[i - 1]);
8157 gimplify_and_add (tem, pre_p);
8160 tree cnts[4];
8161 for (j = 4; j; j--)
8162 if (!unused[j - 1])
8163 break;
8164 for (i = 0; i < 4; i++)
8166 if (i && (i >= j || unused[i - 1]))
8168 cnts[i] = cnts[i - 1];
8169 continue;
8171 cnts[i] = create_tmp_var (sizetype);
8172 if (i == 0)
8173 g = gimple_build_assign (cnts[i], size_int (is_old ? 2 : 5));
8174 else
8176 tree t;
8177 if (is_old)
8178 t = size_binop (PLUS_EXPR, counts[0], size_int (2));
8179 else
8180 t = size_binop (PLUS_EXPR, cnts[i - 1], counts[i - 1]);
8181 if (gimplify_expr (&t, pre_p, NULL, is_gimple_val, fb_rvalue)
8182 == GS_ERROR)
8183 return 2;
8184 g = gimple_build_assign (cnts[i], t);
8186 gimple_seq_add_stmt (pre_p, g);
8189 last_iter = NULL_TREE;
8190 tree last_bind = NULL_TREE;
8191 tree *last_body = NULL;
8192 for (c = *list_p; c; c = OMP_CLAUSE_CHAIN (c))
8193 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND)
8195 switch (OMP_CLAUSE_DEPEND_KIND (c))
8197 case OMP_CLAUSE_DEPEND_IN:
8198 i = 2;
8199 break;
8200 case OMP_CLAUSE_DEPEND_OUT:
8201 case OMP_CLAUSE_DEPEND_INOUT:
8202 i = 0;
8203 break;
8204 case OMP_CLAUSE_DEPEND_MUTEXINOUTSET:
8205 i = 1;
8206 break;
8207 case OMP_CLAUSE_DEPEND_DEPOBJ:
8208 i = 3;
8209 break;
8210 case OMP_CLAUSE_DEPEND_SOURCE:
8211 case OMP_CLAUSE_DEPEND_SINK:
8212 continue;
8213 default:
8214 gcc_unreachable ();
8216 tree t = OMP_CLAUSE_DECL (c);
8217 if (TREE_CODE (t) == TREE_LIST
8218 && TREE_PURPOSE (t)
8219 && TREE_CODE (TREE_PURPOSE (t)) == TREE_VEC)
8221 if (TREE_PURPOSE (t) != last_iter)
8223 if (last_bind)
8224 gimplify_and_add (last_bind, pre_p);
8225 tree block = TREE_VEC_ELT (TREE_PURPOSE (t), 5);
8226 last_bind = build3 (BIND_EXPR, void_type_node,
8227 BLOCK_VARS (block), NULL, block);
8228 TREE_SIDE_EFFECTS (last_bind) = 1;
8229 SET_EXPR_LOCATION (last_bind, OMP_CLAUSE_LOCATION (c));
8230 tree *p = &BIND_EXPR_BODY (last_bind);
8231 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8233 tree var = TREE_VEC_ELT (it, 0);
8234 tree begin = TREE_VEC_ELT (it, 1);
8235 tree end = TREE_VEC_ELT (it, 2);
8236 tree step = TREE_VEC_ELT (it, 3);
8237 tree orig_step = TREE_VEC_ELT (it, 4);
8238 tree type = TREE_TYPE (var);
8239 location_t loc = DECL_SOURCE_LOCATION (var);
8240 /* Emit:
8241 var = begin;
8242 goto cond_label;
8243 beg_label:
8245 var = var + step;
8246 cond_label:
8247 if (orig_step > 0) {
8248 if (var < end) goto beg_label;
8249 } else {
8250 if (var > end) goto beg_label;
8252 for each iterator, with inner iterators added to
8253 the ... above. */
8254 tree beg_label = create_artificial_label (loc);
8255 tree cond_label = NULL_TREE;
8256 tem = build2_loc (loc, MODIFY_EXPR, void_type_node,
8257 var, begin);
8258 append_to_statement_list_force (tem, p);
8259 tem = build_and_jump (&cond_label);
8260 append_to_statement_list_force (tem, p);
8261 tem = build1 (LABEL_EXPR, void_type_node, beg_label);
8262 append_to_statement_list (tem, p);
8263 tree bind = build3 (BIND_EXPR, void_type_node, NULL_TREE,
8264 NULL_TREE, NULL_TREE);
8265 TREE_SIDE_EFFECTS (bind) = 1;
8266 SET_EXPR_LOCATION (bind, loc);
8267 append_to_statement_list_force (bind, p);
8268 if (POINTER_TYPE_P (type))
8269 tem = build2_loc (loc, POINTER_PLUS_EXPR, type,
8270 var, fold_convert_loc (loc, sizetype,
8271 step));
8272 else
8273 tem = build2_loc (loc, PLUS_EXPR, type, var, step);
8274 tem = build2_loc (loc, MODIFY_EXPR, void_type_node,
8275 var, tem);
8276 append_to_statement_list_force (tem, p);
8277 tem = build1 (LABEL_EXPR, void_type_node, cond_label);
8278 append_to_statement_list (tem, p);
8279 tree cond = fold_build2_loc (loc, LT_EXPR,
8280 boolean_type_node,
8281 var, end);
8282 tree pos
8283 = fold_build3_loc (loc, COND_EXPR, void_type_node,
8284 cond, build_and_jump (&beg_label),
8285 void_node);
8286 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8287 var, end);
8288 tree neg
8289 = fold_build3_loc (loc, COND_EXPR, void_type_node,
8290 cond, build_and_jump (&beg_label),
8291 void_node);
8292 tree osteptype = TREE_TYPE (orig_step);
8293 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8294 orig_step,
8295 build_int_cst (osteptype, 0));
8296 tem = fold_build3_loc (loc, COND_EXPR, void_type_node,
8297 cond, pos, neg);
8298 append_to_statement_list_force (tem, p);
8299 p = &BIND_EXPR_BODY (bind);
8301 last_body = p;
8303 last_iter = TREE_PURPOSE (t);
8304 if (TREE_CODE (TREE_VALUE (t)) == COMPOUND_EXPR)
8306 append_to_statement_list (TREE_OPERAND (TREE_VALUE (t),
8307 0), last_body);
8308 TREE_VALUE (t) = TREE_OPERAND (TREE_VALUE (t), 1);
8310 if (error_operand_p (TREE_VALUE (t)))
8311 return 2;
8312 TREE_VALUE (t) = build_fold_addr_expr (TREE_VALUE (t));
8313 r = build4 (ARRAY_REF, ptr_type_node, array, cnts[i],
8314 NULL_TREE, NULL_TREE);
8315 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
8316 void_type_node, r, TREE_VALUE (t));
8317 append_to_statement_list_force (tem, last_body);
8318 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
8319 void_type_node, cnts[i],
8320 size_binop (PLUS_EXPR, cnts[i], size_int (1)));
8321 append_to_statement_list_force (tem, last_body);
8322 TREE_VALUE (t) = null_pointer_node;
8324 else
8326 if (last_bind)
8328 gimplify_and_add (last_bind, pre_p);
8329 last_bind = NULL_TREE;
8331 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
8333 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
8334 NULL, is_gimple_val, fb_rvalue);
8335 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
8337 if (error_operand_p (OMP_CLAUSE_DECL (c)))
8338 return 2;
8339 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (OMP_CLAUSE_DECL (c));
8340 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
8341 is_gimple_val, fb_rvalue) == GS_ERROR)
8342 return 2;
8343 r = build4 (ARRAY_REF, ptr_type_node, array, cnts[i],
8344 NULL_TREE, NULL_TREE);
8345 tem = build2 (MODIFY_EXPR, void_type_node, r, OMP_CLAUSE_DECL (c));
8346 gimplify_and_add (tem, pre_p);
8347 g = gimple_build_assign (cnts[i], size_binop (PLUS_EXPR, cnts[i],
8348 size_int (1)));
8349 gimple_seq_add_stmt (pre_p, g);
8352 if (last_bind)
8353 gimplify_and_add (last_bind, pre_p);
8354 tree cond = boolean_false_node;
8355 if (is_old)
8357 if (!unused[0])
8358 cond = build2_loc (first_loc, NE_EXPR, boolean_type_node, cnts[0],
8359 size_binop_loc (first_loc, PLUS_EXPR, counts[0],
8360 size_int (2)));
8361 if (!unused[2])
8362 cond = build2_loc (first_loc, TRUTH_OR_EXPR, boolean_type_node, cond,
8363 build2_loc (first_loc, NE_EXPR, boolean_type_node,
8364 cnts[2],
8365 size_binop_loc (first_loc, PLUS_EXPR,
8366 totalpx,
8367 size_int (1))));
8369 else
8371 tree prev = size_int (5);
8372 for (i = 0; i < 4; i++)
8374 if (unused[i])
8375 continue;
8376 prev = size_binop_loc (first_loc, PLUS_EXPR, counts[i], prev);
8377 cond = build2_loc (first_loc, TRUTH_OR_EXPR, boolean_type_node, cond,
8378 build2_loc (first_loc, NE_EXPR, boolean_type_node,
8379 cnts[i], unshare_expr (prev)));
8382 tem = build3_loc (first_loc, COND_EXPR, void_type_node, cond,
8383 build_call_expr_loc (first_loc,
8384 builtin_decl_explicit (BUILT_IN_TRAP),
8385 0), void_node);
8386 gimplify_and_add (tem, pre_p);
8387 c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_DEPEND);
8388 OMP_CLAUSE_DEPEND_KIND (c) = OMP_CLAUSE_DEPEND_LAST;
8389 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (array);
8390 OMP_CLAUSE_CHAIN (c) = *list_p;
8391 *list_p = c;
8392 return 1;
8395 /* Insert a GOMP_MAP_ALLOC or GOMP_MAP_RELEASE node following a
8396 GOMP_MAP_STRUCT mapping. C is an always_pointer mapping. STRUCT_NODE is
8397 the struct node to insert the new mapping after (when the struct node is
8398 initially created). PREV_NODE is the first of two or three mappings for a
8399 pointer, and is either:
8400 - the node before C, when a pair of mappings is used, e.g. for a C/C++
8401 array section.
8402 - not the node before C. This is true when we have a reference-to-pointer
8403 type (with a mapping for the reference and for the pointer), or for
8404 Fortran derived-type mappings with a GOMP_MAP_TO_PSET.
8405 If SCP is non-null, the new node is inserted before *SCP.
8406 if SCP is null, the new node is inserted before PREV_NODE.
8407 The return type is:
8408 - PREV_NODE, if SCP is non-null.
8409 - The newly-created ALLOC or RELEASE node, if SCP is null.
8410 - The second newly-created ALLOC or RELEASE node, if we are mapping a
8411 reference to a pointer. */
8413 static tree
8414 insert_struct_comp_map (enum tree_code code, tree c, tree struct_node,
8415 tree prev_node, tree *scp)
8417 enum gomp_map_kind mkind
8418 = (code == OMP_TARGET_EXIT_DATA || code == OACC_EXIT_DATA)
8419 ? GOMP_MAP_RELEASE : GOMP_MAP_ALLOC;
8421 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c), OMP_CLAUSE_MAP);
8422 tree cl = scp ? prev_node : c2;
8423 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
8424 OMP_CLAUSE_DECL (c2) = unshare_expr (OMP_CLAUSE_DECL (c));
8425 OMP_CLAUSE_CHAIN (c2) = scp ? *scp : prev_node;
8426 if (OMP_CLAUSE_CHAIN (prev_node) != c
8427 && OMP_CLAUSE_CODE (OMP_CLAUSE_CHAIN (prev_node)) == OMP_CLAUSE_MAP
8428 && (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (prev_node))
8429 == GOMP_MAP_TO_PSET))
8430 OMP_CLAUSE_SIZE (c2) = OMP_CLAUSE_SIZE (OMP_CLAUSE_CHAIN (prev_node));
8431 else
8432 OMP_CLAUSE_SIZE (c2) = TYPE_SIZE_UNIT (ptr_type_node);
8433 if (struct_node)
8434 OMP_CLAUSE_CHAIN (struct_node) = c2;
8436 /* We might need to create an additional mapping if we have a reference to a
8437 pointer (in C++). Don't do this if we have something other than a
8438 GOMP_MAP_ALWAYS_POINTER though, i.e. a GOMP_MAP_TO_PSET. */
8439 if (OMP_CLAUSE_CHAIN (prev_node) != c
8440 && OMP_CLAUSE_CODE (OMP_CLAUSE_CHAIN (prev_node)) == OMP_CLAUSE_MAP
8441 && ((OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (prev_node))
8442 == GOMP_MAP_ALWAYS_POINTER)
8443 || (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (prev_node))
8444 == GOMP_MAP_ATTACH_DETACH)))
8446 tree c4 = OMP_CLAUSE_CHAIN (prev_node);
8447 tree c3 = build_omp_clause (OMP_CLAUSE_LOCATION (c), OMP_CLAUSE_MAP);
8448 OMP_CLAUSE_SET_MAP_KIND (c3, mkind);
8449 OMP_CLAUSE_DECL (c3) = unshare_expr (OMP_CLAUSE_DECL (c4));
8450 OMP_CLAUSE_SIZE (c3) = TYPE_SIZE_UNIT (ptr_type_node);
8451 OMP_CLAUSE_CHAIN (c3) = prev_node;
8452 if (!scp)
8453 OMP_CLAUSE_CHAIN (c2) = c3;
8454 else
8455 cl = c3;
8458 if (scp)
8459 *scp = c2;
8461 return cl;
8464 /* Strip ARRAY_REFS or an indirect ref off BASE, find the containing object,
8465 and set *BITPOSP and *POFFSETP to the bit offset of the access.
8466 If BASE_REF is non-NULL and the containing object is a reference, set
8467 *BASE_REF to that reference before dereferencing the object.
8468 If BASE_REF is NULL, check that the containing object is a COMPONENT_REF or
8469 has array type, else return NULL. */
8471 static tree
8472 extract_base_bit_offset (tree base, tree *base_ref, poly_int64 *bitposp,
8473 poly_offset_int *poffsetp)
8475 tree offset;
8476 poly_int64 bitsize, bitpos;
8477 machine_mode mode;
8478 int unsignedp, reversep, volatilep = 0;
8479 poly_offset_int poffset;
8481 if (base_ref)
8483 *base_ref = NULL_TREE;
8485 while (TREE_CODE (base) == ARRAY_REF)
8486 base = TREE_OPERAND (base, 0);
8488 if (TREE_CODE (base) == INDIRECT_REF)
8489 base = TREE_OPERAND (base, 0);
8491 else
8493 if (TREE_CODE (base) == ARRAY_REF)
8495 while (TREE_CODE (base) == ARRAY_REF)
8496 base = TREE_OPERAND (base, 0);
8497 if (TREE_CODE (base) != COMPONENT_REF
8498 || TREE_CODE (TREE_TYPE (base)) != ARRAY_TYPE)
8499 return NULL_TREE;
8501 else if (TREE_CODE (base) == INDIRECT_REF
8502 && TREE_CODE (TREE_OPERAND (base, 0)) == COMPONENT_REF
8503 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (base, 0)))
8504 == REFERENCE_TYPE))
8505 base = TREE_OPERAND (base, 0);
8508 base = get_inner_reference (base, &bitsize, &bitpos, &offset, &mode,
8509 &unsignedp, &reversep, &volatilep);
8511 tree orig_base = base;
8513 if ((TREE_CODE (base) == INDIRECT_REF
8514 || (TREE_CODE (base) == MEM_REF
8515 && integer_zerop (TREE_OPERAND (base, 1))))
8516 && DECL_P (TREE_OPERAND (base, 0))
8517 && TREE_CODE (TREE_TYPE (TREE_OPERAND (base, 0))) == REFERENCE_TYPE)
8518 base = TREE_OPERAND (base, 0);
8520 gcc_assert (offset == NULL_TREE || poly_int_tree_p (offset));
8522 if (offset)
8523 poffset = wi::to_poly_offset (offset);
8524 else
8525 poffset = 0;
8527 if (maybe_ne (bitpos, 0))
8528 poffset += bits_to_bytes_round_down (bitpos);
8530 *bitposp = bitpos;
8531 *poffsetp = poffset;
8533 /* Set *BASE_REF if BASE was a dereferenced reference variable. */
8534 if (base_ref && orig_base != base)
8535 *base_ref = orig_base;
8537 return base;
8540 /* Returns true if EXPR is or contains (as a sub-component) BASE_PTR. */
8542 static bool
8543 is_or_contains_p (tree expr, tree base_ptr)
8545 while (expr != base_ptr)
8546 if (TREE_CODE (base_ptr) == COMPONENT_REF)
8547 base_ptr = TREE_OPERAND (base_ptr, 0);
8548 else
8549 break;
8550 return expr == base_ptr;
8553 /* Implement OpenMP 5.x map ordering rules for target directives. There are
8554 several rules, and with some level of ambiguity, hopefully we can at least
8555 collect the complexity here in one place. */
8557 static void
8558 omp_target_reorder_clauses (tree *list_p)
8560 /* Collect refs to alloc/release/delete maps. */
8561 auto_vec<tree, 32> ard;
8562 tree *cp = list_p;
8563 while (*cp != NULL_TREE)
8564 if (OMP_CLAUSE_CODE (*cp) == OMP_CLAUSE_MAP
8565 && (OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_ALLOC
8566 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_RELEASE
8567 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_DELETE))
8569 /* Unlink cp and push to ard. */
8570 tree c = *cp;
8571 tree nc = OMP_CLAUSE_CHAIN (c);
8572 *cp = nc;
8573 ard.safe_push (c);
8575 /* Any associated pointer type maps should also move along. */
8576 while (*cp != NULL_TREE
8577 && OMP_CLAUSE_CODE (*cp) == OMP_CLAUSE_MAP
8578 && (OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_FIRSTPRIVATE_REFERENCE
8579 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_FIRSTPRIVATE_POINTER
8580 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_ATTACH_DETACH
8581 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_POINTER
8582 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_ALWAYS_POINTER
8583 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_TO_PSET))
8585 c = *cp;
8586 nc = OMP_CLAUSE_CHAIN (c);
8587 *cp = nc;
8588 ard.safe_push (c);
8591 else
8592 cp = &OMP_CLAUSE_CHAIN (*cp);
8594 /* Link alloc/release/delete maps to the end of list. */
8595 for (unsigned int i = 0; i < ard.length (); i++)
8597 *cp = ard[i];
8598 cp = &OMP_CLAUSE_CHAIN (ard[i]);
8600 *cp = NULL_TREE;
8602 /* OpenMP 5.0 requires that pointer variables are mapped before
8603 its use as a base-pointer. */
8604 auto_vec<tree *, 32> atf;
8605 for (tree *cp = list_p; *cp; cp = &OMP_CLAUSE_CHAIN (*cp))
8606 if (OMP_CLAUSE_CODE (*cp) == OMP_CLAUSE_MAP)
8608 /* Collect alloc, to, from, to/from clause tree pointers. */
8609 gomp_map_kind k = OMP_CLAUSE_MAP_KIND (*cp);
8610 if (k == GOMP_MAP_ALLOC
8611 || k == GOMP_MAP_TO
8612 || k == GOMP_MAP_FROM
8613 || k == GOMP_MAP_TOFROM
8614 || k == GOMP_MAP_ALWAYS_TO
8615 || k == GOMP_MAP_ALWAYS_FROM
8616 || k == GOMP_MAP_ALWAYS_TOFROM)
8617 atf.safe_push (cp);
8620 for (unsigned int i = 0; i < atf.length (); i++)
8621 if (atf[i])
8623 tree *cp = atf[i];
8624 tree decl = OMP_CLAUSE_DECL (*cp);
8625 if (TREE_CODE (decl) == INDIRECT_REF || TREE_CODE (decl) == MEM_REF)
8627 tree base_ptr = TREE_OPERAND (decl, 0);
8628 STRIP_TYPE_NOPS (base_ptr);
8629 for (unsigned int j = i + 1; j < atf.length (); j++)
8631 tree *cp2 = atf[j];
8632 tree decl2 = OMP_CLAUSE_DECL (*cp2);
8633 if (is_or_contains_p (decl2, base_ptr))
8635 /* Move *cp2 to before *cp. */
8636 tree c = *cp2;
8637 *cp2 = OMP_CLAUSE_CHAIN (c);
8638 OMP_CLAUSE_CHAIN (c) = *cp;
8639 *cp = c;
8640 atf[j] = NULL;
8647 /* DECL is supposed to have lastprivate semantics in the outer contexts
8648 of combined/composite constructs, starting with OCTX.
8649 Add needed lastprivate, shared or map clause if no data sharing or
8650 mapping clause are present. IMPLICIT_P is true if it is an implicit
8651 clause (IV on simd), in which case the lastprivate will not be
8652 copied to some constructs. */
8654 static void
8655 omp_lastprivate_for_combined_outer_constructs (struct gimplify_omp_ctx *octx,
8656 tree decl, bool implicit_p)
8658 struct gimplify_omp_ctx *orig_octx = octx;
8659 for (; octx; octx = octx->outer_context)
8661 if ((octx->region_type == ORT_COMBINED_PARALLEL
8662 || (octx->region_type & ORT_COMBINED_TEAMS) == ORT_COMBINED_TEAMS)
8663 && splay_tree_lookup (octx->variables,
8664 (splay_tree_key) decl) == NULL)
8666 omp_add_variable (octx, decl, GOVD_SHARED | GOVD_SEEN);
8667 continue;
8669 if ((octx->region_type & ORT_TASK) != 0
8670 && octx->combined_loop
8671 && splay_tree_lookup (octx->variables,
8672 (splay_tree_key) decl) == NULL)
8674 omp_add_variable (octx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
8675 continue;
8677 if (implicit_p
8678 && octx->region_type == ORT_WORKSHARE
8679 && octx->combined_loop
8680 && splay_tree_lookup (octx->variables,
8681 (splay_tree_key) decl) == NULL
8682 && octx->outer_context
8683 && octx->outer_context->region_type == ORT_COMBINED_PARALLEL
8684 && splay_tree_lookup (octx->outer_context->variables,
8685 (splay_tree_key) decl) == NULL)
8687 octx = octx->outer_context;
8688 omp_add_variable (octx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
8689 continue;
8691 if ((octx->region_type == ORT_WORKSHARE || octx->region_type == ORT_ACC)
8692 && octx->combined_loop
8693 && splay_tree_lookup (octx->variables,
8694 (splay_tree_key) decl) == NULL
8695 && !omp_check_private (octx, decl, false))
8697 omp_add_variable (octx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
8698 continue;
8700 if (octx->region_type == ORT_COMBINED_TARGET)
8702 splay_tree_node n = splay_tree_lookup (octx->variables,
8703 (splay_tree_key) decl);
8704 if (n == NULL)
8706 omp_add_variable (octx, decl, GOVD_MAP | GOVD_SEEN);
8707 octx = octx->outer_context;
8709 else if (!implicit_p
8710 && (n->value & GOVD_FIRSTPRIVATE_IMPLICIT))
8712 n->value &= ~(GOVD_FIRSTPRIVATE
8713 | GOVD_FIRSTPRIVATE_IMPLICIT
8714 | GOVD_EXPLICIT);
8715 omp_add_variable (octx, decl, GOVD_MAP | GOVD_SEEN);
8716 octx = octx->outer_context;
8719 break;
8721 if (octx && (implicit_p || octx != orig_octx))
8722 omp_notice_variable (octx, decl, true);
8725 /* Scan the OMP clauses in *LIST_P, installing mappings into a new
8726 and previous omp contexts. */
8728 static void
8729 gimplify_scan_omp_clauses (tree *list_p, gimple_seq *pre_p,
8730 enum omp_region_type region_type,
8731 enum tree_code code)
8733 struct gimplify_omp_ctx *ctx, *outer_ctx;
8734 tree c;
8735 hash_map<tree, tree> *struct_map_to_clause = NULL;
8736 hash_set<tree> *struct_deref_set = NULL;
8737 tree *prev_list_p = NULL, *orig_list_p = list_p;
8738 int handled_depend_iterators = -1;
8739 int nowait = -1;
8741 ctx = new_omp_context (region_type);
8742 ctx->code = code;
8743 outer_ctx = ctx->outer_context;
8744 if (code == OMP_TARGET)
8746 if (!lang_GNU_Fortran ())
8747 ctx->defaultmap[GDMK_POINTER] = GOVD_MAP | GOVD_MAP_0LEN_ARRAY;
8748 ctx->defaultmap[GDMK_SCALAR] = GOVD_FIRSTPRIVATE;
8750 if (!lang_GNU_Fortran ())
8751 switch (code)
8753 case OMP_TARGET:
8754 case OMP_TARGET_DATA:
8755 case OMP_TARGET_ENTER_DATA:
8756 case OMP_TARGET_EXIT_DATA:
8757 case OACC_DECLARE:
8758 case OACC_HOST_DATA:
8759 case OACC_PARALLEL:
8760 case OACC_KERNELS:
8761 ctx->target_firstprivatize_array_bases = true;
8762 default:
8763 break;
8766 if (code == OMP_TARGET
8767 || code == OMP_TARGET_DATA
8768 || code == OMP_TARGET_ENTER_DATA
8769 || code == OMP_TARGET_EXIT_DATA)
8770 omp_target_reorder_clauses (list_p);
8772 while ((c = *list_p) != NULL)
8774 bool remove = false;
8775 bool notice_outer = true;
8776 const char *check_non_private = NULL;
8777 unsigned int flags;
8778 tree decl;
8780 switch (OMP_CLAUSE_CODE (c))
8782 case OMP_CLAUSE_PRIVATE:
8783 flags = GOVD_PRIVATE | GOVD_EXPLICIT;
8784 if (lang_hooks.decls.omp_private_outer_ref (OMP_CLAUSE_DECL (c)))
8786 flags |= GOVD_PRIVATE_OUTER_REF;
8787 OMP_CLAUSE_PRIVATE_OUTER_REF (c) = 1;
8789 else
8790 notice_outer = false;
8791 goto do_add;
8792 case OMP_CLAUSE_SHARED:
8793 flags = GOVD_SHARED | GOVD_EXPLICIT;
8794 goto do_add;
8795 case OMP_CLAUSE_FIRSTPRIVATE:
8796 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
8797 check_non_private = "firstprivate";
8798 if (OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (c))
8800 gcc_assert (code == OMP_TARGET);
8801 flags |= GOVD_FIRSTPRIVATE_IMPLICIT;
8803 goto do_add;
8804 case OMP_CLAUSE_LASTPRIVATE:
8805 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
8806 switch (code)
8808 case OMP_DISTRIBUTE:
8809 error_at (OMP_CLAUSE_LOCATION (c),
8810 "conditional %<lastprivate%> clause on "
8811 "%qs construct", "distribute");
8812 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
8813 break;
8814 case OMP_TASKLOOP:
8815 error_at (OMP_CLAUSE_LOCATION (c),
8816 "conditional %<lastprivate%> clause on "
8817 "%qs construct", "taskloop");
8818 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
8819 break;
8820 default:
8821 break;
8823 flags = GOVD_LASTPRIVATE | GOVD_SEEN | GOVD_EXPLICIT;
8824 if (code != OMP_LOOP)
8825 check_non_private = "lastprivate";
8826 decl = OMP_CLAUSE_DECL (c);
8827 if (error_operand_p (decl))
8828 goto do_add;
8829 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c)
8830 && !lang_hooks.decls.omp_scalar_p (decl))
8832 error_at (OMP_CLAUSE_LOCATION (c),
8833 "non-scalar variable %qD in conditional "
8834 "%<lastprivate%> clause", decl);
8835 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
8837 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
8838 flags |= GOVD_LASTPRIVATE_CONDITIONAL;
8839 omp_lastprivate_for_combined_outer_constructs (outer_ctx, decl,
8840 false);
8841 goto do_add;
8842 case OMP_CLAUSE_REDUCTION:
8843 if (OMP_CLAUSE_REDUCTION_TASK (c))
8845 if (region_type == ORT_WORKSHARE)
8847 if (nowait == -1)
8848 nowait = omp_find_clause (*list_p,
8849 OMP_CLAUSE_NOWAIT) != NULL_TREE;
8850 if (nowait
8851 && (outer_ctx == NULL
8852 || outer_ctx->region_type != ORT_COMBINED_PARALLEL))
8854 error_at (OMP_CLAUSE_LOCATION (c),
8855 "%<task%> reduction modifier on a construct "
8856 "with a %<nowait%> clause");
8857 OMP_CLAUSE_REDUCTION_TASK (c) = 0;
8860 else if ((region_type & ORT_PARALLEL) != ORT_PARALLEL)
8862 error_at (OMP_CLAUSE_LOCATION (c),
8863 "invalid %<task%> reduction modifier on construct "
8864 "other than %<parallel%>, %qs or %<sections%>",
8865 lang_GNU_Fortran () ? "do" : "for");
8866 OMP_CLAUSE_REDUCTION_TASK (c) = 0;
8869 if (OMP_CLAUSE_REDUCTION_INSCAN (c))
8870 switch (code)
8872 case OMP_SECTIONS:
8873 error_at (OMP_CLAUSE_LOCATION (c),
8874 "%<inscan%> %<reduction%> clause on "
8875 "%qs construct", "sections");
8876 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
8877 break;
8878 case OMP_PARALLEL:
8879 error_at (OMP_CLAUSE_LOCATION (c),
8880 "%<inscan%> %<reduction%> clause on "
8881 "%qs construct", "parallel");
8882 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
8883 break;
8884 case OMP_TEAMS:
8885 error_at (OMP_CLAUSE_LOCATION (c),
8886 "%<inscan%> %<reduction%> clause on "
8887 "%qs construct", "teams");
8888 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
8889 break;
8890 case OMP_TASKLOOP:
8891 error_at (OMP_CLAUSE_LOCATION (c),
8892 "%<inscan%> %<reduction%> clause on "
8893 "%qs construct", "taskloop");
8894 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
8895 break;
8896 default:
8897 break;
8899 /* FALLTHRU */
8900 case OMP_CLAUSE_IN_REDUCTION:
8901 case OMP_CLAUSE_TASK_REDUCTION:
8902 flags = GOVD_REDUCTION | GOVD_SEEN | GOVD_EXPLICIT;
8903 /* OpenACC permits reductions on private variables. */
8904 if (!(region_type & ORT_ACC)
8905 /* taskgroup is actually not a worksharing region. */
8906 && code != OMP_TASKGROUP)
8907 check_non_private = omp_clause_code_name[OMP_CLAUSE_CODE (c)];
8908 decl = OMP_CLAUSE_DECL (c);
8909 if (TREE_CODE (decl) == MEM_REF)
8911 tree type = TREE_TYPE (decl);
8912 bool saved_into_ssa = gimplify_ctxp->into_ssa;
8913 gimplify_ctxp->into_ssa = false;
8914 if (gimplify_expr (&TYPE_MAX_VALUE (TYPE_DOMAIN (type)), pre_p,
8915 NULL, is_gimple_val, fb_rvalue, false)
8916 == GS_ERROR)
8918 gimplify_ctxp->into_ssa = saved_into_ssa;
8919 remove = true;
8920 break;
8922 gimplify_ctxp->into_ssa = saved_into_ssa;
8923 tree v = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
8924 if (DECL_P (v))
8926 omp_firstprivatize_variable (ctx, v);
8927 omp_notice_variable (ctx, v, true);
8929 decl = TREE_OPERAND (decl, 0);
8930 if (TREE_CODE (decl) == POINTER_PLUS_EXPR)
8932 gimplify_ctxp->into_ssa = false;
8933 if (gimplify_expr (&TREE_OPERAND (decl, 1), pre_p,
8934 NULL, is_gimple_val, fb_rvalue, false)
8935 == GS_ERROR)
8937 gimplify_ctxp->into_ssa = saved_into_ssa;
8938 remove = true;
8939 break;
8941 gimplify_ctxp->into_ssa = saved_into_ssa;
8942 v = TREE_OPERAND (decl, 1);
8943 if (DECL_P (v))
8945 omp_firstprivatize_variable (ctx, v);
8946 omp_notice_variable (ctx, v, true);
8948 decl = TREE_OPERAND (decl, 0);
8950 if (TREE_CODE (decl) == ADDR_EXPR
8951 || TREE_CODE (decl) == INDIRECT_REF)
8952 decl = TREE_OPERAND (decl, 0);
8954 goto do_add_decl;
8955 case OMP_CLAUSE_LINEAR:
8956 if (gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c), pre_p, NULL,
8957 is_gimple_val, fb_rvalue) == GS_ERROR)
8959 remove = true;
8960 break;
8962 else
8964 if (code == OMP_SIMD
8965 && !OMP_CLAUSE_LINEAR_NO_COPYIN (c))
8967 struct gimplify_omp_ctx *octx = outer_ctx;
8968 if (octx
8969 && octx->region_type == ORT_WORKSHARE
8970 && octx->combined_loop
8971 && !octx->distribute)
8973 if (octx->outer_context
8974 && (octx->outer_context->region_type
8975 == ORT_COMBINED_PARALLEL))
8976 octx = octx->outer_context->outer_context;
8977 else
8978 octx = octx->outer_context;
8980 if (octx
8981 && octx->region_type == ORT_WORKSHARE
8982 && octx->combined_loop
8983 && octx->distribute)
8985 error_at (OMP_CLAUSE_LOCATION (c),
8986 "%<linear%> clause for variable other than "
8987 "loop iterator specified on construct "
8988 "combined with %<distribute%>");
8989 remove = true;
8990 break;
8993 /* For combined #pragma omp parallel for simd, need to put
8994 lastprivate and perhaps firstprivate too on the
8995 parallel. Similarly for #pragma omp for simd. */
8996 struct gimplify_omp_ctx *octx = outer_ctx;
8997 bool taskloop_seen = false;
8998 decl = NULL_TREE;
9001 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
9002 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
9003 break;
9004 decl = OMP_CLAUSE_DECL (c);
9005 if (error_operand_p (decl))
9007 decl = NULL_TREE;
9008 break;
9010 flags = GOVD_SEEN;
9011 if (!OMP_CLAUSE_LINEAR_NO_COPYIN (c))
9012 flags |= GOVD_FIRSTPRIVATE;
9013 if (!OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
9014 flags |= GOVD_LASTPRIVATE;
9015 if (octx
9016 && octx->region_type == ORT_WORKSHARE
9017 && octx->combined_loop)
9019 if (octx->outer_context
9020 && (octx->outer_context->region_type
9021 == ORT_COMBINED_PARALLEL))
9022 octx = octx->outer_context;
9023 else if (omp_check_private (octx, decl, false))
9024 break;
9026 else if (octx
9027 && (octx->region_type & ORT_TASK) != 0
9028 && octx->combined_loop)
9029 taskloop_seen = true;
9030 else if (octx
9031 && octx->region_type == ORT_COMBINED_PARALLEL
9032 && ((ctx->region_type == ORT_WORKSHARE
9033 && octx == outer_ctx)
9034 || taskloop_seen))
9035 flags = GOVD_SEEN | GOVD_SHARED;
9036 else if (octx
9037 && ((octx->region_type & ORT_COMBINED_TEAMS)
9038 == ORT_COMBINED_TEAMS))
9039 flags = GOVD_SEEN | GOVD_SHARED;
9040 else if (octx
9041 && octx->region_type == ORT_COMBINED_TARGET)
9043 if (flags & GOVD_LASTPRIVATE)
9044 flags = GOVD_SEEN | GOVD_MAP;
9046 else
9047 break;
9048 splay_tree_node on
9049 = splay_tree_lookup (octx->variables,
9050 (splay_tree_key) decl);
9051 if (on && (on->value & GOVD_DATA_SHARE_CLASS) != 0)
9053 octx = NULL;
9054 break;
9056 omp_add_variable (octx, decl, flags);
9057 if (octx->outer_context == NULL)
9058 break;
9059 octx = octx->outer_context;
9061 while (1);
9062 if (octx
9063 && decl
9064 && (!OMP_CLAUSE_LINEAR_NO_COPYIN (c)
9065 || !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
9066 omp_notice_variable (octx, decl, true);
9068 flags = GOVD_LINEAR | GOVD_EXPLICIT;
9069 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
9070 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
9072 notice_outer = false;
9073 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
9075 goto do_add;
9077 case OMP_CLAUSE_MAP:
9078 decl = OMP_CLAUSE_DECL (c);
9079 if (error_operand_p (decl))
9080 remove = true;
9081 switch (code)
9083 case OMP_TARGET:
9084 break;
9085 case OACC_DATA:
9086 if (TREE_CODE (TREE_TYPE (decl)) != ARRAY_TYPE)
9087 break;
9088 /* FALLTHRU */
9089 case OMP_TARGET_DATA:
9090 case OMP_TARGET_ENTER_DATA:
9091 case OMP_TARGET_EXIT_DATA:
9092 case OACC_ENTER_DATA:
9093 case OACC_EXIT_DATA:
9094 case OACC_HOST_DATA:
9095 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
9096 || (OMP_CLAUSE_MAP_KIND (c)
9097 == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
9098 /* For target {,enter ,exit }data only the array slice is
9099 mapped, but not the pointer to it. */
9100 remove = true;
9101 break;
9102 default:
9103 break;
9105 /* For Fortran, not only the pointer to the data is mapped but also
9106 the address of the pointer, the array descriptor etc.; for
9107 'exit data' - and in particular for 'delete:' - having an 'alloc:'
9108 does not make sense. Likewise, for 'update' only transferring the
9109 data itself is needed as the rest has been handled in previous
9110 directives. However, for 'exit data', the array descriptor needs
9111 to be delete; hence, we turn the MAP_TO_PSET into a MAP_DELETE.
9113 NOTE: Generally, it is not safe to perform "enter data" operations
9114 on arrays where the data *or the descriptor* may go out of scope
9115 before a corresponding "exit data" operation -- and such a
9116 descriptor may be synthesized temporarily, e.g. to pass an
9117 explicit-shape array to a function expecting an assumed-shape
9118 argument. Performing "enter data" inside the called function
9119 would thus be problematic. */
9120 if (code == OMP_TARGET_EXIT_DATA
9121 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_TO_PSET)
9122 OMP_CLAUSE_SET_MAP_KIND (c, OMP_CLAUSE_MAP_KIND (*prev_list_p)
9123 == GOMP_MAP_DELETE
9124 ? GOMP_MAP_DELETE : GOMP_MAP_RELEASE);
9125 else if ((code == OMP_TARGET_EXIT_DATA || code == OMP_TARGET_UPDATE)
9126 && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_POINTER
9127 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_TO_PSET))
9128 remove = true;
9130 if (remove)
9131 break;
9132 if (DECL_P (decl) && outer_ctx && (region_type & ORT_ACC))
9134 struct gimplify_omp_ctx *octx;
9135 for (octx = outer_ctx; octx; octx = octx->outer_context)
9137 if (octx->region_type != ORT_ACC_HOST_DATA)
9138 break;
9139 splay_tree_node n2
9140 = splay_tree_lookup (octx->variables,
9141 (splay_tree_key) decl);
9142 if (n2)
9143 error_at (OMP_CLAUSE_LOCATION (c), "variable %qE "
9144 "declared in enclosing %<host_data%> region",
9145 DECL_NAME (decl));
9148 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
9149 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
9150 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
9151 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
9152 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
9154 remove = true;
9155 break;
9157 else if ((OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
9158 || (OMP_CLAUSE_MAP_KIND (c)
9159 == GOMP_MAP_FIRSTPRIVATE_REFERENCE)
9160 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9161 && TREE_CODE (OMP_CLAUSE_SIZE (c)) != INTEGER_CST)
9163 OMP_CLAUSE_SIZE (c)
9164 = get_initialized_tmp_var (OMP_CLAUSE_SIZE (c), pre_p, NULL,
9165 false);
9166 if ((region_type & ORT_TARGET) != 0)
9167 omp_add_variable (ctx, OMP_CLAUSE_SIZE (c),
9168 GOVD_FIRSTPRIVATE | GOVD_SEEN);
9171 if (!DECL_P (decl))
9173 tree d = decl, *pd;
9174 if (TREE_CODE (d) == ARRAY_REF)
9176 while (TREE_CODE (d) == ARRAY_REF)
9177 d = TREE_OPERAND (d, 0);
9178 if (TREE_CODE (d) == COMPONENT_REF
9179 && TREE_CODE (TREE_TYPE (d)) == ARRAY_TYPE)
9180 decl = d;
9182 pd = &OMP_CLAUSE_DECL (c);
9183 if (d == decl
9184 && TREE_CODE (decl) == INDIRECT_REF
9185 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
9186 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
9187 == REFERENCE_TYPE))
9189 pd = &TREE_OPERAND (decl, 0);
9190 decl = TREE_OPERAND (decl, 0);
9192 bool indir_p = false;
9193 tree orig_decl = decl;
9194 tree decl_ref = NULL_TREE;
9195 if ((region_type & (ORT_ACC | ORT_TARGET | ORT_TARGET_DATA)) != 0
9196 && TREE_CODE (*pd) == COMPONENT_REF
9197 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH
9198 && code != OACC_UPDATE)
9200 while (TREE_CODE (decl) == COMPONENT_REF)
9202 decl = TREE_OPERAND (decl, 0);
9203 if (((TREE_CODE (decl) == MEM_REF
9204 && integer_zerop (TREE_OPERAND (decl, 1)))
9205 || INDIRECT_REF_P (decl))
9206 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
9207 == POINTER_TYPE))
9209 indir_p = true;
9210 decl = TREE_OPERAND (decl, 0);
9212 if (TREE_CODE (decl) == INDIRECT_REF
9213 && DECL_P (TREE_OPERAND (decl, 0))
9214 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
9215 == REFERENCE_TYPE))
9217 decl_ref = decl;
9218 decl = TREE_OPERAND (decl, 0);
9222 else if (TREE_CODE (decl) == COMPONENT_REF)
9224 while (TREE_CODE (decl) == COMPONENT_REF)
9225 decl = TREE_OPERAND (decl, 0);
9226 if (TREE_CODE (decl) == INDIRECT_REF
9227 && DECL_P (TREE_OPERAND (decl, 0))
9228 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
9229 == REFERENCE_TYPE))
9230 decl = TREE_OPERAND (decl, 0);
9232 if (decl != orig_decl && DECL_P (decl) && indir_p)
9234 gomp_map_kind k
9235 = ((code == OACC_EXIT_DATA || code == OMP_TARGET_EXIT_DATA)
9236 ? GOMP_MAP_DETACH : GOMP_MAP_ATTACH);
9237 /* We have a dereference of a struct member. Make this an
9238 attach/detach operation, and ensure the base pointer is
9239 mapped as a FIRSTPRIVATE_POINTER. */
9240 OMP_CLAUSE_SET_MAP_KIND (c, k);
9241 flags = GOVD_MAP | GOVD_SEEN | GOVD_EXPLICIT;
9242 tree next_clause = OMP_CLAUSE_CHAIN (c);
9243 if (k == GOMP_MAP_ATTACH
9244 && code != OACC_ENTER_DATA
9245 && code != OMP_TARGET_ENTER_DATA
9246 && (!next_clause
9247 || (OMP_CLAUSE_CODE (next_clause) != OMP_CLAUSE_MAP)
9248 || (OMP_CLAUSE_MAP_KIND (next_clause)
9249 != GOMP_MAP_POINTER)
9250 || OMP_CLAUSE_DECL (next_clause) != decl)
9251 && (!struct_deref_set
9252 || !struct_deref_set->contains (decl)))
9254 if (!struct_deref_set)
9255 struct_deref_set = new hash_set<tree> ();
9256 /* As well as the attach, we also need a
9257 FIRSTPRIVATE_POINTER clause to properly map the
9258 pointer to the struct base. */
9259 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
9260 OMP_CLAUSE_MAP);
9261 OMP_CLAUSE_SET_MAP_KIND (c2, GOMP_MAP_ALLOC);
9262 OMP_CLAUSE_MAP_MAYBE_ZERO_LENGTH_ARRAY_SECTION (c2)
9263 = 1;
9264 tree charptr_zero
9265 = build_int_cst (build_pointer_type (char_type_node),
9267 OMP_CLAUSE_DECL (c2)
9268 = build2 (MEM_REF, char_type_node,
9269 decl_ref ? decl_ref : decl, charptr_zero);
9270 OMP_CLAUSE_SIZE (c2) = size_zero_node;
9271 tree c3 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
9272 OMP_CLAUSE_MAP);
9273 OMP_CLAUSE_SET_MAP_KIND (c3,
9274 GOMP_MAP_FIRSTPRIVATE_POINTER);
9275 OMP_CLAUSE_DECL (c3) = decl;
9276 OMP_CLAUSE_SIZE (c3) = size_zero_node;
9277 tree mapgrp = *prev_list_p;
9278 *prev_list_p = c2;
9279 OMP_CLAUSE_CHAIN (c3) = mapgrp;
9280 OMP_CLAUSE_CHAIN (c2) = c3;
9282 struct_deref_set->add (decl);
9284 goto do_add_decl;
9286 /* An "attach/detach" operation on an update directive should
9287 behave as a GOMP_MAP_ALWAYS_POINTER. Beware that
9288 unlike attach or detach map kinds, GOMP_MAP_ALWAYS_POINTER
9289 depends on the previous mapping. */
9290 if (code == OACC_UPDATE
9291 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9292 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_ALWAYS_POINTER);
9293 if (DECL_P (decl)
9294 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_TO_PSET
9295 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ATTACH
9296 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_DETACH
9297 && code != OACC_UPDATE
9298 && code != OMP_TARGET_UPDATE)
9300 if (error_operand_p (decl))
9302 remove = true;
9303 break;
9306 tree stype = TREE_TYPE (decl);
9307 if (TREE_CODE (stype) == REFERENCE_TYPE)
9308 stype = TREE_TYPE (stype);
9309 if (TYPE_SIZE_UNIT (stype) == NULL
9310 || TREE_CODE (TYPE_SIZE_UNIT (stype)) != INTEGER_CST)
9312 error_at (OMP_CLAUSE_LOCATION (c),
9313 "mapping field %qE of variable length "
9314 "structure", OMP_CLAUSE_DECL (c));
9315 remove = true;
9316 break;
9319 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_POINTER
9320 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9322 /* Error recovery. */
9323 if (prev_list_p == NULL)
9325 remove = true;
9326 break;
9328 if (OMP_CLAUSE_CHAIN (*prev_list_p) != c)
9330 tree ch = OMP_CLAUSE_CHAIN (*prev_list_p);
9331 if (ch == NULL_TREE || OMP_CLAUSE_CHAIN (ch) != c)
9333 remove = true;
9334 break;
9339 poly_offset_int offset1;
9340 poly_int64 bitpos1;
9341 tree base_ref;
9343 tree base
9344 = extract_base_bit_offset (OMP_CLAUSE_DECL (c), &base_ref,
9345 &bitpos1, &offset1);
9347 gcc_assert (base == decl);
9349 splay_tree_node n
9350 = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
9351 bool ptr = (OMP_CLAUSE_MAP_KIND (c)
9352 == GOMP_MAP_ALWAYS_POINTER);
9353 bool attach_detach = (OMP_CLAUSE_MAP_KIND (c)
9354 == GOMP_MAP_ATTACH_DETACH);
9355 bool attach = OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH
9356 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_DETACH;
9357 bool has_attachments = false;
9358 /* For OpenACC, pointers in structs should trigger an
9359 attach action. */
9360 if (attach_detach
9361 && ((region_type & (ORT_ACC | ORT_TARGET | ORT_TARGET_DATA))
9362 || code == OMP_TARGET_ENTER_DATA
9363 || code == OMP_TARGET_EXIT_DATA))
9366 /* Turn a GOMP_MAP_ATTACH_DETACH clause into a
9367 GOMP_MAP_ATTACH or GOMP_MAP_DETACH clause after we
9368 have detected a case that needs a GOMP_MAP_STRUCT
9369 mapping added. */
9370 gomp_map_kind k
9371 = ((code == OACC_EXIT_DATA || code == OMP_TARGET_EXIT_DATA)
9372 ? GOMP_MAP_DETACH : GOMP_MAP_ATTACH);
9373 OMP_CLAUSE_SET_MAP_KIND (c, k);
9374 has_attachments = true;
9376 if (n == NULL || (n->value & GOVD_MAP) == 0)
9378 tree l = build_omp_clause (OMP_CLAUSE_LOCATION (c),
9379 OMP_CLAUSE_MAP);
9380 gomp_map_kind k = attach ? GOMP_MAP_FORCE_PRESENT
9381 : GOMP_MAP_STRUCT;
9383 OMP_CLAUSE_SET_MAP_KIND (l, k);
9384 if (base_ref)
9385 OMP_CLAUSE_DECL (l) = unshare_expr (base_ref);
9386 else
9387 OMP_CLAUSE_DECL (l) = decl;
9388 OMP_CLAUSE_SIZE (l)
9389 = (!attach
9390 ? size_int (1)
9391 : DECL_P (OMP_CLAUSE_DECL (l))
9392 ? DECL_SIZE_UNIT (OMP_CLAUSE_DECL (l))
9393 : TYPE_SIZE_UNIT (TREE_TYPE (OMP_CLAUSE_DECL (l))));
9394 if (struct_map_to_clause == NULL)
9395 struct_map_to_clause = new hash_map<tree, tree>;
9396 struct_map_to_clause->put (decl, l);
9397 if (ptr || attach_detach)
9399 insert_struct_comp_map (code, c, l, *prev_list_p,
9400 NULL);
9401 *prev_list_p = l;
9402 prev_list_p = NULL;
9404 else
9406 OMP_CLAUSE_CHAIN (l) = c;
9407 *list_p = l;
9408 list_p = &OMP_CLAUSE_CHAIN (l);
9410 if (base_ref && code == OMP_TARGET)
9412 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
9413 OMP_CLAUSE_MAP);
9414 enum gomp_map_kind mkind
9415 = GOMP_MAP_FIRSTPRIVATE_REFERENCE;
9416 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
9417 OMP_CLAUSE_DECL (c2) = decl;
9418 OMP_CLAUSE_SIZE (c2) = size_zero_node;
9419 OMP_CLAUSE_CHAIN (c2) = OMP_CLAUSE_CHAIN (l);
9420 OMP_CLAUSE_CHAIN (l) = c2;
9422 flags = GOVD_MAP | GOVD_EXPLICIT;
9423 if (GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c))
9424 || ptr
9425 || attach_detach)
9426 flags |= GOVD_SEEN;
9427 if (has_attachments)
9428 flags |= GOVD_MAP_HAS_ATTACHMENTS;
9429 goto do_add_decl;
9431 else if (struct_map_to_clause)
9433 tree *osc = struct_map_to_clause->get (decl);
9434 tree *sc = NULL, *scp = NULL;
9435 if (GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c))
9436 || ptr
9437 || attach_detach)
9438 n->value |= GOVD_SEEN;
9439 sc = &OMP_CLAUSE_CHAIN (*osc);
9440 if (*sc != c
9441 && (OMP_CLAUSE_MAP_KIND (*sc)
9442 == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
9443 sc = &OMP_CLAUSE_CHAIN (*sc);
9444 /* Here "prev_list_p" is the end of the inserted
9445 alloc/release nodes after the struct node, OSC. */
9446 for (; *sc != c; sc = &OMP_CLAUSE_CHAIN (*sc))
9447 if ((ptr || attach_detach) && sc == prev_list_p)
9448 break;
9449 else if (TREE_CODE (OMP_CLAUSE_DECL (*sc))
9450 != COMPONENT_REF
9451 && (TREE_CODE (OMP_CLAUSE_DECL (*sc))
9452 != INDIRECT_REF)
9453 && (TREE_CODE (OMP_CLAUSE_DECL (*sc))
9454 != ARRAY_REF))
9455 break;
9456 else
9458 tree sc_decl = OMP_CLAUSE_DECL (*sc);
9459 poly_offset_int offsetn;
9460 poly_int64 bitposn;
9461 tree base
9462 = extract_base_bit_offset (sc_decl, NULL,
9463 &bitposn, &offsetn);
9464 if (base != decl)
9465 break;
9466 if (scp)
9467 continue;
9468 if ((region_type & ORT_ACC) != 0)
9470 /* This duplicate checking code is currently only
9471 enabled for OpenACC. */
9472 tree d1 = OMP_CLAUSE_DECL (*sc);
9473 tree d2 = OMP_CLAUSE_DECL (c);
9474 while (TREE_CODE (d1) == ARRAY_REF)
9475 d1 = TREE_OPERAND (d1, 0);
9476 while (TREE_CODE (d2) == ARRAY_REF)
9477 d2 = TREE_OPERAND (d2, 0);
9478 if (TREE_CODE (d1) == INDIRECT_REF)
9479 d1 = TREE_OPERAND (d1, 0);
9480 if (TREE_CODE (d2) == INDIRECT_REF)
9481 d2 = TREE_OPERAND (d2, 0);
9482 while (TREE_CODE (d1) == COMPONENT_REF)
9483 if (TREE_CODE (d2) == COMPONENT_REF
9484 && TREE_OPERAND (d1, 1)
9485 == TREE_OPERAND (d2, 1))
9487 d1 = TREE_OPERAND (d1, 0);
9488 d2 = TREE_OPERAND (d2, 0);
9490 else
9491 break;
9492 if (d1 == d2)
9494 error_at (OMP_CLAUSE_LOCATION (c),
9495 "%qE appears more than once in map "
9496 "clauses", OMP_CLAUSE_DECL (c));
9497 remove = true;
9498 break;
9501 if (maybe_lt (offset1, offsetn)
9502 || (known_eq (offset1, offsetn)
9503 && maybe_lt (bitpos1, bitposn)))
9505 if (ptr || attach_detach)
9506 scp = sc;
9507 else
9508 break;
9511 if (remove)
9512 break;
9513 if (!attach)
9514 OMP_CLAUSE_SIZE (*osc)
9515 = size_binop (PLUS_EXPR, OMP_CLAUSE_SIZE (*osc),
9516 size_one_node);
9517 if (ptr || attach_detach)
9519 tree cl = insert_struct_comp_map (code, c, NULL,
9520 *prev_list_p, scp);
9521 if (sc == prev_list_p)
9523 *sc = cl;
9524 prev_list_p = NULL;
9526 else
9528 *prev_list_p = OMP_CLAUSE_CHAIN (c);
9529 list_p = prev_list_p;
9530 prev_list_p = NULL;
9531 OMP_CLAUSE_CHAIN (c) = *sc;
9532 *sc = cl;
9533 continue;
9536 else if (*sc != c)
9538 *list_p = OMP_CLAUSE_CHAIN (c);
9539 OMP_CLAUSE_CHAIN (c) = *sc;
9540 *sc = c;
9541 continue;
9545 else if ((code == OACC_ENTER_DATA
9546 || code == OACC_EXIT_DATA
9547 || code == OACC_DATA
9548 || code == OACC_PARALLEL
9549 || code == OACC_KERNELS
9550 || code == OACC_SERIAL)
9551 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9553 gomp_map_kind k = (code == OACC_EXIT_DATA
9554 ? GOMP_MAP_DETACH : GOMP_MAP_ATTACH);
9555 OMP_CLAUSE_SET_MAP_KIND (c, k);
9558 if (gimplify_expr (pd, pre_p, NULL, is_gimple_lvalue, fb_lvalue)
9559 == GS_ERROR)
9561 remove = true;
9562 break;
9565 if (!remove
9566 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ALWAYS_POINTER
9567 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ATTACH_DETACH
9568 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_TO_PSET
9569 && OMP_CLAUSE_CHAIN (c)
9570 && OMP_CLAUSE_CODE (OMP_CLAUSE_CHAIN (c)) == OMP_CLAUSE_MAP
9571 && ((OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (c))
9572 == GOMP_MAP_ALWAYS_POINTER)
9573 || (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (c))
9574 == GOMP_MAP_ATTACH_DETACH)
9575 || (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (c))
9576 == GOMP_MAP_TO_PSET)))
9577 prev_list_p = list_p;
9579 break;
9581 else
9583 /* DECL_P (decl) == true */
9584 tree *sc;
9585 if (struct_map_to_clause
9586 && (sc = struct_map_to_clause->get (decl)) != NULL
9587 && OMP_CLAUSE_MAP_KIND (*sc) == GOMP_MAP_STRUCT
9588 && decl == OMP_CLAUSE_DECL (*sc))
9590 /* We have found a map of the whole structure after a
9591 leading GOMP_MAP_STRUCT has been created, so refill the
9592 leading clause into a map of the whole structure
9593 variable, and remove the current one.
9594 TODO: we should be able to remove some maps of the
9595 following structure element maps if they are of
9596 compatible TO/FROM/ALLOC type. */
9597 OMP_CLAUSE_SET_MAP_KIND (*sc, OMP_CLAUSE_MAP_KIND (c));
9598 OMP_CLAUSE_SIZE (*sc) = unshare_expr (OMP_CLAUSE_SIZE (c));
9599 remove = true;
9600 break;
9603 flags = GOVD_MAP | GOVD_EXPLICIT;
9604 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_TO
9605 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_TOFROM)
9606 flags |= GOVD_MAP_ALWAYS_TO;
9608 if ((code == OMP_TARGET
9609 || code == OMP_TARGET_DATA
9610 || code == OMP_TARGET_ENTER_DATA
9611 || code == OMP_TARGET_EXIT_DATA)
9612 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9614 for (struct gimplify_omp_ctx *octx = outer_ctx; octx;
9615 octx = octx->outer_context)
9617 splay_tree_node n
9618 = splay_tree_lookup (octx->variables,
9619 (splay_tree_key) OMP_CLAUSE_DECL (c));
9620 /* If this is contained in an outer OpenMP region as a
9621 firstprivate value, remove the attach/detach. */
9622 if (n && (n->value & GOVD_FIRSTPRIVATE))
9624 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FIRSTPRIVATE_POINTER);
9625 goto do_add;
9629 enum gomp_map_kind map_kind = (code == OMP_TARGET_EXIT_DATA
9630 ? GOMP_MAP_DETACH
9631 : GOMP_MAP_ATTACH);
9632 OMP_CLAUSE_SET_MAP_KIND (c, map_kind);
9635 goto do_add;
9637 case OMP_CLAUSE_AFFINITY:
9638 gimplify_omp_affinity (list_p, pre_p);
9639 remove = true;
9640 break;
9641 case OMP_CLAUSE_DEPEND:
9642 if (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SINK)
9644 tree deps = OMP_CLAUSE_DECL (c);
9645 while (deps && TREE_CODE (deps) == TREE_LIST)
9647 if (TREE_CODE (TREE_PURPOSE (deps)) == TRUNC_DIV_EXPR
9648 && DECL_P (TREE_OPERAND (TREE_PURPOSE (deps), 1)))
9649 gimplify_expr (&TREE_OPERAND (TREE_PURPOSE (deps), 1),
9650 pre_p, NULL, is_gimple_val, fb_rvalue);
9651 deps = TREE_CHAIN (deps);
9653 break;
9655 else if (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SOURCE)
9656 break;
9657 if (handled_depend_iterators == -1)
9658 handled_depend_iterators = gimplify_omp_depend (list_p, pre_p);
9659 if (handled_depend_iterators)
9661 if (handled_depend_iterators == 2)
9662 remove = true;
9663 break;
9665 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
9667 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
9668 NULL, is_gimple_val, fb_rvalue);
9669 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
9671 if (error_operand_p (OMP_CLAUSE_DECL (c)))
9673 remove = true;
9674 break;
9676 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (OMP_CLAUSE_DECL (c));
9677 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
9678 is_gimple_val, fb_rvalue) == GS_ERROR)
9680 remove = true;
9681 break;
9683 if (code == OMP_TASK)
9684 ctx->has_depend = true;
9685 break;
9687 case OMP_CLAUSE_TO:
9688 case OMP_CLAUSE_FROM:
9689 case OMP_CLAUSE__CACHE_:
9690 decl = OMP_CLAUSE_DECL (c);
9691 if (error_operand_p (decl))
9693 remove = true;
9694 break;
9696 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
9697 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
9698 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
9699 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
9700 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
9702 remove = true;
9703 break;
9705 if (!DECL_P (decl))
9707 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p,
9708 NULL, is_gimple_lvalue, fb_lvalue)
9709 == GS_ERROR)
9711 remove = true;
9712 break;
9714 break;
9716 goto do_notice;
9718 case OMP_CLAUSE_USE_DEVICE_PTR:
9719 case OMP_CLAUSE_USE_DEVICE_ADDR:
9720 flags = GOVD_EXPLICIT;
9721 goto do_add;
9723 case OMP_CLAUSE_IS_DEVICE_PTR:
9724 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
9725 goto do_add;
9727 do_add:
9728 decl = OMP_CLAUSE_DECL (c);
9729 do_add_decl:
9730 if (error_operand_p (decl))
9732 remove = true;
9733 break;
9735 if (DECL_NAME (decl) == NULL_TREE && (flags & GOVD_SHARED) == 0)
9737 tree t = omp_member_access_dummy_var (decl);
9738 if (t)
9740 tree v = DECL_VALUE_EXPR (decl);
9741 DECL_NAME (decl) = DECL_NAME (TREE_OPERAND (v, 1));
9742 if (outer_ctx)
9743 omp_notice_variable (outer_ctx, t, true);
9746 if (code == OACC_DATA
9747 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP
9748 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
9749 flags |= GOVD_MAP_0LEN_ARRAY;
9750 omp_add_variable (ctx, decl, flags);
9751 if ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
9752 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_IN_REDUCTION
9753 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_TASK_REDUCTION)
9754 && OMP_CLAUSE_REDUCTION_PLACEHOLDER (c))
9756 omp_add_variable (ctx, OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
9757 GOVD_LOCAL | GOVD_SEEN);
9758 if (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c)
9759 && walk_tree (&OMP_CLAUSE_REDUCTION_INIT (c),
9760 find_decl_expr,
9761 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
9762 NULL) == NULL_TREE)
9763 omp_add_variable (ctx,
9764 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
9765 GOVD_LOCAL | GOVD_SEEN);
9766 gimplify_omp_ctxp = ctx;
9767 push_gimplify_context ();
9769 OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c) = NULL;
9770 OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c) = NULL;
9772 gimplify_and_add (OMP_CLAUSE_REDUCTION_INIT (c),
9773 &OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c));
9774 pop_gimplify_context
9775 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c)));
9776 push_gimplify_context ();
9777 gimplify_and_add (OMP_CLAUSE_REDUCTION_MERGE (c),
9778 &OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c));
9779 pop_gimplify_context
9780 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c)));
9781 OMP_CLAUSE_REDUCTION_INIT (c) = NULL_TREE;
9782 OMP_CLAUSE_REDUCTION_MERGE (c) = NULL_TREE;
9784 gimplify_omp_ctxp = outer_ctx;
9786 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
9787 && OMP_CLAUSE_LASTPRIVATE_STMT (c))
9789 gimplify_omp_ctxp = ctx;
9790 push_gimplify_context ();
9791 if (TREE_CODE (OMP_CLAUSE_LASTPRIVATE_STMT (c)) != BIND_EXPR)
9793 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
9794 NULL, NULL);
9795 TREE_SIDE_EFFECTS (bind) = 1;
9796 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LASTPRIVATE_STMT (c);
9797 OMP_CLAUSE_LASTPRIVATE_STMT (c) = bind;
9799 gimplify_and_add (OMP_CLAUSE_LASTPRIVATE_STMT (c),
9800 &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c));
9801 pop_gimplify_context
9802 (gimple_seq_first_stmt (OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c)));
9803 OMP_CLAUSE_LASTPRIVATE_STMT (c) = NULL_TREE;
9805 gimplify_omp_ctxp = outer_ctx;
9807 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
9808 && OMP_CLAUSE_LINEAR_STMT (c))
9810 gimplify_omp_ctxp = ctx;
9811 push_gimplify_context ();
9812 if (TREE_CODE (OMP_CLAUSE_LINEAR_STMT (c)) != BIND_EXPR)
9814 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
9815 NULL, NULL);
9816 TREE_SIDE_EFFECTS (bind) = 1;
9817 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LINEAR_STMT (c);
9818 OMP_CLAUSE_LINEAR_STMT (c) = bind;
9820 gimplify_and_add (OMP_CLAUSE_LINEAR_STMT (c),
9821 &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c));
9822 pop_gimplify_context
9823 (gimple_seq_first_stmt (OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c)));
9824 OMP_CLAUSE_LINEAR_STMT (c) = NULL_TREE;
9826 gimplify_omp_ctxp = outer_ctx;
9828 if (notice_outer)
9829 goto do_notice;
9830 break;
9832 case OMP_CLAUSE_COPYIN:
9833 case OMP_CLAUSE_COPYPRIVATE:
9834 decl = OMP_CLAUSE_DECL (c);
9835 if (error_operand_p (decl))
9837 remove = true;
9838 break;
9840 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_COPYPRIVATE
9841 && !remove
9842 && !omp_check_private (ctx, decl, true))
9844 remove = true;
9845 if (is_global_var (decl))
9847 if (DECL_THREAD_LOCAL_P (decl))
9848 remove = false;
9849 else if (DECL_HAS_VALUE_EXPR_P (decl))
9851 tree value = get_base_address (DECL_VALUE_EXPR (decl));
9853 if (value
9854 && DECL_P (value)
9855 && DECL_THREAD_LOCAL_P (value))
9856 remove = false;
9859 if (remove)
9860 error_at (OMP_CLAUSE_LOCATION (c),
9861 "copyprivate variable %qE is not threadprivate"
9862 " or private in outer context", DECL_NAME (decl));
9864 do_notice:
9865 if ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
9866 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_FIRSTPRIVATE
9867 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE)
9868 && outer_ctx
9869 && ((region_type & ORT_TASKLOOP) == ORT_TASKLOOP
9870 || (region_type == ORT_WORKSHARE
9871 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
9872 && (OMP_CLAUSE_REDUCTION_INSCAN (c)
9873 || code == OMP_LOOP)))
9874 && (outer_ctx->region_type == ORT_COMBINED_PARALLEL
9875 || (code == OMP_LOOP
9876 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
9877 && ((outer_ctx->region_type & ORT_COMBINED_TEAMS)
9878 == ORT_COMBINED_TEAMS))))
9880 splay_tree_node on
9881 = splay_tree_lookup (outer_ctx->variables,
9882 (splay_tree_key)decl);
9883 if (on == NULL || (on->value & GOVD_DATA_SHARE_CLASS) == 0)
9885 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
9886 && TREE_CODE (OMP_CLAUSE_DECL (c)) == MEM_REF
9887 && (TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE
9888 || (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
9889 && (TREE_CODE (TREE_TYPE (TREE_TYPE (decl)))
9890 == POINTER_TYPE))))
9891 omp_firstprivatize_variable (outer_ctx, decl);
9892 else
9894 omp_add_variable (outer_ctx, decl,
9895 GOVD_SEEN | GOVD_SHARED);
9896 if (outer_ctx->outer_context)
9897 omp_notice_variable (outer_ctx->outer_context, decl,
9898 true);
9902 if (outer_ctx)
9903 omp_notice_variable (outer_ctx, decl, true);
9904 if (check_non_private
9905 && region_type == ORT_WORKSHARE
9906 && (OMP_CLAUSE_CODE (c) != OMP_CLAUSE_REDUCTION
9907 || decl == OMP_CLAUSE_DECL (c)
9908 || (TREE_CODE (OMP_CLAUSE_DECL (c)) == MEM_REF
9909 && (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c), 0))
9910 == ADDR_EXPR
9911 || (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c), 0))
9912 == POINTER_PLUS_EXPR
9913 && (TREE_CODE (TREE_OPERAND (TREE_OPERAND
9914 (OMP_CLAUSE_DECL (c), 0), 0))
9915 == ADDR_EXPR)))))
9916 && omp_check_private (ctx, decl, false))
9918 error ("%s variable %qE is private in outer context",
9919 check_non_private, DECL_NAME (decl));
9920 remove = true;
9922 break;
9924 case OMP_CLAUSE_DETACH:
9925 flags = GOVD_FIRSTPRIVATE | GOVD_SEEN;
9926 goto do_add;
9928 case OMP_CLAUSE_IF:
9929 if (OMP_CLAUSE_IF_MODIFIER (c) != ERROR_MARK
9930 && OMP_CLAUSE_IF_MODIFIER (c) != code)
9932 const char *p[2];
9933 for (int i = 0; i < 2; i++)
9934 switch (i ? OMP_CLAUSE_IF_MODIFIER (c) : code)
9936 case VOID_CST: p[i] = "cancel"; break;
9937 case OMP_PARALLEL: p[i] = "parallel"; break;
9938 case OMP_SIMD: p[i] = "simd"; break;
9939 case OMP_TASK: p[i] = "task"; break;
9940 case OMP_TASKLOOP: p[i] = "taskloop"; break;
9941 case OMP_TARGET_DATA: p[i] = "target data"; break;
9942 case OMP_TARGET: p[i] = "target"; break;
9943 case OMP_TARGET_UPDATE: p[i] = "target update"; break;
9944 case OMP_TARGET_ENTER_DATA:
9945 p[i] = "target enter data"; break;
9946 case OMP_TARGET_EXIT_DATA: p[i] = "target exit data"; break;
9947 default: gcc_unreachable ();
9949 error_at (OMP_CLAUSE_LOCATION (c),
9950 "expected %qs %<if%> clause modifier rather than %qs",
9951 p[0], p[1]);
9952 remove = true;
9954 /* Fall through. */
9956 case OMP_CLAUSE_FINAL:
9957 OMP_CLAUSE_OPERAND (c, 0)
9958 = gimple_boolify (OMP_CLAUSE_OPERAND (c, 0));
9959 /* Fall through. */
9961 case OMP_CLAUSE_SCHEDULE:
9962 case OMP_CLAUSE_NUM_THREADS:
9963 case OMP_CLAUSE_NUM_TEAMS:
9964 case OMP_CLAUSE_THREAD_LIMIT:
9965 case OMP_CLAUSE_DIST_SCHEDULE:
9966 case OMP_CLAUSE_DEVICE:
9967 case OMP_CLAUSE_PRIORITY:
9968 case OMP_CLAUSE_GRAINSIZE:
9969 case OMP_CLAUSE_NUM_TASKS:
9970 case OMP_CLAUSE_HINT:
9971 case OMP_CLAUSE_ASYNC:
9972 case OMP_CLAUSE_WAIT:
9973 case OMP_CLAUSE_NUM_GANGS:
9974 case OMP_CLAUSE_NUM_WORKERS:
9975 case OMP_CLAUSE_VECTOR_LENGTH:
9976 case OMP_CLAUSE_WORKER:
9977 case OMP_CLAUSE_VECTOR:
9978 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 0), pre_p, NULL,
9979 is_gimple_val, fb_rvalue) == GS_ERROR)
9980 remove = true;
9981 break;
9983 case OMP_CLAUSE_GANG:
9984 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 0), pre_p, NULL,
9985 is_gimple_val, fb_rvalue) == GS_ERROR)
9986 remove = true;
9987 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 1), pre_p, NULL,
9988 is_gimple_val, fb_rvalue) == GS_ERROR)
9989 remove = true;
9990 break;
9992 case OMP_CLAUSE_NOWAIT:
9993 nowait = 1;
9994 break;
9996 case OMP_CLAUSE_ORDERED:
9997 case OMP_CLAUSE_UNTIED:
9998 case OMP_CLAUSE_COLLAPSE:
9999 case OMP_CLAUSE_TILE:
10000 case OMP_CLAUSE_AUTO:
10001 case OMP_CLAUSE_SEQ:
10002 case OMP_CLAUSE_INDEPENDENT:
10003 case OMP_CLAUSE_MERGEABLE:
10004 case OMP_CLAUSE_PROC_BIND:
10005 case OMP_CLAUSE_SAFELEN:
10006 case OMP_CLAUSE_SIMDLEN:
10007 case OMP_CLAUSE_NOGROUP:
10008 case OMP_CLAUSE_THREADS:
10009 case OMP_CLAUSE_SIMD:
10010 case OMP_CLAUSE_BIND:
10011 case OMP_CLAUSE_IF_PRESENT:
10012 case OMP_CLAUSE_FINALIZE:
10013 break;
10015 case OMP_CLAUSE_ORDER:
10016 ctx->order_concurrent = true;
10017 break;
10019 case OMP_CLAUSE_DEFAULTMAP:
10020 enum gimplify_defaultmap_kind gdmkmin, gdmkmax;
10021 switch (OMP_CLAUSE_DEFAULTMAP_CATEGORY (c))
10023 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_UNSPECIFIED:
10024 gdmkmin = GDMK_SCALAR;
10025 gdmkmax = GDMK_POINTER;
10026 break;
10027 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_SCALAR:
10028 gdmkmin = gdmkmax = GDMK_SCALAR;
10029 break;
10030 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_AGGREGATE:
10031 gdmkmin = gdmkmax = GDMK_AGGREGATE;
10032 break;
10033 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_ALLOCATABLE:
10034 gdmkmin = gdmkmax = GDMK_ALLOCATABLE;
10035 break;
10036 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_POINTER:
10037 gdmkmin = gdmkmax = GDMK_POINTER;
10038 break;
10039 default:
10040 gcc_unreachable ();
10042 for (int gdmk = gdmkmin; gdmk <= gdmkmax; gdmk++)
10043 switch (OMP_CLAUSE_DEFAULTMAP_BEHAVIOR (c))
10045 case OMP_CLAUSE_DEFAULTMAP_ALLOC:
10046 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_ALLOC_ONLY;
10047 break;
10048 case OMP_CLAUSE_DEFAULTMAP_TO:
10049 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_TO_ONLY;
10050 break;
10051 case OMP_CLAUSE_DEFAULTMAP_FROM:
10052 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_FROM_ONLY;
10053 break;
10054 case OMP_CLAUSE_DEFAULTMAP_TOFROM:
10055 ctx->defaultmap[gdmk] = GOVD_MAP;
10056 break;
10057 case OMP_CLAUSE_DEFAULTMAP_FIRSTPRIVATE:
10058 ctx->defaultmap[gdmk] = GOVD_FIRSTPRIVATE;
10059 break;
10060 case OMP_CLAUSE_DEFAULTMAP_NONE:
10061 ctx->defaultmap[gdmk] = 0;
10062 break;
10063 case OMP_CLAUSE_DEFAULTMAP_DEFAULT:
10064 switch (gdmk)
10066 case GDMK_SCALAR:
10067 ctx->defaultmap[gdmk] = GOVD_FIRSTPRIVATE;
10068 break;
10069 case GDMK_AGGREGATE:
10070 case GDMK_ALLOCATABLE:
10071 ctx->defaultmap[gdmk] = GOVD_MAP;
10072 break;
10073 case GDMK_POINTER:
10074 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_0LEN_ARRAY;
10075 break;
10076 default:
10077 gcc_unreachable ();
10079 break;
10080 default:
10081 gcc_unreachable ();
10083 break;
10085 case OMP_CLAUSE_ALIGNED:
10086 decl = OMP_CLAUSE_DECL (c);
10087 if (error_operand_p (decl))
10089 remove = true;
10090 break;
10092 if (gimplify_expr (&OMP_CLAUSE_ALIGNED_ALIGNMENT (c), pre_p, NULL,
10093 is_gimple_val, fb_rvalue) == GS_ERROR)
10095 remove = true;
10096 break;
10098 if (!is_global_var (decl)
10099 && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
10100 omp_add_variable (ctx, decl, GOVD_ALIGNED);
10101 break;
10103 case OMP_CLAUSE_NONTEMPORAL:
10104 decl = OMP_CLAUSE_DECL (c);
10105 if (error_operand_p (decl))
10107 remove = true;
10108 break;
10110 omp_add_variable (ctx, decl, GOVD_NONTEMPORAL);
10111 break;
10113 case OMP_CLAUSE_ALLOCATE:
10114 decl = OMP_CLAUSE_DECL (c);
10115 if (error_operand_p (decl))
10117 remove = true;
10118 break;
10120 if (gimplify_expr (&OMP_CLAUSE_ALLOCATE_ALLOCATOR (c), pre_p, NULL,
10121 is_gimple_val, fb_rvalue) == GS_ERROR)
10123 remove = true;
10124 break;
10126 else if (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c) == NULL_TREE
10127 || (TREE_CODE (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c))
10128 == INTEGER_CST))
10130 else if (code == OMP_TASKLOOP
10131 || !DECL_P (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)))
10132 OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
10133 = get_initialized_tmp_var (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
10134 pre_p, NULL, false);
10135 break;
10137 case OMP_CLAUSE_DEFAULT:
10138 ctx->default_kind = OMP_CLAUSE_DEFAULT_KIND (c);
10139 break;
10141 case OMP_CLAUSE_INCLUSIVE:
10142 case OMP_CLAUSE_EXCLUSIVE:
10143 decl = OMP_CLAUSE_DECL (c);
10145 splay_tree_node n = splay_tree_lookup (outer_ctx->variables,
10146 (splay_tree_key) decl);
10147 if (n == NULL || (n->value & GOVD_REDUCTION) == 0)
10149 error_at (OMP_CLAUSE_LOCATION (c),
10150 "%qD specified in %qs clause but not in %<inscan%> "
10151 "%<reduction%> clause on the containing construct",
10152 decl, omp_clause_code_name[OMP_CLAUSE_CODE (c)]);
10153 remove = true;
10155 else
10157 n->value |= GOVD_REDUCTION_INSCAN;
10158 if (outer_ctx->region_type == ORT_SIMD
10159 && outer_ctx->outer_context
10160 && outer_ctx->outer_context->region_type == ORT_WORKSHARE)
10162 n = splay_tree_lookup (outer_ctx->outer_context->variables,
10163 (splay_tree_key) decl);
10164 if (n && (n->value & GOVD_REDUCTION) != 0)
10165 n->value |= GOVD_REDUCTION_INSCAN;
10169 break;
10171 default:
10172 gcc_unreachable ();
10175 if (code == OACC_DATA
10176 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP
10177 && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
10178 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
10179 remove = true;
10180 if (remove)
10181 *list_p = OMP_CLAUSE_CHAIN (c);
10182 else
10183 list_p = &OMP_CLAUSE_CHAIN (c);
10186 ctx->clauses = *orig_list_p;
10187 gimplify_omp_ctxp = ctx;
10188 if (struct_map_to_clause)
10189 delete struct_map_to_clause;
10190 if (struct_deref_set)
10191 delete struct_deref_set;
10194 /* Return true if DECL is a candidate for shared to firstprivate
10195 optimization. We only consider non-addressable scalars, not
10196 too big, and not references. */
10198 static bool
10199 omp_shared_to_firstprivate_optimizable_decl_p (tree decl)
10201 if (TREE_ADDRESSABLE (decl))
10202 return false;
10203 tree type = TREE_TYPE (decl);
10204 if (!is_gimple_reg_type (type)
10205 || TREE_CODE (type) == REFERENCE_TYPE
10206 || TREE_ADDRESSABLE (type))
10207 return false;
10208 /* Don't optimize too large decls, as each thread/task will have
10209 its own. */
10210 HOST_WIDE_INT len = int_size_in_bytes (type);
10211 if (len == -1 || len > 4 * POINTER_SIZE / BITS_PER_UNIT)
10212 return false;
10213 if (lang_hooks.decls.omp_privatize_by_reference (decl))
10214 return false;
10215 return true;
10218 /* Helper function of omp_find_stores_op and gimplify_adjust_omp_clauses*.
10219 For omp_shared_to_firstprivate_optimizable_decl_p decl mark it as
10220 GOVD_WRITTEN in outer contexts. */
10222 static void
10223 omp_mark_stores (struct gimplify_omp_ctx *ctx, tree decl)
10225 for (; ctx; ctx = ctx->outer_context)
10227 splay_tree_node n = splay_tree_lookup (ctx->variables,
10228 (splay_tree_key) decl);
10229 if (n == NULL)
10230 continue;
10231 else if (n->value & GOVD_SHARED)
10233 n->value |= GOVD_WRITTEN;
10234 return;
10236 else if (n->value & GOVD_DATA_SHARE_CLASS)
10237 return;
10241 /* Helper callback for walk_gimple_seq to discover possible stores
10242 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
10243 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
10244 for those. */
10246 static tree
10247 omp_find_stores_op (tree *tp, int *walk_subtrees, void *data)
10249 struct walk_stmt_info *wi = (struct walk_stmt_info *) data;
10251 *walk_subtrees = 0;
10252 if (!wi->is_lhs)
10253 return NULL_TREE;
10255 tree op = *tp;
10258 if (handled_component_p (op))
10259 op = TREE_OPERAND (op, 0);
10260 else if ((TREE_CODE (op) == MEM_REF || TREE_CODE (op) == TARGET_MEM_REF)
10261 && TREE_CODE (TREE_OPERAND (op, 0)) == ADDR_EXPR)
10262 op = TREE_OPERAND (TREE_OPERAND (op, 0), 0);
10263 else
10264 break;
10266 while (1);
10267 if (!DECL_P (op) || !omp_shared_to_firstprivate_optimizable_decl_p (op))
10268 return NULL_TREE;
10270 omp_mark_stores (gimplify_omp_ctxp, op);
10271 return NULL_TREE;
10274 /* Helper callback for walk_gimple_seq to discover possible stores
10275 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
10276 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
10277 for those. */
10279 static tree
10280 omp_find_stores_stmt (gimple_stmt_iterator *gsi_p,
10281 bool *handled_ops_p,
10282 struct walk_stmt_info *wi)
10284 gimple *stmt = gsi_stmt (*gsi_p);
10285 switch (gimple_code (stmt))
10287 /* Don't recurse on OpenMP constructs for which
10288 gimplify_adjust_omp_clauses already handled the bodies,
10289 except handle gimple_omp_for_pre_body. */
10290 case GIMPLE_OMP_FOR:
10291 *handled_ops_p = true;
10292 if (gimple_omp_for_pre_body (stmt))
10293 walk_gimple_seq (gimple_omp_for_pre_body (stmt),
10294 omp_find_stores_stmt, omp_find_stores_op, wi);
10295 break;
10296 case GIMPLE_OMP_PARALLEL:
10297 case GIMPLE_OMP_TASK:
10298 case GIMPLE_OMP_SECTIONS:
10299 case GIMPLE_OMP_SINGLE:
10300 case GIMPLE_OMP_TARGET:
10301 case GIMPLE_OMP_TEAMS:
10302 case GIMPLE_OMP_CRITICAL:
10303 *handled_ops_p = true;
10304 break;
10305 default:
10306 break;
10308 return NULL_TREE;
10311 struct gimplify_adjust_omp_clauses_data
10313 tree *list_p;
10314 gimple_seq *pre_p;
10317 /* For all variables that were not actually used within the context,
10318 remove PRIVATE, SHARED, and FIRSTPRIVATE clauses. */
10320 static int
10321 gimplify_adjust_omp_clauses_1 (splay_tree_node n, void *data)
10323 tree *list_p = ((struct gimplify_adjust_omp_clauses_data *) data)->list_p;
10324 gimple_seq *pre_p
10325 = ((struct gimplify_adjust_omp_clauses_data *) data)->pre_p;
10326 tree decl = (tree) n->key;
10327 unsigned flags = n->value;
10328 enum omp_clause_code code;
10329 tree clause;
10330 bool private_debug;
10332 if (gimplify_omp_ctxp->region_type == ORT_COMBINED_PARALLEL
10333 && (flags & GOVD_LASTPRIVATE_CONDITIONAL) != 0)
10334 flags = GOVD_SHARED | GOVD_SEEN | GOVD_WRITTEN;
10335 if (flags & (GOVD_EXPLICIT | GOVD_LOCAL))
10336 return 0;
10337 if ((flags & GOVD_SEEN) == 0)
10338 return 0;
10339 if ((flags & GOVD_MAP_HAS_ATTACHMENTS) != 0)
10340 return 0;
10341 if (flags & GOVD_DEBUG_PRIVATE)
10343 gcc_assert ((flags & GOVD_DATA_SHARE_CLASS) == GOVD_SHARED);
10344 private_debug = true;
10346 else if (flags & GOVD_MAP)
10347 private_debug = false;
10348 else
10349 private_debug
10350 = lang_hooks.decls.omp_private_debug_clause (decl,
10351 !!(flags & GOVD_SHARED));
10352 if (private_debug)
10353 code = OMP_CLAUSE_PRIVATE;
10354 else if (flags & GOVD_MAP)
10356 code = OMP_CLAUSE_MAP;
10357 if ((gimplify_omp_ctxp->region_type & ORT_ACC) == 0
10358 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl))))
10360 error ("%<_Atomic%> %qD in implicit %<map%> clause", decl);
10361 return 0;
10363 if (VAR_P (decl)
10364 && DECL_IN_CONSTANT_POOL (decl)
10365 && !lookup_attribute ("omp declare target",
10366 DECL_ATTRIBUTES (decl)))
10368 tree id = get_identifier ("omp declare target");
10369 DECL_ATTRIBUTES (decl)
10370 = tree_cons (id, NULL_TREE, DECL_ATTRIBUTES (decl));
10371 varpool_node *node = varpool_node::get (decl);
10372 if (node)
10374 node->offloadable = 1;
10375 if (ENABLE_OFFLOADING)
10376 g->have_offload = true;
10380 else if (flags & GOVD_SHARED)
10382 if (is_global_var (decl))
10384 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
10385 while (ctx != NULL)
10387 splay_tree_node on
10388 = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10389 if (on && (on->value & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
10390 | GOVD_PRIVATE | GOVD_REDUCTION
10391 | GOVD_LINEAR | GOVD_MAP)) != 0)
10392 break;
10393 ctx = ctx->outer_context;
10395 if (ctx == NULL)
10396 return 0;
10398 code = OMP_CLAUSE_SHARED;
10399 /* Don't optimize shared into firstprivate for read-only vars
10400 on tasks with depend clause, we shouldn't try to copy them
10401 until the dependencies are satisfied. */
10402 if (gimplify_omp_ctxp->has_depend)
10403 flags |= GOVD_WRITTEN;
10405 else if (flags & GOVD_PRIVATE)
10406 code = OMP_CLAUSE_PRIVATE;
10407 else if (flags & GOVD_FIRSTPRIVATE)
10409 code = OMP_CLAUSE_FIRSTPRIVATE;
10410 if ((gimplify_omp_ctxp->region_type & ORT_TARGET)
10411 && (gimplify_omp_ctxp->region_type & ORT_ACC) == 0
10412 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl))))
10414 error ("%<_Atomic%> %qD in implicit %<firstprivate%> clause on "
10415 "%<target%> construct", decl);
10416 return 0;
10419 else if (flags & GOVD_LASTPRIVATE)
10420 code = OMP_CLAUSE_LASTPRIVATE;
10421 else if (flags & (GOVD_ALIGNED | GOVD_NONTEMPORAL))
10422 return 0;
10423 else if (flags & GOVD_CONDTEMP)
10425 code = OMP_CLAUSE__CONDTEMP_;
10426 gimple_add_tmp_var (decl);
10428 else
10429 gcc_unreachable ();
10431 if (((flags & GOVD_LASTPRIVATE)
10432 || (code == OMP_CLAUSE_SHARED && (flags & GOVD_WRITTEN)))
10433 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
10434 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
10436 tree chain = *list_p;
10437 clause = build_omp_clause (input_location, code);
10438 OMP_CLAUSE_DECL (clause) = decl;
10439 OMP_CLAUSE_CHAIN (clause) = chain;
10440 if (private_debug)
10441 OMP_CLAUSE_PRIVATE_DEBUG (clause) = 1;
10442 else if (code == OMP_CLAUSE_PRIVATE && (flags & GOVD_PRIVATE_OUTER_REF))
10443 OMP_CLAUSE_PRIVATE_OUTER_REF (clause) = 1;
10444 else if (code == OMP_CLAUSE_SHARED
10445 && (flags & GOVD_WRITTEN) == 0
10446 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
10447 OMP_CLAUSE_SHARED_READONLY (clause) = 1;
10448 else if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_EXPLICIT) == 0)
10449 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (clause) = 1;
10450 else if (code == OMP_CLAUSE_MAP && (flags & GOVD_MAP_0LEN_ARRAY) != 0)
10452 tree nc = build_omp_clause (input_location, OMP_CLAUSE_MAP);
10453 OMP_CLAUSE_DECL (nc) = decl;
10454 if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
10455 && TREE_CODE (TREE_TYPE (TREE_TYPE (decl))) == POINTER_TYPE)
10456 OMP_CLAUSE_DECL (clause)
10457 = build_simple_mem_ref_loc (input_location, decl);
10458 OMP_CLAUSE_DECL (clause)
10459 = build2 (MEM_REF, char_type_node, OMP_CLAUSE_DECL (clause),
10460 build_int_cst (build_pointer_type (char_type_node), 0));
10461 OMP_CLAUSE_SIZE (clause) = size_zero_node;
10462 OMP_CLAUSE_SIZE (nc) = size_zero_node;
10463 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_ALLOC);
10464 OMP_CLAUSE_MAP_MAYBE_ZERO_LENGTH_ARRAY_SECTION (clause) = 1;
10465 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_POINTER);
10466 OMP_CLAUSE_CHAIN (nc) = chain;
10467 OMP_CLAUSE_CHAIN (clause) = nc;
10468 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10469 gimplify_omp_ctxp = ctx->outer_context;
10470 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (clause), 0),
10471 pre_p, NULL, is_gimple_val, fb_rvalue);
10472 gimplify_omp_ctxp = ctx;
10474 else if (code == OMP_CLAUSE_MAP)
10476 int kind;
10477 /* Not all combinations of these GOVD_MAP flags are actually valid. */
10478 switch (flags & (GOVD_MAP_TO_ONLY
10479 | GOVD_MAP_FORCE
10480 | GOVD_MAP_FORCE_PRESENT
10481 | GOVD_MAP_ALLOC_ONLY
10482 | GOVD_MAP_FROM_ONLY))
10484 case 0:
10485 kind = GOMP_MAP_TOFROM;
10486 break;
10487 case GOVD_MAP_FORCE:
10488 kind = GOMP_MAP_TOFROM | GOMP_MAP_FLAG_FORCE;
10489 break;
10490 case GOVD_MAP_TO_ONLY:
10491 kind = GOMP_MAP_TO;
10492 break;
10493 case GOVD_MAP_FROM_ONLY:
10494 kind = GOMP_MAP_FROM;
10495 break;
10496 case GOVD_MAP_ALLOC_ONLY:
10497 kind = GOMP_MAP_ALLOC;
10498 break;
10499 case GOVD_MAP_TO_ONLY | GOVD_MAP_FORCE:
10500 kind = GOMP_MAP_TO | GOMP_MAP_FLAG_FORCE;
10501 break;
10502 case GOVD_MAP_FORCE_PRESENT:
10503 kind = GOMP_MAP_FORCE_PRESENT;
10504 break;
10505 default:
10506 gcc_unreachable ();
10508 OMP_CLAUSE_SET_MAP_KIND (clause, kind);
10509 if (DECL_SIZE (decl)
10510 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
10512 tree decl2 = DECL_VALUE_EXPR (decl);
10513 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
10514 decl2 = TREE_OPERAND (decl2, 0);
10515 gcc_assert (DECL_P (decl2));
10516 tree mem = build_simple_mem_ref (decl2);
10517 OMP_CLAUSE_DECL (clause) = mem;
10518 OMP_CLAUSE_SIZE (clause) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
10519 if (gimplify_omp_ctxp->outer_context)
10521 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
10522 omp_notice_variable (ctx, decl2, true);
10523 omp_notice_variable (ctx, OMP_CLAUSE_SIZE (clause), true);
10525 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
10526 OMP_CLAUSE_MAP);
10527 OMP_CLAUSE_DECL (nc) = decl;
10528 OMP_CLAUSE_SIZE (nc) = size_zero_node;
10529 if (gimplify_omp_ctxp->target_firstprivatize_array_bases)
10530 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_POINTER);
10531 else
10532 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
10533 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
10534 OMP_CLAUSE_CHAIN (clause) = nc;
10536 else if (gimplify_omp_ctxp->target_firstprivatize_array_bases
10537 && lang_hooks.decls.omp_privatize_by_reference (decl))
10539 OMP_CLAUSE_DECL (clause) = build_simple_mem_ref (decl);
10540 OMP_CLAUSE_SIZE (clause)
10541 = unshare_expr (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl))));
10542 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10543 gimplify_omp_ctxp = ctx->outer_context;
10544 gimplify_expr (&OMP_CLAUSE_SIZE (clause),
10545 pre_p, NULL, is_gimple_val, fb_rvalue);
10546 gimplify_omp_ctxp = ctx;
10547 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
10548 OMP_CLAUSE_MAP);
10549 OMP_CLAUSE_DECL (nc) = decl;
10550 OMP_CLAUSE_SIZE (nc) = size_zero_node;
10551 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_REFERENCE);
10552 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
10553 OMP_CLAUSE_CHAIN (clause) = nc;
10555 else
10556 OMP_CLAUSE_SIZE (clause) = DECL_SIZE_UNIT (decl);
10558 if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_LASTPRIVATE) != 0)
10560 tree nc = build_omp_clause (input_location, OMP_CLAUSE_LASTPRIVATE);
10561 OMP_CLAUSE_DECL (nc) = decl;
10562 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (nc) = 1;
10563 OMP_CLAUSE_CHAIN (nc) = chain;
10564 OMP_CLAUSE_CHAIN (clause) = nc;
10565 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10566 gimplify_omp_ctxp = ctx->outer_context;
10567 lang_hooks.decls.omp_finish_clause (nc, pre_p,
10568 (ctx->region_type & ORT_ACC) != 0);
10569 gimplify_omp_ctxp = ctx;
10571 *list_p = clause;
10572 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10573 gimplify_omp_ctxp = ctx->outer_context;
10574 lang_hooks.decls.omp_finish_clause (clause, pre_p,
10575 (ctx->region_type & ORT_ACC) != 0);
10576 if (gimplify_omp_ctxp)
10577 for (; clause != chain; clause = OMP_CLAUSE_CHAIN (clause))
10578 if (OMP_CLAUSE_CODE (clause) == OMP_CLAUSE_MAP
10579 && DECL_P (OMP_CLAUSE_SIZE (clause)))
10580 omp_notice_variable (gimplify_omp_ctxp, OMP_CLAUSE_SIZE (clause),
10581 true);
10582 gimplify_omp_ctxp = ctx;
10583 return 0;
10586 static void
10587 gimplify_adjust_omp_clauses (gimple_seq *pre_p, gimple_seq body, tree *list_p,
10588 enum tree_code code)
10590 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10591 tree *orig_list_p = list_p;
10592 tree c, decl;
10593 bool has_inscan_reductions = false;
10595 if (body)
10597 struct gimplify_omp_ctx *octx;
10598 for (octx = ctx; octx; octx = octx->outer_context)
10599 if ((octx->region_type & (ORT_PARALLEL | ORT_TASK | ORT_TEAMS)) != 0)
10600 break;
10601 if (octx)
10603 struct walk_stmt_info wi;
10604 memset (&wi, 0, sizeof (wi));
10605 walk_gimple_seq (body, omp_find_stores_stmt,
10606 omp_find_stores_op, &wi);
10610 if (ctx->add_safelen1)
10612 /* If there are VLAs in the body of simd loop, prevent
10613 vectorization. */
10614 gcc_assert (ctx->region_type == ORT_SIMD);
10615 c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_SAFELEN);
10616 OMP_CLAUSE_SAFELEN_EXPR (c) = integer_one_node;
10617 OMP_CLAUSE_CHAIN (c) = *list_p;
10618 *list_p = c;
10619 list_p = &OMP_CLAUSE_CHAIN (c);
10622 if (ctx->region_type == ORT_WORKSHARE
10623 && ctx->outer_context
10624 && ctx->outer_context->region_type == ORT_COMBINED_PARALLEL)
10626 for (c = ctx->outer_context->clauses; c; c = OMP_CLAUSE_CHAIN (c))
10627 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
10628 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
10630 decl = OMP_CLAUSE_DECL (c);
10631 splay_tree_node n
10632 = splay_tree_lookup (ctx->outer_context->variables,
10633 (splay_tree_key) decl);
10634 gcc_checking_assert (!splay_tree_lookup (ctx->variables,
10635 (splay_tree_key) decl));
10636 omp_add_variable (ctx, decl, n->value);
10637 tree c2 = copy_node (c);
10638 OMP_CLAUSE_CHAIN (c2) = *list_p;
10639 *list_p = c2;
10640 if ((n->value & GOVD_FIRSTPRIVATE) == 0)
10641 continue;
10642 c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
10643 OMP_CLAUSE_FIRSTPRIVATE);
10644 OMP_CLAUSE_DECL (c2) = decl;
10645 OMP_CLAUSE_CHAIN (c2) = *list_p;
10646 *list_p = c2;
10649 while ((c = *list_p) != NULL)
10651 splay_tree_node n;
10652 bool remove = false;
10654 switch (OMP_CLAUSE_CODE (c))
10656 case OMP_CLAUSE_FIRSTPRIVATE:
10657 if ((ctx->region_type & ORT_TARGET)
10658 && (ctx->region_type & ORT_ACC) == 0
10659 && TYPE_ATOMIC (strip_array_types
10660 (TREE_TYPE (OMP_CLAUSE_DECL (c)))))
10662 error_at (OMP_CLAUSE_LOCATION (c),
10663 "%<_Atomic%> %qD in %<firstprivate%> clause on "
10664 "%<target%> construct", OMP_CLAUSE_DECL (c));
10665 remove = true;
10666 break;
10668 if (OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (c))
10670 decl = OMP_CLAUSE_DECL (c);
10671 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10672 if ((n->value & GOVD_MAP) != 0)
10674 remove = true;
10675 break;
10677 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT_TARGET (c) = 0;
10678 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (c) = 0;
10680 /* FALLTHRU */
10681 case OMP_CLAUSE_PRIVATE:
10682 case OMP_CLAUSE_SHARED:
10683 case OMP_CLAUSE_LINEAR:
10684 decl = OMP_CLAUSE_DECL (c);
10685 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10686 remove = !(n->value & GOVD_SEEN);
10687 if ((n->value & GOVD_LASTPRIVATE_CONDITIONAL) != 0
10688 && code == OMP_PARALLEL
10689 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_FIRSTPRIVATE)
10690 remove = true;
10691 if (! remove)
10693 bool shared = OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED;
10694 if ((n->value & GOVD_DEBUG_PRIVATE)
10695 || lang_hooks.decls.omp_private_debug_clause (decl, shared))
10697 gcc_assert ((n->value & GOVD_DEBUG_PRIVATE) == 0
10698 || ((n->value & GOVD_DATA_SHARE_CLASS)
10699 == GOVD_SHARED));
10700 OMP_CLAUSE_SET_CODE (c, OMP_CLAUSE_PRIVATE);
10701 OMP_CLAUSE_PRIVATE_DEBUG (c) = 1;
10703 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
10704 && ctx->has_depend
10705 && DECL_P (decl))
10706 n->value |= GOVD_WRITTEN;
10707 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
10708 && (n->value & GOVD_WRITTEN) == 0
10709 && DECL_P (decl)
10710 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
10711 OMP_CLAUSE_SHARED_READONLY (c) = 1;
10712 else if (DECL_P (decl)
10713 && ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
10714 && (n->value & GOVD_WRITTEN) != 0)
10715 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
10716 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
10717 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
10718 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
10720 else
10721 n->value &= ~GOVD_EXPLICIT;
10722 break;
10724 case OMP_CLAUSE_LASTPRIVATE:
10725 /* Make sure OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE is set to
10726 accurately reflect the presence of a FIRSTPRIVATE clause. */
10727 decl = OMP_CLAUSE_DECL (c);
10728 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10729 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c)
10730 = (n->value & GOVD_FIRSTPRIVATE) != 0;
10731 if (code == OMP_DISTRIBUTE
10732 && OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
10734 remove = true;
10735 error_at (OMP_CLAUSE_LOCATION (c),
10736 "same variable used in %<firstprivate%> and "
10737 "%<lastprivate%> clauses on %<distribute%> "
10738 "construct");
10740 if (!remove
10741 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
10742 && DECL_P (decl)
10743 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
10744 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
10745 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) && code == OMP_PARALLEL)
10746 remove = true;
10747 break;
10749 case OMP_CLAUSE_ALIGNED:
10750 decl = OMP_CLAUSE_DECL (c);
10751 if (!is_global_var (decl))
10753 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10754 remove = n == NULL || !(n->value & GOVD_SEEN);
10755 if (!remove && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
10757 struct gimplify_omp_ctx *octx;
10758 if (n != NULL
10759 && (n->value & (GOVD_DATA_SHARE_CLASS
10760 & ~GOVD_FIRSTPRIVATE)))
10761 remove = true;
10762 else
10763 for (octx = ctx->outer_context; octx;
10764 octx = octx->outer_context)
10766 n = splay_tree_lookup (octx->variables,
10767 (splay_tree_key) decl);
10768 if (n == NULL)
10769 continue;
10770 if (n->value & GOVD_LOCAL)
10771 break;
10772 /* We have to avoid assigning a shared variable
10773 to itself when trying to add
10774 __builtin_assume_aligned. */
10775 if (n->value & GOVD_SHARED)
10777 remove = true;
10778 break;
10783 else if (TREE_CODE (TREE_TYPE (decl)) == ARRAY_TYPE)
10785 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10786 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
10787 remove = true;
10789 break;
10791 case OMP_CLAUSE_NONTEMPORAL:
10792 decl = OMP_CLAUSE_DECL (c);
10793 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10794 remove = n == NULL || !(n->value & GOVD_SEEN);
10795 break;
10797 case OMP_CLAUSE_MAP:
10798 if (code == OMP_TARGET_EXIT_DATA
10799 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_POINTER)
10801 remove = true;
10802 break;
10804 decl = OMP_CLAUSE_DECL (c);
10805 /* Data clauses associated with reductions must be
10806 compatible with present_or_copy. Warn and adjust the clause
10807 if that is not the case. */
10808 if (ctx->region_type == ORT_ACC_PARALLEL
10809 || ctx->region_type == ORT_ACC_SERIAL)
10811 tree t = DECL_P (decl) ? decl : TREE_OPERAND (decl, 0);
10812 n = NULL;
10814 if (DECL_P (t))
10815 n = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
10817 if (n && (n->value & GOVD_REDUCTION))
10819 enum gomp_map_kind kind = OMP_CLAUSE_MAP_KIND (c);
10821 OMP_CLAUSE_MAP_IN_REDUCTION (c) = 1;
10822 if ((kind & GOMP_MAP_TOFROM) != GOMP_MAP_TOFROM
10823 && kind != GOMP_MAP_FORCE_PRESENT
10824 && kind != GOMP_MAP_POINTER)
10826 warning_at (OMP_CLAUSE_LOCATION (c), 0,
10827 "incompatible data clause with reduction "
10828 "on %qE; promoting to %<present_or_copy%>",
10829 DECL_NAME (t));
10830 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_TOFROM);
10834 if (!DECL_P (decl))
10836 if ((ctx->region_type & ORT_TARGET) != 0
10837 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
10839 if (TREE_CODE (decl) == INDIRECT_REF
10840 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
10841 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
10842 == REFERENCE_TYPE))
10843 decl = TREE_OPERAND (decl, 0);
10844 if (TREE_CODE (decl) == COMPONENT_REF)
10846 while (TREE_CODE (decl) == COMPONENT_REF)
10847 decl = TREE_OPERAND (decl, 0);
10848 if (DECL_P (decl))
10850 n = splay_tree_lookup (ctx->variables,
10851 (splay_tree_key) decl);
10852 if (!(n->value & GOVD_SEEN))
10853 remove = true;
10857 break;
10859 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10860 if ((ctx->region_type & ORT_TARGET) != 0
10861 && !(n->value & GOVD_SEEN)
10862 && GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c)) == 0
10863 && (!is_global_var (decl)
10864 || !lookup_attribute ("omp declare target link",
10865 DECL_ATTRIBUTES (decl))))
10867 remove = true;
10868 /* For struct element mapping, if struct is never referenced
10869 in target block and none of the mapping has always modifier,
10870 remove all the struct element mappings, which immediately
10871 follow the GOMP_MAP_STRUCT map clause. */
10872 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT)
10874 HOST_WIDE_INT cnt = tree_to_shwi (OMP_CLAUSE_SIZE (c));
10875 while (cnt--)
10876 OMP_CLAUSE_CHAIN (c)
10877 = OMP_CLAUSE_CHAIN (OMP_CLAUSE_CHAIN (c));
10880 else if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT
10881 && (code == OMP_TARGET_EXIT_DATA
10882 || code == OACC_EXIT_DATA))
10883 remove = true;
10884 else if (DECL_SIZE (decl)
10885 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST
10886 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_POINTER
10887 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FIRSTPRIVATE_POINTER
10888 && (OMP_CLAUSE_MAP_KIND (c)
10889 != GOMP_MAP_FIRSTPRIVATE_REFERENCE))
10891 /* For GOMP_MAP_FORCE_DEVICEPTR, we'll never enter here, because
10892 for these, TREE_CODE (DECL_SIZE (decl)) will always be
10893 INTEGER_CST. */
10894 gcc_assert (OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FORCE_DEVICEPTR);
10896 tree decl2 = DECL_VALUE_EXPR (decl);
10897 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
10898 decl2 = TREE_OPERAND (decl2, 0);
10899 gcc_assert (DECL_P (decl2));
10900 tree mem = build_simple_mem_ref (decl2);
10901 OMP_CLAUSE_DECL (c) = mem;
10902 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
10903 if (ctx->outer_context)
10905 omp_notice_variable (ctx->outer_context, decl2, true);
10906 omp_notice_variable (ctx->outer_context,
10907 OMP_CLAUSE_SIZE (c), true);
10909 if (((ctx->region_type & ORT_TARGET) != 0
10910 || !ctx->target_firstprivatize_array_bases)
10911 && ((n->value & GOVD_SEEN) == 0
10912 || (n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE)) == 0))
10914 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (c),
10915 OMP_CLAUSE_MAP);
10916 OMP_CLAUSE_DECL (nc) = decl;
10917 OMP_CLAUSE_SIZE (nc) = size_zero_node;
10918 if (ctx->target_firstprivatize_array_bases)
10919 OMP_CLAUSE_SET_MAP_KIND (nc,
10920 GOMP_MAP_FIRSTPRIVATE_POINTER);
10921 else
10922 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
10923 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (c);
10924 OMP_CLAUSE_CHAIN (c) = nc;
10925 c = nc;
10928 else
10930 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
10931 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
10932 gcc_assert ((n->value & GOVD_SEEN) == 0
10933 || ((n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE))
10934 == 0));
10936 break;
10938 case OMP_CLAUSE_TO:
10939 case OMP_CLAUSE_FROM:
10940 case OMP_CLAUSE__CACHE_:
10941 decl = OMP_CLAUSE_DECL (c);
10942 if (!DECL_P (decl))
10943 break;
10944 if (DECL_SIZE (decl)
10945 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
10947 tree decl2 = DECL_VALUE_EXPR (decl);
10948 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
10949 decl2 = TREE_OPERAND (decl2, 0);
10950 gcc_assert (DECL_P (decl2));
10951 tree mem = build_simple_mem_ref (decl2);
10952 OMP_CLAUSE_DECL (c) = mem;
10953 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
10954 if (ctx->outer_context)
10956 omp_notice_variable (ctx->outer_context, decl2, true);
10957 omp_notice_variable (ctx->outer_context,
10958 OMP_CLAUSE_SIZE (c), true);
10961 else if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
10962 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
10963 break;
10965 case OMP_CLAUSE_REDUCTION:
10966 if (OMP_CLAUSE_REDUCTION_INSCAN (c))
10968 decl = OMP_CLAUSE_DECL (c);
10969 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10970 if ((n->value & GOVD_REDUCTION_INSCAN) == 0)
10972 remove = true;
10973 error_at (OMP_CLAUSE_LOCATION (c),
10974 "%qD specified in %<inscan%> %<reduction%> clause "
10975 "but not in %<scan%> directive clause", decl);
10976 break;
10978 has_inscan_reductions = true;
10980 /* FALLTHRU */
10981 case OMP_CLAUSE_IN_REDUCTION:
10982 case OMP_CLAUSE_TASK_REDUCTION:
10983 decl = OMP_CLAUSE_DECL (c);
10984 /* OpenACC reductions need a present_or_copy data clause.
10985 Add one if necessary. Emit error when the reduction is private. */
10986 if (ctx->region_type == ORT_ACC_PARALLEL
10987 || ctx->region_type == ORT_ACC_SERIAL)
10989 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10990 if (n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE))
10992 remove = true;
10993 error_at (OMP_CLAUSE_LOCATION (c), "invalid private "
10994 "reduction on %qE", DECL_NAME (decl));
10996 else if ((n->value & GOVD_MAP) == 0)
10998 tree next = OMP_CLAUSE_CHAIN (c);
10999 tree nc = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_MAP);
11000 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_TOFROM);
11001 OMP_CLAUSE_DECL (nc) = decl;
11002 OMP_CLAUSE_CHAIN (c) = nc;
11003 lang_hooks.decls.omp_finish_clause (nc, pre_p,
11004 (ctx->region_type
11005 & ORT_ACC) != 0);
11006 while (1)
11008 OMP_CLAUSE_MAP_IN_REDUCTION (nc) = 1;
11009 if (OMP_CLAUSE_CHAIN (nc) == NULL)
11010 break;
11011 nc = OMP_CLAUSE_CHAIN (nc);
11013 OMP_CLAUSE_CHAIN (nc) = next;
11014 n->value |= GOVD_MAP;
11017 if (DECL_P (decl)
11018 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
11019 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
11020 break;
11022 case OMP_CLAUSE_ALLOCATE:
11023 decl = OMP_CLAUSE_DECL (c);
11024 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
11025 if (n != NULL && !(n->value & GOVD_SEEN))
11027 if ((n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE | GOVD_LINEAR))
11028 != 0
11029 && (n->value & (GOVD_REDUCTION | GOVD_LASTPRIVATE)) == 0)
11030 remove = true;
11032 if (!remove
11033 && OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
11034 && TREE_CODE (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)) != INTEGER_CST
11035 && ((ctx->region_type & (ORT_PARALLEL | ORT_TARGET)) != 0
11036 || (ctx->region_type & ORT_TASKLOOP) == ORT_TASK
11037 || (ctx->region_type & ORT_HOST_TEAMS) == ORT_HOST_TEAMS))
11039 tree allocator = OMP_CLAUSE_ALLOCATE_ALLOCATOR (c);
11040 n = splay_tree_lookup (ctx->variables, (splay_tree_key) allocator);
11041 if (n == NULL)
11043 enum omp_clause_default_kind default_kind
11044 = ctx->default_kind;
11045 ctx->default_kind = OMP_CLAUSE_DEFAULT_FIRSTPRIVATE;
11046 omp_notice_variable (ctx, OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
11047 true);
11048 ctx->default_kind = default_kind;
11050 else
11051 omp_notice_variable (ctx, OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
11052 true);
11054 break;
11056 case OMP_CLAUSE_COPYIN:
11057 case OMP_CLAUSE_COPYPRIVATE:
11058 case OMP_CLAUSE_IF:
11059 case OMP_CLAUSE_NUM_THREADS:
11060 case OMP_CLAUSE_NUM_TEAMS:
11061 case OMP_CLAUSE_THREAD_LIMIT:
11062 case OMP_CLAUSE_DIST_SCHEDULE:
11063 case OMP_CLAUSE_DEVICE:
11064 case OMP_CLAUSE_SCHEDULE:
11065 case OMP_CLAUSE_NOWAIT:
11066 case OMP_CLAUSE_ORDERED:
11067 case OMP_CLAUSE_DEFAULT:
11068 case OMP_CLAUSE_UNTIED:
11069 case OMP_CLAUSE_COLLAPSE:
11070 case OMP_CLAUSE_FINAL:
11071 case OMP_CLAUSE_MERGEABLE:
11072 case OMP_CLAUSE_PROC_BIND:
11073 case OMP_CLAUSE_SAFELEN:
11074 case OMP_CLAUSE_SIMDLEN:
11075 case OMP_CLAUSE_DEPEND:
11076 case OMP_CLAUSE_PRIORITY:
11077 case OMP_CLAUSE_GRAINSIZE:
11078 case OMP_CLAUSE_NUM_TASKS:
11079 case OMP_CLAUSE_NOGROUP:
11080 case OMP_CLAUSE_THREADS:
11081 case OMP_CLAUSE_SIMD:
11082 case OMP_CLAUSE_HINT:
11083 case OMP_CLAUSE_DEFAULTMAP:
11084 case OMP_CLAUSE_ORDER:
11085 case OMP_CLAUSE_BIND:
11086 case OMP_CLAUSE_DETACH:
11087 case OMP_CLAUSE_USE_DEVICE_PTR:
11088 case OMP_CLAUSE_USE_DEVICE_ADDR:
11089 case OMP_CLAUSE_IS_DEVICE_PTR:
11090 case OMP_CLAUSE_ASYNC:
11091 case OMP_CLAUSE_WAIT:
11092 case OMP_CLAUSE_INDEPENDENT:
11093 case OMP_CLAUSE_NUM_GANGS:
11094 case OMP_CLAUSE_NUM_WORKERS:
11095 case OMP_CLAUSE_VECTOR_LENGTH:
11096 case OMP_CLAUSE_GANG:
11097 case OMP_CLAUSE_WORKER:
11098 case OMP_CLAUSE_VECTOR:
11099 case OMP_CLAUSE_AUTO:
11100 case OMP_CLAUSE_SEQ:
11101 case OMP_CLAUSE_TILE:
11102 case OMP_CLAUSE_IF_PRESENT:
11103 case OMP_CLAUSE_FINALIZE:
11104 case OMP_CLAUSE_INCLUSIVE:
11105 case OMP_CLAUSE_EXCLUSIVE:
11106 break;
11108 default:
11109 gcc_unreachable ();
11112 if (remove)
11113 *list_p = OMP_CLAUSE_CHAIN (c);
11114 else
11115 list_p = &OMP_CLAUSE_CHAIN (c);
11118 /* Add in any implicit data sharing. */
11119 struct gimplify_adjust_omp_clauses_data data;
11120 data.list_p = list_p;
11121 data.pre_p = pre_p;
11122 splay_tree_foreach (ctx->variables, gimplify_adjust_omp_clauses_1, &data);
11124 if (has_inscan_reductions)
11125 for (c = *orig_list_p; c; c = OMP_CLAUSE_CHAIN (c))
11126 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
11127 && !OMP_CLAUSE_LINEAR_NO_COPYIN (c))
11129 error_at (OMP_CLAUSE_LOCATION (c),
11130 "%<inscan%> %<reduction%> clause used together with "
11131 "%<linear%> clause for a variable other than loop "
11132 "iterator");
11133 break;
11136 gimplify_omp_ctxp = ctx->outer_context;
11137 delete_omp_context (ctx);
11140 /* Return 0 if CONSTRUCTS selectors don't match the OpenMP context,
11141 -1 if unknown yet (simd is involved, won't be known until vectorization)
11142 and 1 if they do. If SCORES is non-NULL, it should point to an array
11143 of at least 2*NCONSTRUCTS+2 ints, and will be filled with the positions
11144 of the CONSTRUCTS (position -1 if it will never match) followed by
11145 number of constructs in the OpenMP context construct trait. If the
11146 score depends on whether it will be in a declare simd clone or not,
11147 the function returns 2 and there will be two sets of the scores, the first
11148 one for the case that it is not in a declare simd clone, the other
11149 that it is in a declare simd clone. */
11152 omp_construct_selector_matches (enum tree_code *constructs, int nconstructs,
11153 int *scores)
11155 int matched = 0, cnt = 0;
11156 bool simd_seen = false;
11157 bool target_seen = false;
11158 int declare_simd_cnt = -1;
11159 auto_vec<enum tree_code, 16> codes;
11160 for (struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp; ctx;)
11162 if (((ctx->region_type & ORT_PARALLEL) && ctx->code == OMP_PARALLEL)
11163 || ((ctx->region_type & (ORT_TARGET | ORT_IMPLICIT_TARGET | ORT_ACC))
11164 == ORT_TARGET && ctx->code == OMP_TARGET)
11165 || ((ctx->region_type & ORT_TEAMS) && ctx->code == OMP_TEAMS)
11166 || (ctx->region_type == ORT_WORKSHARE && ctx->code == OMP_FOR)
11167 || (ctx->region_type == ORT_SIMD
11168 && ctx->code == OMP_SIMD
11169 && !omp_find_clause (ctx->clauses, OMP_CLAUSE_BIND)))
11171 ++cnt;
11172 if (scores)
11173 codes.safe_push (ctx->code);
11174 else if (matched < nconstructs && ctx->code == constructs[matched])
11176 if (ctx->code == OMP_SIMD)
11178 if (matched)
11179 return 0;
11180 simd_seen = true;
11182 ++matched;
11184 if (ctx->code == OMP_TARGET)
11186 if (scores == NULL)
11187 return matched < nconstructs ? 0 : simd_seen ? -1 : 1;
11188 target_seen = true;
11189 break;
11192 else if (ctx->region_type == ORT_WORKSHARE
11193 && ctx->code == OMP_LOOP
11194 && ctx->outer_context
11195 && ctx->outer_context->region_type == ORT_COMBINED_PARALLEL
11196 && ctx->outer_context->outer_context
11197 && ctx->outer_context->outer_context->code == OMP_LOOP
11198 && ctx->outer_context->outer_context->distribute)
11199 ctx = ctx->outer_context->outer_context;
11200 ctx = ctx->outer_context;
11202 if (!target_seen
11203 && lookup_attribute ("omp declare simd",
11204 DECL_ATTRIBUTES (current_function_decl)))
11206 /* Declare simd is a maybe case, it is supposed to be added only to the
11207 omp-simd-clone.c added clones and not to the base function. */
11208 declare_simd_cnt = cnt++;
11209 if (scores)
11210 codes.safe_push (OMP_SIMD);
11211 else if (cnt == 0
11212 && constructs[0] == OMP_SIMD)
11214 gcc_assert (matched == 0);
11215 simd_seen = true;
11216 if (++matched == nconstructs)
11217 return -1;
11220 if (tree attr = lookup_attribute ("omp declare variant variant",
11221 DECL_ATTRIBUTES (current_function_decl)))
11223 enum tree_code variant_constructs[5];
11224 int variant_nconstructs = 0;
11225 if (!target_seen)
11226 variant_nconstructs
11227 = omp_constructor_traits_to_codes (TREE_VALUE (attr),
11228 variant_constructs);
11229 for (int i = 0; i < variant_nconstructs; i++)
11231 ++cnt;
11232 if (scores)
11233 codes.safe_push (variant_constructs[i]);
11234 else if (matched < nconstructs
11235 && variant_constructs[i] == constructs[matched])
11237 if (variant_constructs[i] == OMP_SIMD)
11239 if (matched)
11240 return 0;
11241 simd_seen = true;
11243 ++matched;
11247 if (!target_seen
11248 && lookup_attribute ("omp declare target block",
11249 DECL_ATTRIBUTES (current_function_decl)))
11251 if (scores)
11252 codes.safe_push (OMP_TARGET);
11253 else if (matched < nconstructs && constructs[matched] == OMP_TARGET)
11254 ++matched;
11256 if (scores)
11258 for (int pass = 0; pass < (declare_simd_cnt == -1 ? 1 : 2); pass++)
11260 int j = codes.length () - 1;
11261 for (int i = nconstructs - 1; i >= 0; i--)
11263 while (j >= 0
11264 && (pass != 0 || declare_simd_cnt != j)
11265 && constructs[i] != codes[j])
11266 --j;
11267 if (pass == 0 && declare_simd_cnt != -1 && j > declare_simd_cnt)
11268 *scores++ = j - 1;
11269 else
11270 *scores++ = j;
11272 *scores++ = ((pass == 0 && declare_simd_cnt != -1)
11273 ? codes.length () - 1 : codes.length ());
11275 return declare_simd_cnt == -1 ? 1 : 2;
11277 if (matched == nconstructs)
11278 return simd_seen ? -1 : 1;
11279 return 0;
11282 /* Gimplify OACC_CACHE. */
11284 static void
11285 gimplify_oacc_cache (tree *expr_p, gimple_seq *pre_p)
11287 tree expr = *expr_p;
11289 gimplify_scan_omp_clauses (&OACC_CACHE_CLAUSES (expr), pre_p, ORT_ACC,
11290 OACC_CACHE);
11291 gimplify_adjust_omp_clauses (pre_p, NULL, &OACC_CACHE_CLAUSES (expr),
11292 OACC_CACHE);
11294 /* TODO: Do something sensible with this information. */
11296 *expr_p = NULL_TREE;
11299 /* Helper function of gimplify_oacc_declare. The helper's purpose is to,
11300 if required, translate 'kind' in CLAUSE into an 'entry' kind and 'exit'
11301 kind. The entry kind will replace the one in CLAUSE, while the exit
11302 kind will be used in a new omp_clause and returned to the caller. */
11304 static tree
11305 gimplify_oacc_declare_1 (tree clause)
11307 HOST_WIDE_INT kind, new_op;
11308 bool ret = false;
11309 tree c = NULL;
11311 kind = OMP_CLAUSE_MAP_KIND (clause);
11313 switch (kind)
11315 case GOMP_MAP_ALLOC:
11316 new_op = GOMP_MAP_RELEASE;
11317 ret = true;
11318 break;
11320 case GOMP_MAP_FROM:
11321 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_FORCE_ALLOC);
11322 new_op = GOMP_MAP_FROM;
11323 ret = true;
11324 break;
11326 case GOMP_MAP_TOFROM:
11327 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_TO);
11328 new_op = GOMP_MAP_FROM;
11329 ret = true;
11330 break;
11332 case GOMP_MAP_DEVICE_RESIDENT:
11333 case GOMP_MAP_FORCE_DEVICEPTR:
11334 case GOMP_MAP_FORCE_PRESENT:
11335 case GOMP_MAP_LINK:
11336 case GOMP_MAP_POINTER:
11337 case GOMP_MAP_TO:
11338 break;
11340 default:
11341 gcc_unreachable ();
11342 break;
11345 if (ret)
11347 c = build_omp_clause (OMP_CLAUSE_LOCATION (clause), OMP_CLAUSE_MAP);
11348 OMP_CLAUSE_SET_MAP_KIND (c, new_op);
11349 OMP_CLAUSE_DECL (c) = OMP_CLAUSE_DECL (clause);
11352 return c;
11355 /* Gimplify OACC_DECLARE. */
11357 static void
11358 gimplify_oacc_declare (tree *expr_p, gimple_seq *pre_p)
11360 tree expr = *expr_p;
11361 gomp_target *stmt;
11362 tree clauses, t, decl;
11364 clauses = OACC_DECLARE_CLAUSES (expr);
11366 gimplify_scan_omp_clauses (&clauses, pre_p, ORT_TARGET_DATA, OACC_DECLARE);
11367 gimplify_adjust_omp_clauses (pre_p, NULL, &clauses, OACC_DECLARE);
11369 for (t = clauses; t; t = OMP_CLAUSE_CHAIN (t))
11371 decl = OMP_CLAUSE_DECL (t);
11373 if (TREE_CODE (decl) == MEM_REF)
11374 decl = TREE_OPERAND (decl, 0);
11376 if (VAR_P (decl) && !is_oacc_declared (decl))
11378 tree attr = get_identifier ("oacc declare target");
11379 DECL_ATTRIBUTES (decl) = tree_cons (attr, NULL_TREE,
11380 DECL_ATTRIBUTES (decl));
11383 if (VAR_P (decl)
11384 && !is_global_var (decl)
11385 && DECL_CONTEXT (decl) == current_function_decl)
11387 tree c = gimplify_oacc_declare_1 (t);
11388 if (c)
11390 if (oacc_declare_returns == NULL)
11391 oacc_declare_returns = new hash_map<tree, tree>;
11393 oacc_declare_returns->put (decl, c);
11397 if (gimplify_omp_ctxp)
11398 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_SEEN);
11401 stmt = gimple_build_omp_target (NULL, GF_OMP_TARGET_KIND_OACC_DECLARE,
11402 clauses);
11404 gimplify_seq_add_stmt (pre_p, stmt);
11406 *expr_p = NULL_TREE;
11409 /* Gimplify the contents of an OMP_PARALLEL statement. This involves
11410 gimplification of the body, as well as scanning the body for used
11411 variables. We need to do this scan now, because variable-sized
11412 decls will be decomposed during gimplification. */
11414 static void
11415 gimplify_omp_parallel (tree *expr_p, gimple_seq *pre_p)
11417 tree expr = *expr_p;
11418 gimple *g;
11419 gimple_seq body = NULL;
11421 gimplify_scan_omp_clauses (&OMP_PARALLEL_CLAUSES (expr), pre_p,
11422 OMP_PARALLEL_COMBINED (expr)
11423 ? ORT_COMBINED_PARALLEL
11424 : ORT_PARALLEL, OMP_PARALLEL);
11426 push_gimplify_context ();
11428 g = gimplify_and_return_first (OMP_PARALLEL_BODY (expr), &body);
11429 if (gimple_code (g) == GIMPLE_BIND)
11430 pop_gimplify_context (g);
11431 else
11432 pop_gimplify_context (NULL);
11434 gimplify_adjust_omp_clauses (pre_p, body, &OMP_PARALLEL_CLAUSES (expr),
11435 OMP_PARALLEL);
11437 g = gimple_build_omp_parallel (body,
11438 OMP_PARALLEL_CLAUSES (expr),
11439 NULL_TREE, NULL_TREE);
11440 if (OMP_PARALLEL_COMBINED (expr))
11441 gimple_omp_set_subcode (g, GF_OMP_PARALLEL_COMBINED);
11442 gimplify_seq_add_stmt (pre_p, g);
11443 *expr_p = NULL_TREE;
11446 /* Gimplify the contents of an OMP_TASK statement. This involves
11447 gimplification of the body, as well as scanning the body for used
11448 variables. We need to do this scan now, because variable-sized
11449 decls will be decomposed during gimplification. */
11451 static void
11452 gimplify_omp_task (tree *expr_p, gimple_seq *pre_p)
11454 tree expr = *expr_p;
11455 gimple *g;
11456 gimple_seq body = NULL;
11458 if (OMP_TASK_BODY (expr) == NULL_TREE)
11459 for (tree c = OMP_TASK_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
11460 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
11461 && OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_MUTEXINOUTSET)
11463 error_at (OMP_CLAUSE_LOCATION (c),
11464 "%<mutexinoutset%> kind in %<depend%> clause on a "
11465 "%<taskwait%> construct");
11466 break;
11469 gimplify_scan_omp_clauses (&OMP_TASK_CLAUSES (expr), pre_p,
11470 omp_find_clause (OMP_TASK_CLAUSES (expr),
11471 OMP_CLAUSE_UNTIED)
11472 ? ORT_UNTIED_TASK : ORT_TASK, OMP_TASK);
11474 if (OMP_TASK_BODY (expr))
11476 push_gimplify_context ();
11478 g = gimplify_and_return_first (OMP_TASK_BODY (expr), &body);
11479 if (gimple_code (g) == GIMPLE_BIND)
11480 pop_gimplify_context (g);
11481 else
11482 pop_gimplify_context (NULL);
11485 gimplify_adjust_omp_clauses (pre_p, body, &OMP_TASK_CLAUSES (expr),
11486 OMP_TASK);
11488 g = gimple_build_omp_task (body,
11489 OMP_TASK_CLAUSES (expr),
11490 NULL_TREE, NULL_TREE,
11491 NULL_TREE, NULL_TREE, NULL_TREE);
11492 if (OMP_TASK_BODY (expr) == NULL_TREE)
11493 gimple_omp_task_set_taskwait_p (g, true);
11494 gimplify_seq_add_stmt (pre_p, g);
11495 *expr_p = NULL_TREE;
11498 /* Helper function for gimplify_omp_for. If *TP is not a gimple constant,
11499 force it into a temporary initialized in PRE_P and add firstprivate clause
11500 to ORIG_FOR_STMT. */
11502 static void
11503 gimplify_omp_taskloop_expr (tree type, tree *tp, gimple_seq *pre_p,
11504 tree orig_for_stmt)
11506 if (*tp == NULL || is_gimple_constant (*tp))
11507 return;
11509 *tp = get_initialized_tmp_var (*tp, pre_p, NULL, false);
11510 /* Reference to pointer conversion is considered useless,
11511 but is significant for firstprivate clause. Force it
11512 here. */
11513 if (type
11514 && TREE_CODE (type) == POINTER_TYPE
11515 && TREE_CODE (TREE_TYPE (*tp)) == REFERENCE_TYPE)
11517 tree v = create_tmp_var (TYPE_MAIN_VARIANT (type));
11518 tree m = build2 (INIT_EXPR, TREE_TYPE (v), v, *tp);
11519 gimplify_and_add (m, pre_p);
11520 *tp = v;
11523 tree c = build_omp_clause (input_location, OMP_CLAUSE_FIRSTPRIVATE);
11524 OMP_CLAUSE_DECL (c) = *tp;
11525 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (orig_for_stmt);
11526 OMP_FOR_CLAUSES (orig_for_stmt) = c;
11529 /* Gimplify the gross structure of an OMP_FOR statement. */
11531 static enum gimplify_status
11532 gimplify_omp_for (tree *expr_p, gimple_seq *pre_p)
11534 tree for_stmt, orig_for_stmt, inner_for_stmt = NULL_TREE, decl, var, t;
11535 enum gimplify_status ret = GS_ALL_DONE;
11536 enum gimplify_status tret;
11537 gomp_for *gfor;
11538 gimple_seq for_body, for_pre_body;
11539 int i;
11540 bitmap has_decl_expr = NULL;
11541 enum omp_region_type ort = ORT_WORKSHARE;
11542 bool openacc = TREE_CODE (*expr_p) == OACC_LOOP;
11544 orig_for_stmt = for_stmt = *expr_p;
11546 bool loop_p = (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_BIND)
11547 != NULL_TREE);
11548 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
11550 tree *data[4] = { NULL, NULL, NULL, NULL };
11551 gcc_assert (TREE_CODE (for_stmt) != OACC_LOOP);
11552 inner_for_stmt = walk_tree (&OMP_FOR_BODY (for_stmt),
11553 find_combined_omp_for, data, NULL);
11554 if (inner_for_stmt == NULL_TREE)
11556 gcc_assert (seen_error ());
11557 *expr_p = NULL_TREE;
11558 return GS_ERROR;
11560 if (data[2] && OMP_FOR_PRE_BODY (*data[2]))
11562 append_to_statement_list_force (OMP_FOR_PRE_BODY (*data[2]),
11563 &OMP_FOR_PRE_BODY (for_stmt));
11564 OMP_FOR_PRE_BODY (*data[2]) = NULL_TREE;
11566 if (OMP_FOR_PRE_BODY (inner_for_stmt))
11568 append_to_statement_list_force (OMP_FOR_PRE_BODY (inner_for_stmt),
11569 &OMP_FOR_PRE_BODY (for_stmt));
11570 OMP_FOR_PRE_BODY (inner_for_stmt) = NULL_TREE;
11573 if (data[0])
11575 /* We have some statements or variable declarations in between
11576 the composite construct directives. Move them around the
11577 inner_for_stmt. */
11578 data[0] = expr_p;
11579 for (i = 0; i < 3; i++)
11580 if (data[i])
11582 tree t = *data[i];
11583 if (i < 2 && data[i + 1] == &OMP_BODY (t))
11584 data[i + 1] = data[i];
11585 *data[i] = OMP_BODY (t);
11586 tree body = build3 (BIND_EXPR, void_type_node, NULL_TREE,
11587 NULL_TREE, make_node (BLOCK));
11588 OMP_BODY (t) = body;
11589 append_to_statement_list_force (inner_for_stmt,
11590 &BIND_EXPR_BODY (body));
11591 *data[3] = t;
11592 data[3] = tsi_stmt_ptr (tsi_start (BIND_EXPR_BODY (body)));
11593 gcc_assert (*data[3] == inner_for_stmt);
11595 return GS_OK;
11598 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (inner_for_stmt)); i++)
11599 if (!loop_p
11600 && OMP_FOR_ORIG_DECLS (inner_for_stmt)
11601 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
11602 i)) == TREE_LIST
11603 && TREE_PURPOSE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
11604 i)))
11606 tree orig = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt), i);
11607 /* Class iterators aren't allowed on OMP_SIMD, so the only
11608 case we need to solve is distribute parallel for. They are
11609 allowed on the loop construct, but that is already handled
11610 in gimplify_omp_loop. */
11611 gcc_assert (TREE_CODE (inner_for_stmt) == OMP_FOR
11612 && TREE_CODE (for_stmt) == OMP_DISTRIBUTE
11613 && data[1]);
11614 tree orig_decl = TREE_PURPOSE (orig);
11615 tree last = TREE_VALUE (orig);
11616 tree *pc;
11617 for (pc = &OMP_FOR_CLAUSES (inner_for_stmt);
11618 *pc; pc = &OMP_CLAUSE_CHAIN (*pc))
11619 if ((OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_PRIVATE
11620 || OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_LASTPRIVATE)
11621 && OMP_CLAUSE_DECL (*pc) == orig_decl)
11622 break;
11623 if (*pc == NULL_TREE)
11625 tree *spc;
11626 for (spc = &OMP_PARALLEL_CLAUSES (*data[1]);
11627 *spc; spc = &OMP_CLAUSE_CHAIN (*spc))
11628 if (OMP_CLAUSE_CODE (*spc) == OMP_CLAUSE_PRIVATE
11629 && OMP_CLAUSE_DECL (*spc) == orig_decl)
11630 break;
11631 if (*spc)
11633 tree c = *spc;
11634 *spc = OMP_CLAUSE_CHAIN (c);
11635 OMP_CLAUSE_CHAIN (c) = NULL_TREE;
11636 *pc = c;
11639 if (*pc == NULL_TREE)
11641 else if (OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_PRIVATE)
11643 /* private clause will appear only on inner_for_stmt.
11644 Change it into firstprivate, and add private clause
11645 on for_stmt. */
11646 tree c = copy_node (*pc);
11647 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
11648 OMP_FOR_CLAUSES (for_stmt) = c;
11649 OMP_CLAUSE_CODE (*pc) = OMP_CLAUSE_FIRSTPRIVATE;
11650 lang_hooks.decls.omp_finish_clause (*pc, pre_p, openacc);
11652 else
11654 /* lastprivate clause will appear on both inner_for_stmt
11655 and for_stmt. Add firstprivate clause to
11656 inner_for_stmt. */
11657 tree c = build_omp_clause (OMP_CLAUSE_LOCATION (*pc),
11658 OMP_CLAUSE_FIRSTPRIVATE);
11659 OMP_CLAUSE_DECL (c) = OMP_CLAUSE_DECL (*pc);
11660 OMP_CLAUSE_CHAIN (c) = *pc;
11661 *pc = c;
11662 lang_hooks.decls.omp_finish_clause (*pc, pre_p, openacc);
11664 tree c = build_omp_clause (UNKNOWN_LOCATION,
11665 OMP_CLAUSE_FIRSTPRIVATE);
11666 OMP_CLAUSE_DECL (c) = last;
11667 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
11668 OMP_PARALLEL_CLAUSES (*data[1]) = c;
11669 c = build_omp_clause (UNKNOWN_LOCATION,
11670 *pc ? OMP_CLAUSE_SHARED
11671 : OMP_CLAUSE_FIRSTPRIVATE);
11672 OMP_CLAUSE_DECL (c) = orig_decl;
11673 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
11674 OMP_PARALLEL_CLAUSES (*data[1]) = c;
11676 /* Similarly, take care of C++ range for temporaries, those should
11677 be firstprivate on OMP_PARALLEL if any. */
11678 if (data[1])
11679 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (inner_for_stmt)); i++)
11680 if (OMP_FOR_ORIG_DECLS (inner_for_stmt)
11681 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
11682 i)) == TREE_LIST
11683 && TREE_CHAIN (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
11684 i)))
11686 tree orig
11687 = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt), i);
11688 tree v = TREE_CHAIN (orig);
11689 tree c = build_omp_clause (UNKNOWN_LOCATION,
11690 OMP_CLAUSE_FIRSTPRIVATE);
11691 /* First add firstprivate clause for the __for_end artificial
11692 decl. */
11693 OMP_CLAUSE_DECL (c) = TREE_VEC_ELT (v, 1);
11694 if (TREE_CODE (TREE_TYPE (OMP_CLAUSE_DECL (c)))
11695 == REFERENCE_TYPE)
11696 OMP_CLAUSE_FIRSTPRIVATE_NO_REFERENCE (c) = 1;
11697 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
11698 OMP_PARALLEL_CLAUSES (*data[1]) = c;
11699 if (TREE_VEC_ELT (v, 0))
11701 /* And now the same for __for_range artificial decl if it
11702 exists. */
11703 c = build_omp_clause (UNKNOWN_LOCATION,
11704 OMP_CLAUSE_FIRSTPRIVATE);
11705 OMP_CLAUSE_DECL (c) = TREE_VEC_ELT (v, 0);
11706 if (TREE_CODE (TREE_TYPE (OMP_CLAUSE_DECL (c)))
11707 == REFERENCE_TYPE)
11708 OMP_CLAUSE_FIRSTPRIVATE_NO_REFERENCE (c) = 1;
11709 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
11710 OMP_PARALLEL_CLAUSES (*data[1]) = c;
11715 switch (TREE_CODE (for_stmt))
11717 case OMP_FOR:
11718 if (OMP_FOR_NON_RECTANGULAR (inner_for_stmt ? inner_for_stmt : for_stmt))
11720 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
11721 OMP_CLAUSE_SCHEDULE))
11722 error_at (EXPR_LOCATION (for_stmt),
11723 "%qs clause may not appear on non-rectangular %qs",
11724 "schedule", "for");
11725 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ORDERED))
11726 error_at (EXPR_LOCATION (for_stmt),
11727 "%qs clause may not appear on non-rectangular %qs",
11728 "ordered", "for");
11730 break;
11731 case OMP_DISTRIBUTE:
11732 if (OMP_FOR_NON_RECTANGULAR (inner_for_stmt ? inner_for_stmt : for_stmt)
11733 && omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
11734 OMP_CLAUSE_DIST_SCHEDULE))
11735 error_at (EXPR_LOCATION (for_stmt),
11736 "%qs clause may not appear on non-rectangular %qs",
11737 "dist_schedule", "distribute");
11738 break;
11739 case OACC_LOOP:
11740 ort = ORT_ACC;
11741 break;
11742 case OMP_TASKLOOP:
11743 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_UNTIED))
11744 ort = ORT_UNTIED_TASKLOOP;
11745 else
11746 ort = ORT_TASKLOOP;
11747 break;
11748 case OMP_SIMD:
11749 ort = ORT_SIMD;
11750 break;
11751 default:
11752 gcc_unreachable ();
11755 /* Set OMP_CLAUSE_LINEAR_NO_COPYIN flag on explicit linear
11756 clause for the IV. */
11757 if (ort == ORT_SIMD && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
11759 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), 0);
11760 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
11761 decl = TREE_OPERAND (t, 0);
11762 for (tree c = OMP_FOR_CLAUSES (for_stmt); c; c = OMP_CLAUSE_CHAIN (c))
11763 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
11764 && OMP_CLAUSE_DECL (c) == decl)
11766 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
11767 break;
11771 if (TREE_CODE (for_stmt) != OMP_TASKLOOP)
11772 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (for_stmt), pre_p, ort,
11773 loop_p && TREE_CODE (for_stmt) != OMP_SIMD
11774 ? OMP_LOOP : TREE_CODE (for_stmt));
11776 if (TREE_CODE (for_stmt) == OMP_DISTRIBUTE)
11777 gimplify_omp_ctxp->distribute = true;
11779 /* Handle OMP_FOR_INIT. */
11780 for_pre_body = NULL;
11781 if ((ort == ORT_SIMD
11782 || (inner_for_stmt && TREE_CODE (inner_for_stmt) == OMP_SIMD))
11783 && OMP_FOR_PRE_BODY (for_stmt))
11785 has_decl_expr = BITMAP_ALLOC (NULL);
11786 if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == DECL_EXPR
11787 && TREE_CODE (DECL_EXPR_DECL (OMP_FOR_PRE_BODY (for_stmt)))
11788 == VAR_DECL)
11790 t = OMP_FOR_PRE_BODY (for_stmt);
11791 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
11793 else if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == STATEMENT_LIST)
11795 tree_stmt_iterator si;
11796 for (si = tsi_start (OMP_FOR_PRE_BODY (for_stmt)); !tsi_end_p (si);
11797 tsi_next (&si))
11799 t = tsi_stmt (si);
11800 if (TREE_CODE (t) == DECL_EXPR
11801 && TREE_CODE (DECL_EXPR_DECL (t)) == VAR_DECL)
11802 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
11806 if (OMP_FOR_PRE_BODY (for_stmt))
11808 if (TREE_CODE (for_stmt) != OMP_TASKLOOP || gimplify_omp_ctxp)
11809 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
11810 else
11812 struct gimplify_omp_ctx ctx;
11813 memset (&ctx, 0, sizeof (ctx));
11814 ctx.region_type = ORT_NONE;
11815 gimplify_omp_ctxp = &ctx;
11816 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
11817 gimplify_omp_ctxp = NULL;
11820 OMP_FOR_PRE_BODY (for_stmt) = NULL_TREE;
11822 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
11823 for_stmt = inner_for_stmt;
11825 /* For taskloop, need to gimplify the start, end and step before the
11826 taskloop, outside of the taskloop omp context. */
11827 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
11829 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
11831 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
11832 gimple_seq *for_pre_p = (gimple_seq_empty_p (for_pre_body)
11833 ? pre_p : &for_pre_body);
11834 tree type = TREE_TYPE (TREE_OPERAND (t, 0));
11835 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
11837 tree v = TREE_OPERAND (t, 1);
11838 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 1),
11839 for_pre_p, orig_for_stmt);
11840 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 2),
11841 for_pre_p, orig_for_stmt);
11843 else
11844 gimplify_omp_taskloop_expr (type, &TREE_OPERAND (t, 1), for_pre_p,
11845 orig_for_stmt);
11847 /* Handle OMP_FOR_COND. */
11848 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
11849 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
11851 tree v = TREE_OPERAND (t, 1);
11852 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 1),
11853 for_pre_p, orig_for_stmt);
11854 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 2),
11855 for_pre_p, orig_for_stmt);
11857 else
11858 gimplify_omp_taskloop_expr (type, &TREE_OPERAND (t, 1), for_pre_p,
11859 orig_for_stmt);
11861 /* Handle OMP_FOR_INCR. */
11862 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
11863 if (TREE_CODE (t) == MODIFY_EXPR)
11865 decl = TREE_OPERAND (t, 0);
11866 t = TREE_OPERAND (t, 1);
11867 tree *tp = &TREE_OPERAND (t, 1);
11868 if (TREE_CODE (t) == PLUS_EXPR && *tp == decl)
11869 tp = &TREE_OPERAND (t, 0);
11871 gimplify_omp_taskloop_expr (NULL_TREE, tp, for_pre_p,
11872 orig_for_stmt);
11876 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (orig_for_stmt), pre_p, ort,
11877 OMP_TASKLOOP);
11880 if (orig_for_stmt != for_stmt)
11881 gimplify_omp_ctxp->combined_loop = true;
11883 for_body = NULL;
11884 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
11885 == TREE_VEC_LENGTH (OMP_FOR_COND (for_stmt)));
11886 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
11887 == TREE_VEC_LENGTH (OMP_FOR_INCR (for_stmt)));
11889 tree c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ORDERED);
11890 bool is_doacross = false;
11891 if (c && OMP_CLAUSE_ORDERED_EXPR (c))
11893 is_doacross = true;
11894 gimplify_omp_ctxp->loop_iter_var.create (TREE_VEC_LENGTH
11895 (OMP_FOR_INIT (for_stmt))
11896 * 2);
11898 int collapse = 1, tile = 0;
11899 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_COLLAPSE);
11900 if (c)
11901 collapse = tree_to_shwi (OMP_CLAUSE_COLLAPSE_EXPR (c));
11902 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_TILE);
11903 if (c)
11904 tile = list_length (OMP_CLAUSE_TILE_LIST (c));
11905 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ALLOCATE);
11906 hash_set<tree> *allocate_uids = NULL;
11907 if (c)
11909 allocate_uids = new hash_set<tree>;
11910 for (; c; c = OMP_CLAUSE_CHAIN (c))
11911 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_ALLOCATE)
11912 allocate_uids->add (OMP_CLAUSE_DECL (c));
11914 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
11916 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
11917 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
11918 decl = TREE_OPERAND (t, 0);
11919 gcc_assert (DECL_P (decl));
11920 gcc_assert (INTEGRAL_TYPE_P (TREE_TYPE (decl))
11921 || POINTER_TYPE_P (TREE_TYPE (decl)));
11922 if (is_doacross)
11924 if (TREE_CODE (for_stmt) == OMP_FOR && OMP_FOR_ORIG_DECLS (for_stmt))
11926 tree orig_decl = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
11927 if (TREE_CODE (orig_decl) == TREE_LIST)
11929 orig_decl = TREE_PURPOSE (orig_decl);
11930 if (!orig_decl)
11931 orig_decl = decl;
11933 gimplify_omp_ctxp->loop_iter_var.quick_push (orig_decl);
11935 else
11936 gimplify_omp_ctxp->loop_iter_var.quick_push (decl);
11937 gimplify_omp_ctxp->loop_iter_var.quick_push (decl);
11940 /* Make sure the iteration variable is private. */
11941 tree c = NULL_TREE;
11942 tree c2 = NULL_TREE;
11943 if (orig_for_stmt != for_stmt)
11945 /* Preserve this information until we gimplify the inner simd. */
11946 if (has_decl_expr
11947 && bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
11948 TREE_PRIVATE (t) = 1;
11950 else if (ort == ORT_SIMD)
11952 splay_tree_node n = splay_tree_lookup (gimplify_omp_ctxp->variables,
11953 (splay_tree_key) decl);
11954 omp_is_private (gimplify_omp_ctxp, decl,
11955 1 + (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
11956 != 1));
11957 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
11959 omp_notice_variable (gimplify_omp_ctxp, decl, true);
11960 if (n->value & GOVD_LASTPRIVATE_CONDITIONAL)
11961 for (tree c3 = omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
11962 OMP_CLAUSE_LASTPRIVATE);
11963 c3; c3 = omp_find_clause (OMP_CLAUSE_CHAIN (c3),
11964 OMP_CLAUSE_LASTPRIVATE))
11965 if (OMP_CLAUSE_DECL (c3) == decl)
11967 warning_at (OMP_CLAUSE_LOCATION (c3), 0,
11968 "conditional %<lastprivate%> on loop "
11969 "iterator %qD ignored", decl);
11970 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c3) = 0;
11971 n->value &= ~GOVD_LASTPRIVATE_CONDITIONAL;
11974 else if (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1 && !loop_p)
11976 c = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
11977 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
11978 unsigned int flags = GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN;
11979 if ((has_decl_expr
11980 && bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
11981 || TREE_PRIVATE (t))
11983 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
11984 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
11986 struct gimplify_omp_ctx *outer
11987 = gimplify_omp_ctxp->outer_context;
11988 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
11990 if (outer->region_type == ORT_WORKSHARE
11991 && outer->combined_loop)
11993 n = splay_tree_lookup (outer->variables,
11994 (splay_tree_key)decl);
11995 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
11997 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
11998 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
12000 else
12002 struct gimplify_omp_ctx *octx = outer->outer_context;
12003 if (octx
12004 && octx->region_type == ORT_COMBINED_PARALLEL
12005 && octx->outer_context
12006 && (octx->outer_context->region_type
12007 == ORT_WORKSHARE)
12008 && octx->outer_context->combined_loop)
12010 octx = octx->outer_context;
12011 n = splay_tree_lookup (octx->variables,
12012 (splay_tree_key)decl);
12013 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
12015 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
12016 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
12023 OMP_CLAUSE_DECL (c) = decl;
12024 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
12025 OMP_FOR_CLAUSES (for_stmt) = c;
12026 omp_add_variable (gimplify_omp_ctxp, decl, flags);
12027 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
12028 omp_lastprivate_for_combined_outer_constructs (outer, decl,
12029 true);
12031 else
12033 bool lastprivate
12034 = (!has_decl_expr
12035 || !bitmap_bit_p (has_decl_expr, DECL_UID (decl)));
12036 if (TREE_PRIVATE (t))
12037 lastprivate = false;
12038 if (loop_p && OMP_FOR_ORIG_DECLS (for_stmt))
12040 tree elt = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
12041 if (TREE_CODE (elt) == TREE_LIST && TREE_PURPOSE (elt))
12042 lastprivate = false;
12045 struct gimplify_omp_ctx *outer
12046 = gimplify_omp_ctxp->outer_context;
12047 if (outer && lastprivate)
12048 omp_lastprivate_for_combined_outer_constructs (outer, decl,
12049 true);
12051 c = build_omp_clause (input_location,
12052 lastprivate ? OMP_CLAUSE_LASTPRIVATE
12053 : OMP_CLAUSE_PRIVATE);
12054 OMP_CLAUSE_DECL (c) = decl;
12055 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
12056 OMP_FOR_CLAUSES (for_stmt) = c;
12057 omp_add_variable (gimplify_omp_ctxp, decl,
12058 (lastprivate ? GOVD_LASTPRIVATE : GOVD_PRIVATE)
12059 | GOVD_EXPLICIT | GOVD_SEEN);
12060 c = NULL_TREE;
12063 else if (omp_is_private (gimplify_omp_ctxp, decl, 0))
12065 omp_notice_variable (gimplify_omp_ctxp, decl, true);
12066 splay_tree_node n = splay_tree_lookup (gimplify_omp_ctxp->variables,
12067 (splay_tree_key) decl);
12068 if (n && (n->value & GOVD_LASTPRIVATE_CONDITIONAL))
12069 for (tree c3 = omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
12070 OMP_CLAUSE_LASTPRIVATE);
12071 c3; c3 = omp_find_clause (OMP_CLAUSE_CHAIN (c3),
12072 OMP_CLAUSE_LASTPRIVATE))
12073 if (OMP_CLAUSE_DECL (c3) == decl)
12075 warning_at (OMP_CLAUSE_LOCATION (c3), 0,
12076 "conditional %<lastprivate%> on loop "
12077 "iterator %qD ignored", decl);
12078 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c3) = 0;
12079 n->value &= ~GOVD_LASTPRIVATE_CONDITIONAL;
12082 else
12083 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_PRIVATE | GOVD_SEEN);
12085 /* If DECL is not a gimple register, create a temporary variable to act
12086 as an iteration counter. This is valid, since DECL cannot be
12087 modified in the body of the loop. Similarly for any iteration vars
12088 in simd with collapse > 1 where the iterator vars must be
12089 lastprivate. And similarly for vars mentioned in allocate clauses. */
12090 if (orig_for_stmt != for_stmt)
12091 var = decl;
12092 else if (!is_gimple_reg (decl)
12093 || (ort == ORT_SIMD
12094 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) > 1)
12095 || (allocate_uids && allocate_uids->contains (decl)))
12097 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
12098 /* Make sure omp_add_variable is not called on it prematurely.
12099 We call it ourselves a few lines later. */
12100 gimplify_omp_ctxp = NULL;
12101 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
12102 gimplify_omp_ctxp = ctx;
12103 TREE_OPERAND (t, 0) = var;
12105 gimplify_seq_add_stmt (&for_body, gimple_build_assign (decl, var));
12107 if (ort == ORT_SIMD
12108 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
12110 c2 = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
12111 OMP_CLAUSE_LINEAR_NO_COPYIN (c2) = 1;
12112 OMP_CLAUSE_LINEAR_NO_COPYOUT (c2) = 1;
12113 OMP_CLAUSE_DECL (c2) = var;
12114 OMP_CLAUSE_CHAIN (c2) = OMP_FOR_CLAUSES (for_stmt);
12115 OMP_FOR_CLAUSES (for_stmt) = c2;
12116 omp_add_variable (gimplify_omp_ctxp, var,
12117 GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN);
12118 if (c == NULL_TREE)
12120 c = c2;
12121 c2 = NULL_TREE;
12124 else
12125 omp_add_variable (gimplify_omp_ctxp, var,
12126 GOVD_PRIVATE | GOVD_SEEN);
12128 else
12129 var = decl;
12131 gimplify_omp_ctxp->in_for_exprs = true;
12132 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
12134 tree lb = TREE_OPERAND (t, 1);
12135 tret = gimplify_expr (&TREE_VEC_ELT (lb, 1), &for_pre_body, NULL,
12136 is_gimple_val, fb_rvalue, false);
12137 ret = MIN (ret, tret);
12138 tret = gimplify_expr (&TREE_VEC_ELT (lb, 2), &for_pre_body, NULL,
12139 is_gimple_val, fb_rvalue, false);
12141 else
12142 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
12143 is_gimple_val, fb_rvalue, false);
12144 gimplify_omp_ctxp->in_for_exprs = false;
12145 ret = MIN (ret, tret);
12146 if (ret == GS_ERROR)
12147 return ret;
12149 /* Handle OMP_FOR_COND. */
12150 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
12151 gcc_assert (COMPARISON_CLASS_P (t));
12152 gcc_assert (TREE_OPERAND (t, 0) == decl);
12154 gimplify_omp_ctxp->in_for_exprs = true;
12155 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
12157 tree ub = TREE_OPERAND (t, 1);
12158 tret = gimplify_expr (&TREE_VEC_ELT (ub, 1), &for_pre_body, NULL,
12159 is_gimple_val, fb_rvalue, false);
12160 ret = MIN (ret, tret);
12161 tret = gimplify_expr (&TREE_VEC_ELT (ub, 2), &for_pre_body, NULL,
12162 is_gimple_val, fb_rvalue, false);
12164 else
12165 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
12166 is_gimple_val, fb_rvalue, false);
12167 gimplify_omp_ctxp->in_for_exprs = false;
12168 ret = MIN (ret, tret);
12170 /* Handle OMP_FOR_INCR. */
12171 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
12172 switch (TREE_CODE (t))
12174 case PREINCREMENT_EXPR:
12175 case POSTINCREMENT_EXPR:
12177 tree decl = TREE_OPERAND (t, 0);
12178 /* c_omp_for_incr_canonicalize_ptr() should have been
12179 called to massage things appropriately. */
12180 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
12182 if (orig_for_stmt != for_stmt)
12183 break;
12184 t = build_int_cst (TREE_TYPE (decl), 1);
12185 if (c)
12186 OMP_CLAUSE_LINEAR_STEP (c) = t;
12187 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
12188 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
12189 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
12190 break;
12193 case PREDECREMENT_EXPR:
12194 case POSTDECREMENT_EXPR:
12195 /* c_omp_for_incr_canonicalize_ptr() should have been
12196 called to massage things appropriately. */
12197 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
12198 if (orig_for_stmt != for_stmt)
12199 break;
12200 t = build_int_cst (TREE_TYPE (decl), -1);
12201 if (c)
12202 OMP_CLAUSE_LINEAR_STEP (c) = t;
12203 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
12204 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
12205 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
12206 break;
12208 case MODIFY_EXPR:
12209 gcc_assert (TREE_OPERAND (t, 0) == decl);
12210 TREE_OPERAND (t, 0) = var;
12212 t = TREE_OPERAND (t, 1);
12213 switch (TREE_CODE (t))
12215 case PLUS_EXPR:
12216 if (TREE_OPERAND (t, 1) == decl)
12218 TREE_OPERAND (t, 1) = TREE_OPERAND (t, 0);
12219 TREE_OPERAND (t, 0) = var;
12220 break;
12223 /* Fallthru. */
12224 case MINUS_EXPR:
12225 case POINTER_PLUS_EXPR:
12226 gcc_assert (TREE_OPERAND (t, 0) == decl);
12227 TREE_OPERAND (t, 0) = var;
12228 break;
12229 default:
12230 gcc_unreachable ();
12233 gimplify_omp_ctxp->in_for_exprs = true;
12234 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
12235 is_gimple_val, fb_rvalue, false);
12236 ret = MIN (ret, tret);
12237 if (c)
12239 tree step = TREE_OPERAND (t, 1);
12240 tree stept = TREE_TYPE (decl);
12241 if (POINTER_TYPE_P (stept))
12242 stept = sizetype;
12243 step = fold_convert (stept, step);
12244 if (TREE_CODE (t) == MINUS_EXPR)
12245 step = fold_build1 (NEGATE_EXPR, stept, step);
12246 OMP_CLAUSE_LINEAR_STEP (c) = step;
12247 if (step != TREE_OPERAND (t, 1))
12249 tret = gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c),
12250 &for_pre_body, NULL,
12251 is_gimple_val, fb_rvalue, false);
12252 ret = MIN (ret, tret);
12255 gimplify_omp_ctxp->in_for_exprs = false;
12256 break;
12258 default:
12259 gcc_unreachable ();
12262 if (c2)
12264 gcc_assert (c);
12265 OMP_CLAUSE_LINEAR_STEP (c2) = OMP_CLAUSE_LINEAR_STEP (c);
12268 if ((var != decl || collapse > 1 || tile) && orig_for_stmt == for_stmt)
12270 for (c = OMP_FOR_CLAUSES (for_stmt); c ; c = OMP_CLAUSE_CHAIN (c))
12271 if (((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
12272 && OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c) == NULL)
12273 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
12274 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)
12275 && OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c) == NULL))
12276 && OMP_CLAUSE_DECL (c) == decl)
12278 if (is_doacross && (collapse == 1 || i >= collapse))
12279 t = var;
12280 else
12282 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
12283 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
12284 gcc_assert (TREE_OPERAND (t, 0) == var);
12285 t = TREE_OPERAND (t, 1);
12286 gcc_assert (TREE_CODE (t) == PLUS_EXPR
12287 || TREE_CODE (t) == MINUS_EXPR
12288 || TREE_CODE (t) == POINTER_PLUS_EXPR);
12289 gcc_assert (TREE_OPERAND (t, 0) == var);
12290 t = build2 (TREE_CODE (t), TREE_TYPE (decl),
12291 is_doacross ? var : decl,
12292 TREE_OPERAND (t, 1));
12294 gimple_seq *seq;
12295 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE)
12296 seq = &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c);
12297 else
12298 seq = &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c);
12299 push_gimplify_context ();
12300 gimplify_assign (decl, t, seq);
12301 gimple *bind = NULL;
12302 if (gimplify_ctxp->temps)
12304 bind = gimple_build_bind (NULL_TREE, *seq, NULL_TREE);
12305 *seq = NULL;
12306 gimplify_seq_add_stmt (seq, bind);
12308 pop_gimplify_context (bind);
12311 if (OMP_FOR_NON_RECTANGULAR (for_stmt) && var != decl)
12312 for (int j = i + 1; j < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); j++)
12314 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), j);
12315 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
12316 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
12317 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
12318 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
12319 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), j);
12320 gcc_assert (COMPARISON_CLASS_P (t));
12321 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
12322 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
12323 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
12327 BITMAP_FREE (has_decl_expr);
12328 delete allocate_uids;
12330 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP
12331 || (loop_p && orig_for_stmt == for_stmt))
12333 push_gimplify_context ();
12334 if (TREE_CODE (OMP_FOR_BODY (orig_for_stmt)) != BIND_EXPR)
12336 OMP_FOR_BODY (orig_for_stmt)
12337 = build3 (BIND_EXPR, void_type_node, NULL,
12338 OMP_FOR_BODY (orig_for_stmt), NULL);
12339 TREE_SIDE_EFFECTS (OMP_FOR_BODY (orig_for_stmt)) = 1;
12343 gimple *g = gimplify_and_return_first (OMP_FOR_BODY (orig_for_stmt),
12344 &for_body);
12346 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP
12347 || (loop_p && orig_for_stmt == for_stmt))
12349 if (gimple_code (g) == GIMPLE_BIND)
12350 pop_gimplify_context (g);
12351 else
12352 pop_gimplify_context (NULL);
12355 if (orig_for_stmt != for_stmt)
12356 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
12358 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
12359 decl = TREE_OPERAND (t, 0);
12360 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
12361 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
12362 gimplify_omp_ctxp = ctx->outer_context;
12363 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
12364 gimplify_omp_ctxp = ctx;
12365 omp_add_variable (gimplify_omp_ctxp, var, GOVD_PRIVATE | GOVD_SEEN);
12366 TREE_OPERAND (t, 0) = var;
12367 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
12368 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
12369 TREE_OPERAND (TREE_OPERAND (t, 1), 0) = var;
12370 if (OMP_FOR_NON_RECTANGULAR (for_stmt))
12371 for (int j = i + 1;
12372 j < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); j++)
12374 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), j);
12375 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
12376 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
12377 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
12379 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
12380 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
12382 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), j);
12383 gcc_assert (COMPARISON_CLASS_P (t));
12384 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
12385 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
12387 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
12388 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
12393 gimplify_adjust_omp_clauses (pre_p, for_body,
12394 &OMP_FOR_CLAUSES (orig_for_stmt),
12395 TREE_CODE (orig_for_stmt));
12397 int kind;
12398 switch (TREE_CODE (orig_for_stmt))
12400 case OMP_FOR: kind = GF_OMP_FOR_KIND_FOR; break;
12401 case OMP_SIMD: kind = GF_OMP_FOR_KIND_SIMD; break;
12402 case OMP_DISTRIBUTE: kind = GF_OMP_FOR_KIND_DISTRIBUTE; break;
12403 case OMP_TASKLOOP: kind = GF_OMP_FOR_KIND_TASKLOOP; break;
12404 case OACC_LOOP: kind = GF_OMP_FOR_KIND_OACC_LOOP; break;
12405 default:
12406 gcc_unreachable ();
12408 if (loop_p && kind == GF_OMP_FOR_KIND_SIMD)
12410 gimplify_seq_add_seq (pre_p, for_pre_body);
12411 for_pre_body = NULL;
12413 gfor = gimple_build_omp_for (for_body, kind, OMP_FOR_CLAUSES (orig_for_stmt),
12414 TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)),
12415 for_pre_body);
12416 if (orig_for_stmt != for_stmt)
12417 gimple_omp_for_set_combined_p (gfor, true);
12418 if (gimplify_omp_ctxp
12419 && (gimplify_omp_ctxp->combined_loop
12420 || (gimplify_omp_ctxp->region_type == ORT_COMBINED_PARALLEL
12421 && gimplify_omp_ctxp->outer_context
12422 && gimplify_omp_ctxp->outer_context->combined_loop)))
12424 gimple_omp_for_set_combined_into_p (gfor, true);
12425 if (gimplify_omp_ctxp->combined_loop)
12426 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_SIMD);
12427 else
12428 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_FOR);
12431 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
12433 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
12434 gimple_omp_for_set_index (gfor, i, TREE_OPERAND (t, 0));
12435 gimple_omp_for_set_initial (gfor, i, TREE_OPERAND (t, 1));
12436 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
12437 gimple_omp_for_set_cond (gfor, i, TREE_CODE (t));
12438 gimple_omp_for_set_final (gfor, i, TREE_OPERAND (t, 1));
12439 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
12440 gimple_omp_for_set_incr (gfor, i, TREE_OPERAND (t, 1));
12443 /* OMP_TASKLOOP is gimplified as two GIMPLE_OMP_FOR taskloop
12444 constructs with GIMPLE_OMP_TASK sandwiched in between them.
12445 The outer taskloop stands for computing the number of iterations,
12446 counts for collapsed loops and holding taskloop specific clauses.
12447 The task construct stands for the effect of data sharing on the
12448 explicit task it creates and the inner taskloop stands for expansion
12449 of the static loop inside of the explicit task construct. */
12450 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
12452 tree *gfor_clauses_ptr = gimple_omp_for_clauses_ptr (gfor);
12453 tree task_clauses = NULL_TREE;
12454 tree c = *gfor_clauses_ptr;
12455 tree *gtask_clauses_ptr = &task_clauses;
12456 tree outer_for_clauses = NULL_TREE;
12457 tree *gforo_clauses_ptr = &outer_for_clauses;
12458 bitmap lastprivate_uids = NULL;
12459 if (omp_find_clause (c, OMP_CLAUSE_ALLOCATE))
12461 c = omp_find_clause (c, OMP_CLAUSE_LASTPRIVATE);
12462 if (c)
12464 lastprivate_uids = BITMAP_ALLOC (NULL);
12465 for (; c; c = omp_find_clause (OMP_CLAUSE_CHAIN (c),
12466 OMP_CLAUSE_LASTPRIVATE))
12467 bitmap_set_bit (lastprivate_uids,
12468 DECL_UID (OMP_CLAUSE_DECL (c)));
12470 c = *gfor_clauses_ptr;
12472 for (; c; c = OMP_CLAUSE_CHAIN (c))
12473 switch (OMP_CLAUSE_CODE (c))
12475 /* These clauses are allowed on task, move them there. */
12476 case OMP_CLAUSE_SHARED:
12477 case OMP_CLAUSE_FIRSTPRIVATE:
12478 case OMP_CLAUSE_DEFAULT:
12479 case OMP_CLAUSE_IF:
12480 case OMP_CLAUSE_UNTIED:
12481 case OMP_CLAUSE_FINAL:
12482 case OMP_CLAUSE_MERGEABLE:
12483 case OMP_CLAUSE_PRIORITY:
12484 case OMP_CLAUSE_REDUCTION:
12485 case OMP_CLAUSE_IN_REDUCTION:
12486 *gtask_clauses_ptr = c;
12487 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12488 break;
12489 case OMP_CLAUSE_PRIVATE:
12490 if (OMP_CLAUSE_PRIVATE_TASKLOOP_IV (c))
12492 /* We want private on outer for and firstprivate
12493 on task. */
12494 *gtask_clauses_ptr
12495 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
12496 OMP_CLAUSE_FIRSTPRIVATE);
12497 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
12498 lang_hooks.decls.omp_finish_clause (*gtask_clauses_ptr, NULL,
12499 openacc);
12500 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
12501 *gforo_clauses_ptr = c;
12502 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12504 else
12506 *gtask_clauses_ptr = c;
12507 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12509 break;
12510 /* These clauses go into outer taskloop clauses. */
12511 case OMP_CLAUSE_GRAINSIZE:
12512 case OMP_CLAUSE_NUM_TASKS:
12513 case OMP_CLAUSE_NOGROUP:
12514 *gforo_clauses_ptr = c;
12515 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12516 break;
12517 /* Collapse clause we duplicate on both taskloops. */
12518 case OMP_CLAUSE_COLLAPSE:
12519 *gfor_clauses_ptr = c;
12520 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12521 *gforo_clauses_ptr = copy_node (c);
12522 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr);
12523 break;
12524 /* For lastprivate, keep the clause on inner taskloop, and add
12525 a shared clause on task. If the same decl is also firstprivate,
12526 add also firstprivate clause on the inner taskloop. */
12527 case OMP_CLAUSE_LASTPRIVATE:
12528 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c))
12530 /* For taskloop C++ lastprivate IVs, we want:
12531 1) private on outer taskloop
12532 2) firstprivate and shared on task
12533 3) lastprivate on inner taskloop */
12534 *gtask_clauses_ptr
12535 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
12536 OMP_CLAUSE_FIRSTPRIVATE);
12537 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
12538 lang_hooks.decls.omp_finish_clause (*gtask_clauses_ptr, NULL,
12539 openacc);
12540 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
12541 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c) = 1;
12542 *gforo_clauses_ptr = build_omp_clause (OMP_CLAUSE_LOCATION (c),
12543 OMP_CLAUSE_PRIVATE);
12544 OMP_CLAUSE_DECL (*gforo_clauses_ptr) = OMP_CLAUSE_DECL (c);
12545 OMP_CLAUSE_PRIVATE_TASKLOOP_IV (*gforo_clauses_ptr) = 1;
12546 TREE_TYPE (*gforo_clauses_ptr) = TREE_TYPE (c);
12547 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr);
12549 *gfor_clauses_ptr = c;
12550 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12551 *gtask_clauses_ptr
12552 = build_omp_clause (OMP_CLAUSE_LOCATION (c), OMP_CLAUSE_SHARED);
12553 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
12554 if (OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
12555 OMP_CLAUSE_SHARED_FIRSTPRIVATE (*gtask_clauses_ptr) = 1;
12556 gtask_clauses_ptr
12557 = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
12558 break;
12559 /* Allocate clause we duplicate on task and inner taskloop
12560 if the decl is lastprivate, otherwise just put on task. */
12561 case OMP_CLAUSE_ALLOCATE:
12562 if (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
12563 && DECL_P (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)))
12565 /* Additionally, put firstprivate clause on task
12566 for the allocator if it is not constant. */
12567 *gtask_clauses_ptr
12568 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
12569 OMP_CLAUSE_FIRSTPRIVATE);
12570 OMP_CLAUSE_DECL (*gtask_clauses_ptr)
12571 = OMP_CLAUSE_ALLOCATE_ALLOCATOR (c);
12572 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
12574 if (lastprivate_uids
12575 && bitmap_bit_p (lastprivate_uids,
12576 DECL_UID (OMP_CLAUSE_DECL (c))))
12578 *gfor_clauses_ptr = c;
12579 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12580 *gtask_clauses_ptr = copy_node (c);
12581 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
12583 else
12585 *gtask_clauses_ptr = c;
12586 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12588 break;
12589 default:
12590 gcc_unreachable ();
12592 *gfor_clauses_ptr = NULL_TREE;
12593 *gtask_clauses_ptr = NULL_TREE;
12594 *gforo_clauses_ptr = NULL_TREE;
12595 BITMAP_FREE (lastprivate_uids);
12596 g = gimple_build_bind (NULL_TREE, gfor, NULL_TREE);
12597 g = gimple_build_omp_task (g, task_clauses, NULL_TREE, NULL_TREE,
12598 NULL_TREE, NULL_TREE, NULL_TREE);
12599 gimple_omp_task_set_taskloop_p (g, true);
12600 g = gimple_build_bind (NULL_TREE, g, NULL_TREE);
12601 gomp_for *gforo
12602 = gimple_build_omp_for (g, GF_OMP_FOR_KIND_TASKLOOP, outer_for_clauses,
12603 gimple_omp_for_collapse (gfor),
12604 gimple_omp_for_pre_body (gfor));
12605 gimple_omp_for_set_pre_body (gfor, NULL);
12606 gimple_omp_for_set_combined_p (gforo, true);
12607 gimple_omp_for_set_combined_into_p (gfor, true);
12608 for (i = 0; i < (int) gimple_omp_for_collapse (gfor); i++)
12610 tree type = TREE_TYPE (gimple_omp_for_index (gfor, i));
12611 tree v = create_tmp_var (type);
12612 gimple_omp_for_set_index (gforo, i, v);
12613 t = unshare_expr (gimple_omp_for_initial (gfor, i));
12614 gimple_omp_for_set_initial (gforo, i, t);
12615 gimple_omp_for_set_cond (gforo, i,
12616 gimple_omp_for_cond (gfor, i));
12617 t = unshare_expr (gimple_omp_for_final (gfor, i));
12618 gimple_omp_for_set_final (gforo, i, t);
12619 t = unshare_expr (gimple_omp_for_incr (gfor, i));
12620 gcc_assert (TREE_OPERAND (t, 0) == gimple_omp_for_index (gfor, i));
12621 TREE_OPERAND (t, 0) = v;
12622 gimple_omp_for_set_incr (gforo, i, t);
12623 t = build_omp_clause (input_location, OMP_CLAUSE_PRIVATE);
12624 OMP_CLAUSE_DECL (t) = v;
12625 OMP_CLAUSE_CHAIN (t) = gimple_omp_for_clauses (gforo);
12626 gimple_omp_for_set_clauses (gforo, t);
12627 if (OMP_FOR_NON_RECTANGULAR (for_stmt))
12629 tree *p1 = NULL, *p2 = NULL;
12630 t = gimple_omp_for_initial (gforo, i);
12631 if (TREE_CODE (t) == TREE_VEC)
12632 p1 = &TREE_VEC_ELT (t, 0);
12633 t = gimple_omp_for_final (gforo, i);
12634 if (TREE_CODE (t) == TREE_VEC)
12636 if (p1)
12637 p2 = &TREE_VEC_ELT (t, 0);
12638 else
12639 p1 = &TREE_VEC_ELT (t, 0);
12641 if (p1)
12643 int j;
12644 for (j = 0; j < i; j++)
12645 if (*p1 == gimple_omp_for_index (gfor, j))
12647 *p1 = gimple_omp_for_index (gforo, j);
12648 if (p2)
12649 *p2 = *p1;
12650 break;
12652 gcc_assert (j < i);
12656 gimplify_seq_add_stmt (pre_p, gforo);
12658 else
12659 gimplify_seq_add_stmt (pre_p, gfor);
12661 if (TREE_CODE (orig_for_stmt) == OMP_FOR)
12663 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
12664 unsigned lastprivate_conditional = 0;
12665 while (ctx
12666 && (ctx->region_type == ORT_TARGET_DATA
12667 || ctx->region_type == ORT_TASKGROUP))
12668 ctx = ctx->outer_context;
12669 if (ctx && (ctx->region_type & ORT_PARALLEL) != 0)
12670 for (tree c = gimple_omp_for_clauses (gfor);
12671 c; c = OMP_CLAUSE_CHAIN (c))
12672 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
12673 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
12674 ++lastprivate_conditional;
12675 if (lastprivate_conditional)
12677 struct omp_for_data fd;
12678 omp_extract_for_data (gfor, &fd, NULL);
12679 tree type = build_array_type_nelts (unsigned_type_for (fd.iter_type),
12680 lastprivate_conditional);
12681 tree var = create_tmp_var_raw (type);
12682 tree c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE__CONDTEMP_);
12683 OMP_CLAUSE_DECL (c) = var;
12684 OMP_CLAUSE_CHAIN (c) = gimple_omp_for_clauses (gfor);
12685 gimple_omp_for_set_clauses (gfor, c);
12686 omp_add_variable (ctx, var, GOVD_CONDTEMP | GOVD_SEEN);
12689 else if (TREE_CODE (orig_for_stmt) == OMP_SIMD)
12691 unsigned lastprivate_conditional = 0;
12692 for (tree c = gimple_omp_for_clauses (gfor); c; c = OMP_CLAUSE_CHAIN (c))
12693 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
12694 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
12695 ++lastprivate_conditional;
12696 if (lastprivate_conditional)
12698 struct omp_for_data fd;
12699 omp_extract_for_data (gfor, &fd, NULL);
12700 tree type = unsigned_type_for (fd.iter_type);
12701 while (lastprivate_conditional--)
12703 tree c = build_omp_clause (UNKNOWN_LOCATION,
12704 OMP_CLAUSE__CONDTEMP_);
12705 OMP_CLAUSE_DECL (c) = create_tmp_var (type);
12706 OMP_CLAUSE_CHAIN (c) = gimple_omp_for_clauses (gfor);
12707 gimple_omp_for_set_clauses (gfor, c);
12712 if (ret != GS_ALL_DONE)
12713 return GS_ERROR;
12714 *expr_p = NULL_TREE;
12715 return GS_ALL_DONE;
12718 /* Helper for gimplify_omp_loop, called through walk_tree. */
12720 static tree
12721 replace_reduction_placeholders (tree *tp, int *walk_subtrees, void *data)
12723 if (DECL_P (*tp))
12725 tree *d = (tree *) data;
12726 if (*tp == OMP_CLAUSE_REDUCTION_PLACEHOLDER (d[0]))
12728 *tp = OMP_CLAUSE_REDUCTION_PLACEHOLDER (d[1]);
12729 *walk_subtrees = 0;
12731 else if (*tp == OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (d[0]))
12733 *tp = OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (d[1]);
12734 *walk_subtrees = 0;
12737 return NULL_TREE;
12740 /* Gimplify the gross structure of an OMP_LOOP statement. */
12742 static enum gimplify_status
12743 gimplify_omp_loop (tree *expr_p, gimple_seq *pre_p)
12745 tree for_stmt = *expr_p;
12746 tree clauses = OMP_FOR_CLAUSES (for_stmt);
12747 struct gimplify_omp_ctx *octx = gimplify_omp_ctxp;
12748 enum omp_clause_bind_kind kind = OMP_CLAUSE_BIND_THREAD;
12749 int i;
12751 /* If order is not present, the behavior is as if order(concurrent)
12752 appeared. */
12753 tree order = omp_find_clause (clauses, OMP_CLAUSE_ORDER);
12754 if (order == NULL_TREE)
12756 order = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_ORDER);
12757 OMP_CLAUSE_CHAIN (order) = clauses;
12758 OMP_FOR_CLAUSES (for_stmt) = clauses = order;
12761 tree bind = omp_find_clause (clauses, OMP_CLAUSE_BIND);
12762 if (bind == NULL_TREE)
12764 if (!flag_openmp) /* flag_openmp_simd */
12766 else if (octx && (octx->region_type & ORT_TEAMS) != 0)
12767 kind = OMP_CLAUSE_BIND_TEAMS;
12768 else if (octx && (octx->region_type & ORT_PARALLEL) != 0)
12769 kind = OMP_CLAUSE_BIND_PARALLEL;
12770 else
12772 for (; octx; octx = octx->outer_context)
12774 if ((octx->region_type & ORT_ACC) != 0
12775 || octx->region_type == ORT_NONE
12776 || octx->region_type == ORT_IMPLICIT_TARGET)
12777 continue;
12778 break;
12780 if (octx == NULL && !in_omp_construct)
12781 error_at (EXPR_LOCATION (for_stmt),
12782 "%<bind%> clause not specified on a %<loop%> "
12783 "construct not nested inside another OpenMP construct");
12785 bind = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_BIND);
12786 OMP_CLAUSE_CHAIN (bind) = clauses;
12787 OMP_CLAUSE_BIND_KIND (bind) = kind;
12788 OMP_FOR_CLAUSES (for_stmt) = bind;
12790 else
12791 switch (OMP_CLAUSE_BIND_KIND (bind))
12793 case OMP_CLAUSE_BIND_THREAD:
12794 break;
12795 case OMP_CLAUSE_BIND_PARALLEL:
12796 if (!flag_openmp) /* flag_openmp_simd */
12798 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
12799 break;
12801 for (; octx; octx = octx->outer_context)
12802 if (octx->region_type == ORT_SIMD
12803 && omp_find_clause (octx->clauses, OMP_CLAUSE_BIND) == NULL_TREE)
12805 error_at (EXPR_LOCATION (for_stmt),
12806 "%<bind(parallel)%> on a %<loop%> construct nested "
12807 "inside %<simd%> construct");
12808 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
12809 break;
12811 kind = OMP_CLAUSE_BIND_PARALLEL;
12812 break;
12813 case OMP_CLAUSE_BIND_TEAMS:
12814 if (!flag_openmp) /* flag_openmp_simd */
12816 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
12817 break;
12819 if ((octx
12820 && octx->region_type != ORT_IMPLICIT_TARGET
12821 && octx->region_type != ORT_NONE
12822 && (octx->region_type & ORT_TEAMS) == 0)
12823 || in_omp_construct)
12825 error_at (EXPR_LOCATION (for_stmt),
12826 "%<bind(teams)%> on a %<loop%> region not strictly "
12827 "nested inside of a %<teams%> region");
12828 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
12829 break;
12831 kind = OMP_CLAUSE_BIND_TEAMS;
12832 break;
12833 default:
12834 gcc_unreachable ();
12837 for (tree *pc = &OMP_FOR_CLAUSES (for_stmt); *pc; )
12838 switch (OMP_CLAUSE_CODE (*pc))
12840 case OMP_CLAUSE_REDUCTION:
12841 if (OMP_CLAUSE_REDUCTION_INSCAN (*pc))
12843 error_at (OMP_CLAUSE_LOCATION (*pc),
12844 "%<inscan%> %<reduction%> clause on "
12845 "%qs construct", "loop");
12846 OMP_CLAUSE_REDUCTION_INSCAN (*pc) = 0;
12848 if (OMP_CLAUSE_REDUCTION_TASK (*pc))
12850 error_at (OMP_CLAUSE_LOCATION (*pc),
12851 "invalid %<task%> reduction modifier on construct "
12852 "other than %<parallel%>, %qs or %<sections%>",
12853 lang_GNU_Fortran () ? "do" : "for");
12854 OMP_CLAUSE_REDUCTION_TASK (*pc) = 0;
12856 pc = &OMP_CLAUSE_CHAIN (*pc);
12857 break;
12858 case OMP_CLAUSE_LASTPRIVATE:
12859 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
12861 tree t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
12862 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
12863 if (OMP_CLAUSE_DECL (*pc) == TREE_OPERAND (t, 0))
12864 break;
12865 if (OMP_FOR_ORIG_DECLS (for_stmt)
12866 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt),
12867 i)) == TREE_LIST
12868 && TREE_PURPOSE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt),
12869 i)))
12871 tree orig = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
12872 if (OMP_CLAUSE_DECL (*pc) == TREE_PURPOSE (orig))
12873 break;
12876 if (i == TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)))
12878 error_at (OMP_CLAUSE_LOCATION (*pc),
12879 "%<lastprivate%> clause on a %<loop%> construct refers "
12880 "to a variable %qD which is not the loop iterator",
12881 OMP_CLAUSE_DECL (*pc));
12882 *pc = OMP_CLAUSE_CHAIN (*pc);
12883 break;
12885 pc = &OMP_CLAUSE_CHAIN (*pc);
12886 break;
12887 default:
12888 pc = &OMP_CLAUSE_CHAIN (*pc);
12889 break;
12892 TREE_SET_CODE (for_stmt, OMP_SIMD);
12894 int last;
12895 switch (kind)
12897 case OMP_CLAUSE_BIND_THREAD: last = 0; break;
12898 case OMP_CLAUSE_BIND_PARALLEL: last = 1; break;
12899 case OMP_CLAUSE_BIND_TEAMS: last = 2; break;
12901 for (int pass = 1; pass <= last; pass++)
12903 if (pass == 2)
12905 tree bind = build3 (BIND_EXPR, void_type_node, NULL, NULL, NULL);
12906 append_to_statement_list (*expr_p, &BIND_EXPR_BODY (bind));
12907 *expr_p = make_node (OMP_PARALLEL);
12908 TREE_TYPE (*expr_p) = void_type_node;
12909 OMP_PARALLEL_BODY (*expr_p) = bind;
12910 OMP_PARALLEL_COMBINED (*expr_p) = 1;
12911 SET_EXPR_LOCATION (*expr_p, EXPR_LOCATION (for_stmt));
12912 tree *pc = &OMP_PARALLEL_CLAUSES (*expr_p);
12913 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
12914 if (OMP_FOR_ORIG_DECLS (for_stmt)
12915 && (TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i))
12916 == TREE_LIST))
12918 tree elt = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
12919 if (TREE_PURPOSE (elt) && TREE_VALUE (elt))
12921 *pc = build_omp_clause (UNKNOWN_LOCATION,
12922 OMP_CLAUSE_FIRSTPRIVATE);
12923 OMP_CLAUSE_DECL (*pc) = TREE_VALUE (elt);
12924 pc = &OMP_CLAUSE_CHAIN (*pc);
12928 tree t = make_node (pass == 2 ? OMP_DISTRIBUTE : OMP_FOR);
12929 tree *pc = &OMP_FOR_CLAUSES (t);
12930 TREE_TYPE (t) = void_type_node;
12931 OMP_FOR_BODY (t) = *expr_p;
12932 SET_EXPR_LOCATION (t, EXPR_LOCATION (for_stmt));
12933 for (tree c = OMP_FOR_CLAUSES (for_stmt); c; c = OMP_CLAUSE_CHAIN (c))
12934 switch (OMP_CLAUSE_CODE (c))
12936 case OMP_CLAUSE_BIND:
12937 case OMP_CLAUSE_ORDER:
12938 case OMP_CLAUSE_COLLAPSE:
12939 *pc = copy_node (c);
12940 pc = &OMP_CLAUSE_CHAIN (*pc);
12941 break;
12942 case OMP_CLAUSE_PRIVATE:
12943 case OMP_CLAUSE_FIRSTPRIVATE:
12944 /* Only needed on innermost. */
12945 break;
12946 case OMP_CLAUSE_LASTPRIVATE:
12947 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c) && pass != last)
12949 *pc = build_omp_clause (OMP_CLAUSE_LOCATION (c),
12950 OMP_CLAUSE_FIRSTPRIVATE);
12951 OMP_CLAUSE_DECL (*pc) = OMP_CLAUSE_DECL (c);
12952 lang_hooks.decls.omp_finish_clause (*pc, NULL, false);
12953 pc = &OMP_CLAUSE_CHAIN (*pc);
12955 *pc = copy_node (c);
12956 OMP_CLAUSE_LASTPRIVATE_STMT (*pc) = NULL_TREE;
12957 TREE_TYPE (*pc) = unshare_expr (TREE_TYPE (c));
12958 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c))
12960 if (pass != last)
12961 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (*pc) = 1;
12962 else
12963 lang_hooks.decls.omp_finish_clause (*pc, NULL, false);
12964 OMP_CLAUSE_LASTPRIVATE_LOOP_IV (*pc) = 0;
12966 pc = &OMP_CLAUSE_CHAIN (*pc);
12967 break;
12968 case OMP_CLAUSE_REDUCTION:
12969 *pc = copy_node (c);
12970 OMP_CLAUSE_DECL (*pc) = unshare_expr (OMP_CLAUSE_DECL (c));
12971 TREE_TYPE (*pc) = unshare_expr (TREE_TYPE (c));
12972 OMP_CLAUSE_REDUCTION_INIT (*pc)
12973 = unshare_expr (OMP_CLAUSE_REDUCTION_INIT (c));
12974 OMP_CLAUSE_REDUCTION_MERGE (*pc)
12975 = unshare_expr (OMP_CLAUSE_REDUCTION_MERGE (c));
12976 if (OMP_CLAUSE_REDUCTION_PLACEHOLDER (*pc))
12978 OMP_CLAUSE_REDUCTION_PLACEHOLDER (*pc)
12979 = copy_node (OMP_CLAUSE_REDUCTION_PLACEHOLDER (c));
12980 if (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (*pc))
12981 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (*pc)
12982 = copy_node (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c));
12983 tree nc = *pc;
12984 tree data[2] = { c, nc };
12985 walk_tree_without_duplicates (&OMP_CLAUSE_REDUCTION_INIT (nc),
12986 replace_reduction_placeholders,
12987 data);
12988 walk_tree_without_duplicates (&OMP_CLAUSE_REDUCTION_MERGE (nc),
12989 replace_reduction_placeholders,
12990 data);
12992 pc = &OMP_CLAUSE_CHAIN (*pc);
12993 break;
12994 default:
12995 gcc_unreachable ();
12997 *pc = NULL_TREE;
12998 *expr_p = t;
13000 return gimplify_omp_for (expr_p, pre_p);
13004 /* Helper function of optimize_target_teams, find OMP_TEAMS inside
13005 of OMP_TARGET's body. */
13007 static tree
13008 find_omp_teams (tree *tp, int *walk_subtrees, void *)
13010 *walk_subtrees = 0;
13011 switch (TREE_CODE (*tp))
13013 case OMP_TEAMS:
13014 return *tp;
13015 case BIND_EXPR:
13016 case STATEMENT_LIST:
13017 *walk_subtrees = 1;
13018 break;
13019 default:
13020 break;
13022 return NULL_TREE;
13025 /* Helper function of optimize_target_teams, determine if the expression
13026 can be computed safely before the target construct on the host. */
13028 static tree
13029 computable_teams_clause (tree *tp, int *walk_subtrees, void *)
13031 splay_tree_node n;
13033 if (TYPE_P (*tp))
13035 *walk_subtrees = 0;
13036 return NULL_TREE;
13038 switch (TREE_CODE (*tp))
13040 case VAR_DECL:
13041 case PARM_DECL:
13042 case RESULT_DECL:
13043 *walk_subtrees = 0;
13044 if (error_operand_p (*tp)
13045 || !INTEGRAL_TYPE_P (TREE_TYPE (*tp))
13046 || DECL_HAS_VALUE_EXPR_P (*tp)
13047 || DECL_THREAD_LOCAL_P (*tp)
13048 || TREE_SIDE_EFFECTS (*tp)
13049 || TREE_THIS_VOLATILE (*tp))
13050 return *tp;
13051 if (is_global_var (*tp)
13052 && (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (*tp))
13053 || lookup_attribute ("omp declare target link",
13054 DECL_ATTRIBUTES (*tp))))
13055 return *tp;
13056 if (VAR_P (*tp)
13057 && !DECL_SEEN_IN_BIND_EXPR_P (*tp)
13058 && !is_global_var (*tp)
13059 && decl_function_context (*tp) == current_function_decl)
13060 return *tp;
13061 n = splay_tree_lookup (gimplify_omp_ctxp->variables,
13062 (splay_tree_key) *tp);
13063 if (n == NULL)
13065 if (gimplify_omp_ctxp->defaultmap[GDMK_SCALAR] & GOVD_FIRSTPRIVATE)
13066 return NULL_TREE;
13067 return *tp;
13069 else if (n->value & GOVD_LOCAL)
13070 return *tp;
13071 else if (n->value & GOVD_FIRSTPRIVATE)
13072 return NULL_TREE;
13073 else if ((n->value & (GOVD_MAP | GOVD_MAP_ALWAYS_TO))
13074 == (GOVD_MAP | GOVD_MAP_ALWAYS_TO))
13075 return NULL_TREE;
13076 return *tp;
13077 case INTEGER_CST:
13078 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp)))
13079 return *tp;
13080 return NULL_TREE;
13081 case TARGET_EXPR:
13082 if (TARGET_EXPR_INITIAL (*tp)
13083 || TREE_CODE (TARGET_EXPR_SLOT (*tp)) != VAR_DECL)
13084 return *tp;
13085 return computable_teams_clause (&TARGET_EXPR_SLOT (*tp),
13086 walk_subtrees, NULL);
13087 /* Allow some reasonable subset of integral arithmetics. */
13088 case PLUS_EXPR:
13089 case MINUS_EXPR:
13090 case MULT_EXPR:
13091 case TRUNC_DIV_EXPR:
13092 case CEIL_DIV_EXPR:
13093 case FLOOR_DIV_EXPR:
13094 case ROUND_DIV_EXPR:
13095 case TRUNC_MOD_EXPR:
13096 case CEIL_MOD_EXPR:
13097 case FLOOR_MOD_EXPR:
13098 case ROUND_MOD_EXPR:
13099 case RDIV_EXPR:
13100 case EXACT_DIV_EXPR:
13101 case MIN_EXPR:
13102 case MAX_EXPR:
13103 case LSHIFT_EXPR:
13104 case RSHIFT_EXPR:
13105 case BIT_IOR_EXPR:
13106 case BIT_XOR_EXPR:
13107 case BIT_AND_EXPR:
13108 case NEGATE_EXPR:
13109 case ABS_EXPR:
13110 case BIT_NOT_EXPR:
13111 case NON_LVALUE_EXPR:
13112 CASE_CONVERT:
13113 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp)))
13114 return *tp;
13115 return NULL_TREE;
13116 /* And disallow anything else, except for comparisons. */
13117 default:
13118 if (COMPARISON_CLASS_P (*tp))
13119 return NULL_TREE;
13120 return *tp;
13124 /* Try to determine if the num_teams and/or thread_limit expressions
13125 can have their values determined already before entering the
13126 target construct.
13127 INTEGER_CSTs trivially are,
13128 integral decls that are firstprivate (explicitly or implicitly)
13129 or explicitly map(always, to:) or map(always, tofrom:) on the target
13130 region too, and expressions involving simple arithmetics on those
13131 too, function calls are not ok, dereferencing something neither etc.
13132 Add NUM_TEAMS and THREAD_LIMIT clauses to the OMP_CLAUSES of
13133 EXPR based on what we find:
13134 0 stands for clause not specified at all, use implementation default
13135 -1 stands for value that can't be determined easily before entering
13136 the target construct.
13137 If teams construct is not present at all, use 1 for num_teams
13138 and 0 for thread_limit (only one team is involved, and the thread
13139 limit is implementation defined. */
13141 static void
13142 optimize_target_teams (tree target, gimple_seq *pre_p)
13144 tree body = OMP_BODY (target);
13145 tree teams = walk_tree (&body, find_omp_teams, NULL, NULL);
13146 tree num_teams = integer_zero_node;
13147 tree thread_limit = integer_zero_node;
13148 location_t num_teams_loc = EXPR_LOCATION (target);
13149 location_t thread_limit_loc = EXPR_LOCATION (target);
13150 tree c, *p, expr;
13151 struct gimplify_omp_ctx *target_ctx = gimplify_omp_ctxp;
13153 if (teams == NULL_TREE)
13154 num_teams = integer_one_node;
13155 else
13156 for (c = OMP_TEAMS_CLAUSES (teams); c; c = OMP_CLAUSE_CHAIN (c))
13158 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_NUM_TEAMS)
13160 p = &num_teams;
13161 num_teams_loc = OMP_CLAUSE_LOCATION (c);
13163 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_THREAD_LIMIT)
13165 p = &thread_limit;
13166 thread_limit_loc = OMP_CLAUSE_LOCATION (c);
13168 else
13169 continue;
13170 expr = OMP_CLAUSE_OPERAND (c, 0);
13171 if (TREE_CODE (expr) == INTEGER_CST)
13173 *p = expr;
13174 continue;
13176 if (walk_tree (&expr, computable_teams_clause, NULL, NULL))
13178 *p = integer_minus_one_node;
13179 continue;
13181 *p = expr;
13182 gimplify_omp_ctxp = gimplify_omp_ctxp->outer_context;
13183 if (gimplify_expr (p, pre_p, NULL, is_gimple_val, fb_rvalue, false)
13184 == GS_ERROR)
13186 gimplify_omp_ctxp = target_ctx;
13187 *p = integer_minus_one_node;
13188 continue;
13190 gimplify_omp_ctxp = target_ctx;
13191 if (!DECL_P (expr) && TREE_CODE (expr) != TARGET_EXPR)
13192 OMP_CLAUSE_OPERAND (c, 0) = *p;
13194 c = build_omp_clause (thread_limit_loc, OMP_CLAUSE_THREAD_LIMIT);
13195 OMP_CLAUSE_THREAD_LIMIT_EXPR (c) = thread_limit;
13196 OMP_CLAUSE_CHAIN (c) = OMP_TARGET_CLAUSES (target);
13197 OMP_TARGET_CLAUSES (target) = c;
13198 c = build_omp_clause (num_teams_loc, OMP_CLAUSE_NUM_TEAMS);
13199 OMP_CLAUSE_NUM_TEAMS_EXPR (c) = num_teams;
13200 OMP_CLAUSE_CHAIN (c) = OMP_TARGET_CLAUSES (target);
13201 OMP_TARGET_CLAUSES (target) = c;
13204 /* Gimplify the gross structure of several OMP constructs. */
13206 static void
13207 gimplify_omp_workshare (tree *expr_p, gimple_seq *pre_p)
13209 tree expr = *expr_p;
13210 gimple *stmt;
13211 gimple_seq body = NULL;
13212 enum omp_region_type ort;
13214 switch (TREE_CODE (expr))
13216 case OMP_SECTIONS:
13217 case OMP_SINGLE:
13218 ort = ORT_WORKSHARE;
13219 break;
13220 case OMP_TARGET:
13221 ort = OMP_TARGET_COMBINED (expr) ? ORT_COMBINED_TARGET : ORT_TARGET;
13222 break;
13223 case OACC_KERNELS:
13224 ort = ORT_ACC_KERNELS;
13225 break;
13226 case OACC_PARALLEL:
13227 ort = ORT_ACC_PARALLEL;
13228 break;
13229 case OACC_SERIAL:
13230 ort = ORT_ACC_SERIAL;
13231 break;
13232 case OACC_DATA:
13233 ort = ORT_ACC_DATA;
13234 break;
13235 case OMP_TARGET_DATA:
13236 ort = ORT_TARGET_DATA;
13237 break;
13238 case OMP_TEAMS:
13239 ort = OMP_TEAMS_COMBINED (expr) ? ORT_COMBINED_TEAMS : ORT_TEAMS;
13240 if (gimplify_omp_ctxp == NULL
13241 || gimplify_omp_ctxp->region_type == ORT_IMPLICIT_TARGET)
13242 ort = (enum omp_region_type) (ort | ORT_HOST_TEAMS);
13243 break;
13244 case OACC_HOST_DATA:
13245 ort = ORT_ACC_HOST_DATA;
13246 break;
13247 default:
13248 gcc_unreachable ();
13251 bool save_in_omp_construct = in_omp_construct;
13252 if ((ort & ORT_ACC) == 0)
13253 in_omp_construct = false;
13254 gimplify_scan_omp_clauses (&OMP_CLAUSES (expr), pre_p, ort,
13255 TREE_CODE (expr));
13256 if (TREE_CODE (expr) == OMP_TARGET)
13257 optimize_target_teams (expr, pre_p);
13258 if ((ort & (ORT_TARGET | ORT_TARGET_DATA)) != 0
13259 || (ort & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
13261 push_gimplify_context ();
13262 gimple *g = gimplify_and_return_first (OMP_BODY (expr), &body);
13263 if (gimple_code (g) == GIMPLE_BIND)
13264 pop_gimplify_context (g);
13265 else
13266 pop_gimplify_context (NULL);
13267 if ((ort & ORT_TARGET_DATA) != 0)
13269 enum built_in_function end_ix;
13270 switch (TREE_CODE (expr))
13272 case OACC_DATA:
13273 case OACC_HOST_DATA:
13274 end_ix = BUILT_IN_GOACC_DATA_END;
13275 break;
13276 case OMP_TARGET_DATA:
13277 end_ix = BUILT_IN_GOMP_TARGET_END_DATA;
13278 break;
13279 default:
13280 gcc_unreachable ();
13282 tree fn = builtin_decl_explicit (end_ix);
13283 g = gimple_build_call (fn, 0);
13284 gimple_seq cleanup = NULL;
13285 gimple_seq_add_stmt (&cleanup, g);
13286 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
13287 body = NULL;
13288 gimple_seq_add_stmt (&body, g);
13291 else
13292 gimplify_and_add (OMP_BODY (expr), &body);
13293 gimplify_adjust_omp_clauses (pre_p, body, &OMP_CLAUSES (expr),
13294 TREE_CODE (expr));
13295 in_omp_construct = save_in_omp_construct;
13297 switch (TREE_CODE (expr))
13299 case OACC_DATA:
13300 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_DATA,
13301 OMP_CLAUSES (expr));
13302 break;
13303 case OACC_HOST_DATA:
13304 if (omp_find_clause (OMP_CLAUSES (expr), OMP_CLAUSE_IF_PRESENT))
13306 for (tree c = OMP_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
13307 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_USE_DEVICE_PTR)
13308 OMP_CLAUSE_USE_DEVICE_PTR_IF_PRESENT (c) = 1;
13311 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_HOST_DATA,
13312 OMP_CLAUSES (expr));
13313 break;
13314 case OACC_KERNELS:
13315 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_KERNELS,
13316 OMP_CLAUSES (expr));
13317 break;
13318 case OACC_PARALLEL:
13319 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_PARALLEL,
13320 OMP_CLAUSES (expr));
13321 break;
13322 case OACC_SERIAL:
13323 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_SERIAL,
13324 OMP_CLAUSES (expr));
13325 break;
13326 case OMP_SECTIONS:
13327 stmt = gimple_build_omp_sections (body, OMP_CLAUSES (expr));
13328 break;
13329 case OMP_SINGLE:
13330 stmt = gimple_build_omp_single (body, OMP_CLAUSES (expr));
13331 break;
13332 case OMP_TARGET:
13333 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_REGION,
13334 OMP_CLAUSES (expr));
13335 break;
13336 case OMP_TARGET_DATA:
13337 /* Put use_device_{ptr,addr} clauses last, as map clauses are supposed
13338 to be evaluated before the use_device_{ptr,addr} clauses if they
13339 refer to the same variables. */
13341 tree use_device_clauses;
13342 tree *pc, *uc = &use_device_clauses;
13343 for (pc = &OMP_CLAUSES (expr); *pc; )
13344 if (OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_USE_DEVICE_PTR
13345 || OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_USE_DEVICE_ADDR)
13347 *uc = *pc;
13348 *pc = OMP_CLAUSE_CHAIN (*pc);
13349 uc = &OMP_CLAUSE_CHAIN (*uc);
13351 else
13352 pc = &OMP_CLAUSE_CHAIN (*pc);
13353 *uc = NULL_TREE;
13354 *pc = use_device_clauses;
13355 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_DATA,
13356 OMP_CLAUSES (expr));
13358 break;
13359 case OMP_TEAMS:
13360 stmt = gimple_build_omp_teams (body, OMP_CLAUSES (expr));
13361 if ((ort & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
13362 gimple_omp_teams_set_host (as_a <gomp_teams *> (stmt), true);
13363 break;
13364 default:
13365 gcc_unreachable ();
13368 gimplify_seq_add_stmt (pre_p, stmt);
13369 *expr_p = NULL_TREE;
13372 /* Gimplify the gross structure of OpenACC enter/exit data, update, and OpenMP
13373 target update constructs. */
13375 static void
13376 gimplify_omp_target_update (tree *expr_p, gimple_seq *pre_p)
13378 tree expr = *expr_p;
13379 int kind;
13380 gomp_target *stmt;
13381 enum omp_region_type ort = ORT_WORKSHARE;
13383 switch (TREE_CODE (expr))
13385 case OACC_ENTER_DATA:
13386 case OACC_EXIT_DATA:
13387 kind = GF_OMP_TARGET_KIND_OACC_ENTER_EXIT_DATA;
13388 ort = ORT_ACC;
13389 break;
13390 case OACC_UPDATE:
13391 kind = GF_OMP_TARGET_KIND_OACC_UPDATE;
13392 ort = ORT_ACC;
13393 break;
13394 case OMP_TARGET_UPDATE:
13395 kind = GF_OMP_TARGET_KIND_UPDATE;
13396 break;
13397 case OMP_TARGET_ENTER_DATA:
13398 kind = GF_OMP_TARGET_KIND_ENTER_DATA;
13399 break;
13400 case OMP_TARGET_EXIT_DATA:
13401 kind = GF_OMP_TARGET_KIND_EXIT_DATA;
13402 break;
13403 default:
13404 gcc_unreachable ();
13406 gimplify_scan_omp_clauses (&OMP_STANDALONE_CLAUSES (expr), pre_p,
13407 ort, TREE_CODE (expr));
13408 gimplify_adjust_omp_clauses (pre_p, NULL, &OMP_STANDALONE_CLAUSES (expr),
13409 TREE_CODE (expr));
13410 if (TREE_CODE (expr) == OACC_UPDATE
13411 && omp_find_clause (OMP_STANDALONE_CLAUSES (expr),
13412 OMP_CLAUSE_IF_PRESENT))
13414 /* The runtime uses GOMP_MAP_{TO,FROM} to denote the if_present
13415 clause. */
13416 for (tree c = OMP_STANDALONE_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
13417 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP)
13418 switch (OMP_CLAUSE_MAP_KIND (c))
13420 case GOMP_MAP_FORCE_TO:
13421 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_TO);
13422 break;
13423 case GOMP_MAP_FORCE_FROM:
13424 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FROM);
13425 break;
13426 default:
13427 break;
13430 else if (TREE_CODE (expr) == OACC_EXIT_DATA
13431 && omp_find_clause (OMP_STANDALONE_CLAUSES (expr),
13432 OMP_CLAUSE_FINALIZE))
13434 /* Use GOMP_MAP_DELETE/GOMP_MAP_FORCE_FROM to denote "finalize"
13435 semantics. */
13436 bool have_clause = false;
13437 for (tree c = OMP_STANDALONE_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
13438 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP)
13439 switch (OMP_CLAUSE_MAP_KIND (c))
13441 case GOMP_MAP_FROM:
13442 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FORCE_FROM);
13443 have_clause = true;
13444 break;
13445 case GOMP_MAP_RELEASE:
13446 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_DELETE);
13447 have_clause = true;
13448 break;
13449 case GOMP_MAP_TO_PSET:
13450 /* Fortran arrays with descriptors must map that descriptor when
13451 doing standalone "attach" operations (in OpenACC). In that
13452 case GOMP_MAP_TO_PSET appears by itself with no preceding
13453 clause (see trans-openmp.c:gfc_trans_omp_clauses). */
13454 break;
13455 case GOMP_MAP_POINTER:
13456 /* TODO PR92929: we may see these here, but they'll always follow
13457 one of the clauses above, and will be handled by libgomp as
13458 one group, so no handling required here. */
13459 gcc_assert (have_clause);
13460 break;
13461 case GOMP_MAP_DETACH:
13462 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FORCE_DETACH);
13463 have_clause = false;
13464 break;
13465 case GOMP_MAP_STRUCT:
13466 have_clause = false;
13467 break;
13468 default:
13469 gcc_unreachable ();
13472 stmt = gimple_build_omp_target (NULL, kind, OMP_STANDALONE_CLAUSES (expr));
13474 gimplify_seq_add_stmt (pre_p, stmt);
13475 *expr_p = NULL_TREE;
13478 /* A subroutine of gimplify_omp_atomic. The front end is supposed to have
13479 stabilized the lhs of the atomic operation as *ADDR. Return true if
13480 EXPR is this stabilized form. */
13482 static bool
13483 goa_lhs_expr_p (tree expr, tree addr)
13485 /* Also include casts to other type variants. The C front end is fond
13486 of adding these for e.g. volatile variables. This is like
13487 STRIP_TYPE_NOPS but includes the main variant lookup. */
13488 STRIP_USELESS_TYPE_CONVERSION (expr);
13490 if (TREE_CODE (expr) == INDIRECT_REF)
13492 expr = TREE_OPERAND (expr, 0);
13493 while (expr != addr
13494 && (CONVERT_EXPR_P (expr)
13495 || TREE_CODE (expr) == NON_LVALUE_EXPR)
13496 && TREE_CODE (expr) == TREE_CODE (addr)
13497 && types_compatible_p (TREE_TYPE (expr), TREE_TYPE (addr)))
13499 expr = TREE_OPERAND (expr, 0);
13500 addr = TREE_OPERAND (addr, 0);
13502 if (expr == addr)
13503 return true;
13504 return (TREE_CODE (addr) == ADDR_EXPR
13505 && TREE_CODE (expr) == ADDR_EXPR
13506 && TREE_OPERAND (addr, 0) == TREE_OPERAND (expr, 0));
13508 if (TREE_CODE (addr) == ADDR_EXPR && expr == TREE_OPERAND (addr, 0))
13509 return true;
13510 return false;
13513 /* Walk *EXPR_P and replace appearances of *LHS_ADDR with LHS_VAR. If an
13514 expression does not involve the lhs, evaluate it into a temporary.
13515 Return 1 if the lhs appeared as a subexpression, 0 if it did not,
13516 or -1 if an error was encountered. */
13518 static int
13519 goa_stabilize_expr (tree *expr_p, gimple_seq *pre_p, tree lhs_addr,
13520 tree lhs_var)
13522 tree expr = *expr_p;
13523 int saw_lhs;
13525 if (goa_lhs_expr_p (expr, lhs_addr))
13527 *expr_p = lhs_var;
13528 return 1;
13530 if (is_gimple_val (expr))
13531 return 0;
13533 saw_lhs = 0;
13534 switch (TREE_CODE_CLASS (TREE_CODE (expr)))
13536 case tcc_binary:
13537 case tcc_comparison:
13538 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p, lhs_addr,
13539 lhs_var);
13540 /* FALLTHRU */
13541 case tcc_unary:
13542 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p, lhs_addr,
13543 lhs_var);
13544 break;
13545 case tcc_expression:
13546 switch (TREE_CODE (expr))
13548 case TRUTH_ANDIF_EXPR:
13549 case TRUTH_ORIF_EXPR:
13550 case TRUTH_AND_EXPR:
13551 case TRUTH_OR_EXPR:
13552 case TRUTH_XOR_EXPR:
13553 case BIT_INSERT_EXPR:
13554 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
13555 lhs_addr, lhs_var);
13556 /* FALLTHRU */
13557 case TRUTH_NOT_EXPR:
13558 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
13559 lhs_addr, lhs_var);
13560 break;
13561 case COMPOUND_EXPR:
13562 /* Break out any preevaluations from cp_build_modify_expr. */
13563 for (; TREE_CODE (expr) == COMPOUND_EXPR;
13564 expr = TREE_OPERAND (expr, 1))
13565 gimplify_stmt (&TREE_OPERAND (expr, 0), pre_p);
13566 *expr_p = expr;
13567 return goa_stabilize_expr (expr_p, pre_p, lhs_addr, lhs_var);
13568 default:
13569 break;
13571 break;
13572 case tcc_reference:
13573 if (TREE_CODE (expr) == BIT_FIELD_REF)
13574 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
13575 lhs_addr, lhs_var);
13576 break;
13577 default:
13578 break;
13581 if (saw_lhs == 0)
13583 enum gimplify_status gs;
13584 gs = gimplify_expr (expr_p, pre_p, NULL, is_gimple_val, fb_rvalue);
13585 if (gs != GS_ALL_DONE)
13586 saw_lhs = -1;
13589 return saw_lhs;
13592 /* Gimplify an OMP_ATOMIC statement. */
13594 static enum gimplify_status
13595 gimplify_omp_atomic (tree *expr_p, gimple_seq *pre_p)
13597 tree addr = TREE_OPERAND (*expr_p, 0);
13598 tree rhs = TREE_CODE (*expr_p) == OMP_ATOMIC_READ
13599 ? NULL : TREE_OPERAND (*expr_p, 1);
13600 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (addr)));
13601 tree tmp_load;
13602 gomp_atomic_load *loadstmt;
13603 gomp_atomic_store *storestmt;
13605 tmp_load = create_tmp_reg (type);
13606 if (rhs && goa_stabilize_expr (&rhs, pre_p, addr, tmp_load) < 0)
13607 return GS_ERROR;
13609 if (gimplify_expr (&addr, pre_p, NULL, is_gimple_val, fb_rvalue)
13610 != GS_ALL_DONE)
13611 return GS_ERROR;
13613 loadstmt = gimple_build_omp_atomic_load (tmp_load, addr,
13614 OMP_ATOMIC_MEMORY_ORDER (*expr_p));
13615 gimplify_seq_add_stmt (pre_p, loadstmt);
13616 if (rhs)
13618 /* BIT_INSERT_EXPR is not valid for non-integral bitfield
13619 representatives. Use BIT_FIELD_REF on the lhs instead. */
13620 if (TREE_CODE (rhs) == BIT_INSERT_EXPR
13621 && !INTEGRAL_TYPE_P (TREE_TYPE (tmp_load)))
13623 tree bitpos = TREE_OPERAND (rhs, 2);
13624 tree op1 = TREE_OPERAND (rhs, 1);
13625 tree bitsize;
13626 tree tmp_store = tmp_load;
13627 if (TREE_CODE (*expr_p) == OMP_ATOMIC_CAPTURE_OLD)
13628 tmp_store = get_initialized_tmp_var (tmp_load, pre_p);
13629 if (INTEGRAL_TYPE_P (TREE_TYPE (op1)))
13630 bitsize = bitsize_int (TYPE_PRECISION (TREE_TYPE (op1)));
13631 else
13632 bitsize = TYPE_SIZE (TREE_TYPE (op1));
13633 gcc_assert (TREE_OPERAND (rhs, 0) == tmp_load);
13634 tree t = build2_loc (EXPR_LOCATION (rhs),
13635 MODIFY_EXPR, void_type_node,
13636 build3_loc (EXPR_LOCATION (rhs), BIT_FIELD_REF,
13637 TREE_TYPE (op1), tmp_store, bitsize,
13638 bitpos), op1);
13639 gimplify_and_add (t, pre_p);
13640 rhs = tmp_store;
13642 if (gimplify_expr (&rhs, pre_p, NULL, is_gimple_val, fb_rvalue)
13643 != GS_ALL_DONE)
13644 return GS_ERROR;
13647 if (TREE_CODE (*expr_p) == OMP_ATOMIC_READ)
13648 rhs = tmp_load;
13649 storestmt
13650 = gimple_build_omp_atomic_store (rhs, OMP_ATOMIC_MEMORY_ORDER (*expr_p));
13651 gimplify_seq_add_stmt (pre_p, storestmt);
13652 switch (TREE_CODE (*expr_p))
13654 case OMP_ATOMIC_READ:
13655 case OMP_ATOMIC_CAPTURE_OLD:
13656 *expr_p = tmp_load;
13657 gimple_omp_atomic_set_need_value (loadstmt);
13658 break;
13659 case OMP_ATOMIC_CAPTURE_NEW:
13660 *expr_p = rhs;
13661 gimple_omp_atomic_set_need_value (storestmt);
13662 break;
13663 default:
13664 *expr_p = NULL;
13665 break;
13668 return GS_ALL_DONE;
13671 /* Gimplify a TRANSACTION_EXPR. This involves gimplification of the
13672 body, and adding some EH bits. */
13674 static enum gimplify_status
13675 gimplify_transaction (tree *expr_p, gimple_seq *pre_p)
13677 tree expr = *expr_p, temp, tbody = TRANSACTION_EXPR_BODY (expr);
13678 gimple *body_stmt;
13679 gtransaction *trans_stmt;
13680 gimple_seq body = NULL;
13681 int subcode = 0;
13683 /* Wrap the transaction body in a BIND_EXPR so we have a context
13684 where to put decls for OMP. */
13685 if (TREE_CODE (tbody) != BIND_EXPR)
13687 tree bind = build3 (BIND_EXPR, void_type_node, NULL, tbody, NULL);
13688 TREE_SIDE_EFFECTS (bind) = 1;
13689 SET_EXPR_LOCATION (bind, EXPR_LOCATION (tbody));
13690 TRANSACTION_EXPR_BODY (expr) = bind;
13693 push_gimplify_context ();
13694 temp = voidify_wrapper_expr (*expr_p, NULL);
13696 body_stmt = gimplify_and_return_first (TRANSACTION_EXPR_BODY (expr), &body);
13697 pop_gimplify_context (body_stmt);
13699 trans_stmt = gimple_build_transaction (body);
13700 if (TRANSACTION_EXPR_OUTER (expr))
13701 subcode = GTMA_IS_OUTER;
13702 else if (TRANSACTION_EXPR_RELAXED (expr))
13703 subcode = GTMA_IS_RELAXED;
13704 gimple_transaction_set_subcode (trans_stmt, subcode);
13706 gimplify_seq_add_stmt (pre_p, trans_stmt);
13708 if (temp)
13710 *expr_p = temp;
13711 return GS_OK;
13714 *expr_p = NULL_TREE;
13715 return GS_ALL_DONE;
13718 /* Gimplify an OMP_ORDERED construct. EXPR is the tree version. BODY
13719 is the OMP_BODY of the original EXPR (which has already been
13720 gimplified so it's not present in the EXPR).
13722 Return the gimplified GIMPLE_OMP_ORDERED tuple. */
13724 static gimple *
13725 gimplify_omp_ordered (tree expr, gimple_seq body)
13727 tree c, decls;
13728 int failures = 0;
13729 unsigned int i;
13730 tree source_c = NULL_TREE;
13731 tree sink_c = NULL_TREE;
13733 if (gimplify_omp_ctxp)
13735 for (c = OMP_ORDERED_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
13736 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
13737 && gimplify_omp_ctxp->loop_iter_var.is_empty ()
13738 && (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SINK
13739 || OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SOURCE))
13741 error_at (OMP_CLAUSE_LOCATION (c),
13742 "%<ordered%> construct with %<depend%> clause must be "
13743 "closely nested inside a loop with %<ordered%> clause "
13744 "with a parameter");
13745 failures++;
13747 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
13748 && OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SINK)
13750 bool fail = false;
13751 for (decls = OMP_CLAUSE_DECL (c), i = 0;
13752 decls && TREE_CODE (decls) == TREE_LIST;
13753 decls = TREE_CHAIN (decls), ++i)
13754 if (i >= gimplify_omp_ctxp->loop_iter_var.length () / 2)
13755 continue;
13756 else if (TREE_VALUE (decls)
13757 != gimplify_omp_ctxp->loop_iter_var[2 * i])
13759 error_at (OMP_CLAUSE_LOCATION (c),
13760 "variable %qE is not an iteration "
13761 "of outermost loop %d, expected %qE",
13762 TREE_VALUE (decls), i + 1,
13763 gimplify_omp_ctxp->loop_iter_var[2 * i]);
13764 fail = true;
13765 failures++;
13767 else
13768 TREE_VALUE (decls)
13769 = gimplify_omp_ctxp->loop_iter_var[2 * i + 1];
13770 if (!fail && i != gimplify_omp_ctxp->loop_iter_var.length () / 2)
13772 error_at (OMP_CLAUSE_LOCATION (c),
13773 "number of variables in %<depend%> clause with "
13774 "%<sink%> modifier does not match number of "
13775 "iteration variables");
13776 failures++;
13778 sink_c = c;
13780 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
13781 && OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SOURCE)
13783 if (source_c)
13785 error_at (OMP_CLAUSE_LOCATION (c),
13786 "more than one %<depend%> clause with %<source%> "
13787 "modifier on an %<ordered%> construct");
13788 failures++;
13790 else
13791 source_c = c;
13794 if (source_c && sink_c)
13796 error_at (OMP_CLAUSE_LOCATION (source_c),
13797 "%<depend%> clause with %<source%> modifier specified "
13798 "together with %<depend%> clauses with %<sink%> modifier "
13799 "on the same construct");
13800 failures++;
13803 if (failures)
13804 return gimple_build_nop ();
13805 return gimple_build_omp_ordered (body, OMP_ORDERED_CLAUSES (expr));
13808 /* Convert the GENERIC expression tree *EXPR_P to GIMPLE. If the
13809 expression produces a value to be used as an operand inside a GIMPLE
13810 statement, the value will be stored back in *EXPR_P. This value will
13811 be a tree of class tcc_declaration, tcc_constant, tcc_reference or
13812 an SSA_NAME. The corresponding sequence of GIMPLE statements is
13813 emitted in PRE_P and POST_P.
13815 Additionally, this process may overwrite parts of the input
13816 expression during gimplification. Ideally, it should be
13817 possible to do non-destructive gimplification.
13819 EXPR_P points to the GENERIC expression to convert to GIMPLE. If
13820 the expression needs to evaluate to a value to be used as
13821 an operand in a GIMPLE statement, this value will be stored in
13822 *EXPR_P on exit. This happens when the caller specifies one
13823 of fb_lvalue or fb_rvalue fallback flags.
13825 PRE_P will contain the sequence of GIMPLE statements corresponding
13826 to the evaluation of EXPR and all the side-effects that must
13827 be executed before the main expression. On exit, the last
13828 statement of PRE_P is the core statement being gimplified. For
13829 instance, when gimplifying 'if (++a)' the last statement in
13830 PRE_P will be 'if (t.1)' where t.1 is the result of
13831 pre-incrementing 'a'.
13833 POST_P will contain the sequence of GIMPLE statements corresponding
13834 to the evaluation of all the side-effects that must be executed
13835 after the main expression. If this is NULL, the post
13836 side-effects are stored at the end of PRE_P.
13838 The reason why the output is split in two is to handle post
13839 side-effects explicitly. In some cases, an expression may have
13840 inner and outer post side-effects which need to be emitted in
13841 an order different from the one given by the recursive
13842 traversal. For instance, for the expression (*p--)++ the post
13843 side-effects of '--' must actually occur *after* the post
13844 side-effects of '++'. However, gimplification will first visit
13845 the inner expression, so if a separate POST sequence was not
13846 used, the resulting sequence would be:
13848 1 t.1 = *p
13849 2 p = p - 1
13850 3 t.2 = t.1 + 1
13851 4 *p = t.2
13853 However, the post-decrement operation in line #2 must not be
13854 evaluated until after the store to *p at line #4, so the
13855 correct sequence should be:
13857 1 t.1 = *p
13858 2 t.2 = t.1 + 1
13859 3 *p = t.2
13860 4 p = p - 1
13862 So, by specifying a separate post queue, it is possible
13863 to emit the post side-effects in the correct order.
13864 If POST_P is NULL, an internal queue will be used. Before
13865 returning to the caller, the sequence POST_P is appended to
13866 the main output sequence PRE_P.
13868 GIMPLE_TEST_F points to a function that takes a tree T and
13869 returns nonzero if T is in the GIMPLE form requested by the
13870 caller. The GIMPLE predicates are in gimple.c.
13872 FALLBACK tells the function what sort of a temporary we want if
13873 gimplification cannot produce an expression that complies with
13874 GIMPLE_TEST_F.
13876 fb_none means that no temporary should be generated
13877 fb_rvalue means that an rvalue is OK to generate
13878 fb_lvalue means that an lvalue is OK to generate
13879 fb_either means that either is OK, but an lvalue is preferable.
13880 fb_mayfail means that gimplification may fail (in which case
13881 GS_ERROR will be returned)
13883 The return value is either GS_ERROR or GS_ALL_DONE, since this
13884 function iterates until EXPR is completely gimplified or an error
13885 occurs. */
13887 enum gimplify_status
13888 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
13889 bool (*gimple_test_f) (tree), fallback_t fallback)
13891 tree tmp;
13892 gimple_seq internal_pre = NULL;
13893 gimple_seq internal_post = NULL;
13894 tree save_expr;
13895 bool is_statement;
13896 location_t saved_location;
13897 enum gimplify_status ret;
13898 gimple_stmt_iterator pre_last_gsi, post_last_gsi;
13899 tree label;
13901 save_expr = *expr_p;
13902 if (save_expr == NULL_TREE)
13903 return GS_ALL_DONE;
13905 /* If we are gimplifying a top-level statement, PRE_P must be valid. */
13906 is_statement = gimple_test_f == is_gimple_stmt;
13907 if (is_statement)
13908 gcc_assert (pre_p);
13910 /* Consistency checks. */
13911 if (gimple_test_f == is_gimple_reg)
13912 gcc_assert (fallback & (fb_rvalue | fb_lvalue));
13913 else if (gimple_test_f == is_gimple_val
13914 || gimple_test_f == is_gimple_call_addr
13915 || gimple_test_f == is_gimple_condexpr
13916 || gimple_test_f == is_gimple_condexpr_for_cond
13917 || gimple_test_f == is_gimple_mem_rhs
13918 || gimple_test_f == is_gimple_mem_rhs_or_call
13919 || gimple_test_f == is_gimple_reg_rhs
13920 || gimple_test_f == is_gimple_reg_rhs_or_call
13921 || gimple_test_f == is_gimple_asm_val
13922 || gimple_test_f == is_gimple_mem_ref_addr)
13923 gcc_assert (fallback & fb_rvalue);
13924 else if (gimple_test_f == is_gimple_min_lval
13925 || gimple_test_f == is_gimple_lvalue)
13926 gcc_assert (fallback & fb_lvalue);
13927 else if (gimple_test_f == is_gimple_addressable)
13928 gcc_assert (fallback & fb_either);
13929 else if (gimple_test_f == is_gimple_stmt)
13930 gcc_assert (fallback == fb_none);
13931 else
13933 /* We should have recognized the GIMPLE_TEST_F predicate to
13934 know what kind of fallback to use in case a temporary is
13935 needed to hold the value or address of *EXPR_P. */
13936 gcc_unreachable ();
13939 /* We used to check the predicate here and return immediately if it
13940 succeeds. This is wrong; the design is for gimplification to be
13941 idempotent, and for the predicates to only test for valid forms, not
13942 whether they are fully simplified. */
13943 if (pre_p == NULL)
13944 pre_p = &internal_pre;
13946 if (post_p == NULL)
13947 post_p = &internal_post;
13949 /* Remember the last statements added to PRE_P and POST_P. Every
13950 new statement added by the gimplification helpers needs to be
13951 annotated with location information. To centralize the
13952 responsibility, we remember the last statement that had been
13953 added to both queues before gimplifying *EXPR_P. If
13954 gimplification produces new statements in PRE_P and POST_P, those
13955 statements will be annotated with the same location information
13956 as *EXPR_P. */
13957 pre_last_gsi = gsi_last (*pre_p);
13958 post_last_gsi = gsi_last (*post_p);
13960 saved_location = input_location;
13961 if (save_expr != error_mark_node
13962 && EXPR_HAS_LOCATION (*expr_p))
13963 input_location = EXPR_LOCATION (*expr_p);
13965 /* Loop over the specific gimplifiers until the toplevel node
13966 remains the same. */
13969 /* Strip away as many useless type conversions as possible
13970 at the toplevel. */
13971 STRIP_USELESS_TYPE_CONVERSION (*expr_p);
13973 /* Remember the expr. */
13974 save_expr = *expr_p;
13976 /* Die, die, die, my darling. */
13977 if (error_operand_p (save_expr))
13979 ret = GS_ERROR;
13980 break;
13983 /* Do any language-specific gimplification. */
13984 ret = ((enum gimplify_status)
13985 lang_hooks.gimplify_expr (expr_p, pre_p, post_p));
13986 if (ret == GS_OK)
13988 if (*expr_p == NULL_TREE)
13989 break;
13990 if (*expr_p != save_expr)
13991 continue;
13993 else if (ret != GS_UNHANDLED)
13994 break;
13996 /* Make sure that all the cases set 'ret' appropriately. */
13997 ret = GS_UNHANDLED;
13998 switch (TREE_CODE (*expr_p))
14000 /* First deal with the special cases. */
14002 case POSTINCREMENT_EXPR:
14003 case POSTDECREMENT_EXPR:
14004 case PREINCREMENT_EXPR:
14005 case PREDECREMENT_EXPR:
14006 ret = gimplify_self_mod_expr (expr_p, pre_p, post_p,
14007 fallback != fb_none,
14008 TREE_TYPE (*expr_p));
14009 break;
14011 case VIEW_CONVERT_EXPR:
14012 if ((fallback & fb_rvalue)
14013 && is_gimple_reg_type (TREE_TYPE (*expr_p))
14014 && is_gimple_reg_type (TREE_TYPE (TREE_OPERAND (*expr_p, 0))))
14016 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
14017 post_p, is_gimple_val, fb_rvalue);
14018 recalculate_side_effects (*expr_p);
14019 break;
14021 /* Fallthru. */
14023 case ARRAY_REF:
14024 case ARRAY_RANGE_REF:
14025 case REALPART_EXPR:
14026 case IMAGPART_EXPR:
14027 case COMPONENT_REF:
14028 ret = gimplify_compound_lval (expr_p, pre_p, post_p,
14029 fallback ? fallback : fb_rvalue);
14030 break;
14032 case COND_EXPR:
14033 ret = gimplify_cond_expr (expr_p, pre_p, fallback);
14035 /* C99 code may assign to an array in a structure value of a
14036 conditional expression, and this has undefined behavior
14037 only on execution, so create a temporary if an lvalue is
14038 required. */
14039 if (fallback == fb_lvalue)
14041 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
14042 mark_addressable (*expr_p);
14043 ret = GS_OK;
14045 break;
14047 case CALL_EXPR:
14048 ret = gimplify_call_expr (expr_p, pre_p, fallback != fb_none);
14050 /* C99 code may assign to an array in a structure returned
14051 from a function, and this has undefined behavior only on
14052 execution, so create a temporary if an lvalue is
14053 required. */
14054 if (fallback == fb_lvalue)
14056 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
14057 mark_addressable (*expr_p);
14058 ret = GS_OK;
14060 break;
14062 case TREE_LIST:
14063 gcc_unreachable ();
14065 case COMPOUND_EXPR:
14066 ret = gimplify_compound_expr (expr_p, pre_p, fallback != fb_none);
14067 break;
14069 case COMPOUND_LITERAL_EXPR:
14070 ret = gimplify_compound_literal_expr (expr_p, pre_p,
14071 gimple_test_f, fallback);
14072 break;
14074 case MODIFY_EXPR:
14075 case INIT_EXPR:
14076 ret = gimplify_modify_expr (expr_p, pre_p, post_p,
14077 fallback != fb_none);
14078 break;
14080 case TRUTH_ANDIF_EXPR:
14081 case TRUTH_ORIF_EXPR:
14083 /* Preserve the original type of the expression and the
14084 source location of the outer expression. */
14085 tree org_type = TREE_TYPE (*expr_p);
14086 *expr_p = gimple_boolify (*expr_p);
14087 *expr_p = build3_loc (input_location, COND_EXPR,
14088 org_type, *expr_p,
14089 fold_convert_loc
14090 (input_location,
14091 org_type, boolean_true_node),
14092 fold_convert_loc
14093 (input_location,
14094 org_type, boolean_false_node));
14095 ret = GS_OK;
14096 break;
14099 case TRUTH_NOT_EXPR:
14101 tree type = TREE_TYPE (*expr_p);
14102 /* The parsers are careful to generate TRUTH_NOT_EXPR
14103 only with operands that are always zero or one.
14104 We do not fold here but handle the only interesting case
14105 manually, as fold may re-introduce the TRUTH_NOT_EXPR. */
14106 *expr_p = gimple_boolify (*expr_p);
14107 if (TYPE_PRECISION (TREE_TYPE (*expr_p)) == 1)
14108 *expr_p = build1_loc (input_location, BIT_NOT_EXPR,
14109 TREE_TYPE (*expr_p),
14110 TREE_OPERAND (*expr_p, 0));
14111 else
14112 *expr_p = build2_loc (input_location, BIT_XOR_EXPR,
14113 TREE_TYPE (*expr_p),
14114 TREE_OPERAND (*expr_p, 0),
14115 build_int_cst (TREE_TYPE (*expr_p), 1));
14116 if (!useless_type_conversion_p (type, TREE_TYPE (*expr_p)))
14117 *expr_p = fold_convert_loc (input_location, type, *expr_p);
14118 ret = GS_OK;
14119 break;
14122 case ADDR_EXPR:
14123 ret = gimplify_addr_expr (expr_p, pre_p, post_p);
14124 break;
14126 case ANNOTATE_EXPR:
14128 tree cond = TREE_OPERAND (*expr_p, 0);
14129 tree kind = TREE_OPERAND (*expr_p, 1);
14130 tree data = TREE_OPERAND (*expr_p, 2);
14131 tree type = TREE_TYPE (cond);
14132 if (!INTEGRAL_TYPE_P (type))
14134 *expr_p = cond;
14135 ret = GS_OK;
14136 break;
14138 tree tmp = create_tmp_var (type);
14139 gimplify_arg (&cond, pre_p, EXPR_LOCATION (*expr_p));
14140 gcall *call
14141 = gimple_build_call_internal (IFN_ANNOTATE, 3, cond, kind, data);
14142 gimple_call_set_lhs (call, tmp);
14143 gimplify_seq_add_stmt (pre_p, call);
14144 *expr_p = tmp;
14145 ret = GS_ALL_DONE;
14146 break;
14149 case VA_ARG_EXPR:
14150 ret = gimplify_va_arg_expr (expr_p, pre_p, post_p);
14151 break;
14153 CASE_CONVERT:
14154 if (IS_EMPTY_STMT (*expr_p))
14156 ret = GS_ALL_DONE;
14157 break;
14160 if (VOID_TYPE_P (TREE_TYPE (*expr_p))
14161 || fallback == fb_none)
14163 /* Just strip a conversion to void (or in void context) and
14164 try again. */
14165 *expr_p = TREE_OPERAND (*expr_p, 0);
14166 ret = GS_OK;
14167 break;
14170 ret = gimplify_conversion (expr_p);
14171 if (ret == GS_ERROR)
14172 break;
14173 if (*expr_p != save_expr)
14174 break;
14175 /* FALLTHRU */
14177 case FIX_TRUNC_EXPR:
14178 /* unary_expr: ... | '(' cast ')' val | ... */
14179 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
14180 is_gimple_val, fb_rvalue);
14181 recalculate_side_effects (*expr_p);
14182 break;
14184 case INDIRECT_REF:
14186 bool volatilep = TREE_THIS_VOLATILE (*expr_p);
14187 bool notrap = TREE_THIS_NOTRAP (*expr_p);
14188 tree saved_ptr_type = TREE_TYPE (TREE_OPERAND (*expr_p, 0));
14190 *expr_p = fold_indirect_ref_loc (input_location, *expr_p);
14191 if (*expr_p != save_expr)
14193 ret = GS_OK;
14194 break;
14197 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
14198 is_gimple_reg, fb_rvalue);
14199 if (ret == GS_ERROR)
14200 break;
14202 recalculate_side_effects (*expr_p);
14203 *expr_p = fold_build2_loc (input_location, MEM_REF,
14204 TREE_TYPE (*expr_p),
14205 TREE_OPERAND (*expr_p, 0),
14206 build_int_cst (saved_ptr_type, 0));
14207 TREE_THIS_VOLATILE (*expr_p) = volatilep;
14208 TREE_THIS_NOTRAP (*expr_p) = notrap;
14209 ret = GS_OK;
14210 break;
14213 /* We arrive here through the various re-gimplifcation paths. */
14214 case MEM_REF:
14215 /* First try re-folding the whole thing. */
14216 tmp = fold_binary (MEM_REF, TREE_TYPE (*expr_p),
14217 TREE_OPERAND (*expr_p, 0),
14218 TREE_OPERAND (*expr_p, 1));
14219 if (tmp)
14221 REF_REVERSE_STORAGE_ORDER (tmp)
14222 = REF_REVERSE_STORAGE_ORDER (*expr_p);
14223 *expr_p = tmp;
14224 recalculate_side_effects (*expr_p);
14225 ret = GS_OK;
14226 break;
14228 /* Avoid re-gimplifying the address operand if it is already
14229 in suitable form. Re-gimplifying would mark the address
14230 operand addressable. Always gimplify when not in SSA form
14231 as we still may have to gimplify decls with value-exprs. */
14232 if (!gimplify_ctxp || !gimple_in_ssa_p (cfun)
14233 || !is_gimple_mem_ref_addr (TREE_OPERAND (*expr_p, 0)))
14235 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
14236 is_gimple_mem_ref_addr, fb_rvalue);
14237 if (ret == GS_ERROR)
14238 break;
14240 recalculate_side_effects (*expr_p);
14241 ret = GS_ALL_DONE;
14242 break;
14244 /* Constants need not be gimplified. */
14245 case INTEGER_CST:
14246 case REAL_CST:
14247 case FIXED_CST:
14248 case STRING_CST:
14249 case COMPLEX_CST:
14250 case VECTOR_CST:
14251 /* Drop the overflow flag on constants, we do not want
14252 that in the GIMPLE IL. */
14253 if (TREE_OVERFLOW_P (*expr_p))
14254 *expr_p = drop_tree_overflow (*expr_p);
14255 ret = GS_ALL_DONE;
14256 break;
14258 case CONST_DECL:
14259 /* If we require an lvalue, such as for ADDR_EXPR, retain the
14260 CONST_DECL node. Otherwise the decl is replaceable by its
14261 value. */
14262 /* ??? Should be == fb_lvalue, but ADDR_EXPR passes fb_either. */
14263 if (fallback & fb_lvalue)
14264 ret = GS_ALL_DONE;
14265 else
14267 *expr_p = DECL_INITIAL (*expr_p);
14268 ret = GS_OK;
14270 break;
14272 case DECL_EXPR:
14273 ret = gimplify_decl_expr (expr_p, pre_p);
14274 break;
14276 case BIND_EXPR:
14277 ret = gimplify_bind_expr (expr_p, pre_p);
14278 break;
14280 case LOOP_EXPR:
14281 ret = gimplify_loop_expr (expr_p, pre_p);
14282 break;
14284 case SWITCH_EXPR:
14285 ret = gimplify_switch_expr (expr_p, pre_p);
14286 break;
14288 case EXIT_EXPR:
14289 ret = gimplify_exit_expr (expr_p);
14290 break;
14292 case GOTO_EXPR:
14293 /* If the target is not LABEL, then it is a computed jump
14294 and the target needs to be gimplified. */
14295 if (TREE_CODE (GOTO_DESTINATION (*expr_p)) != LABEL_DECL)
14297 ret = gimplify_expr (&GOTO_DESTINATION (*expr_p), pre_p,
14298 NULL, is_gimple_val, fb_rvalue);
14299 if (ret == GS_ERROR)
14300 break;
14302 gimplify_seq_add_stmt (pre_p,
14303 gimple_build_goto (GOTO_DESTINATION (*expr_p)));
14304 ret = GS_ALL_DONE;
14305 break;
14307 case PREDICT_EXPR:
14308 gimplify_seq_add_stmt (pre_p,
14309 gimple_build_predict (PREDICT_EXPR_PREDICTOR (*expr_p),
14310 PREDICT_EXPR_OUTCOME (*expr_p)));
14311 ret = GS_ALL_DONE;
14312 break;
14314 case LABEL_EXPR:
14315 ret = gimplify_label_expr (expr_p, pre_p);
14316 label = LABEL_EXPR_LABEL (*expr_p);
14317 gcc_assert (decl_function_context (label) == current_function_decl);
14319 /* If the label is used in a goto statement, or address of the label
14320 is taken, we need to unpoison all variables that were seen so far.
14321 Doing so would prevent us from reporting a false positives. */
14322 if (asan_poisoned_variables
14323 && asan_used_labels != NULL
14324 && asan_used_labels->contains (label)
14325 && !gimplify_omp_ctxp)
14326 asan_poison_variables (asan_poisoned_variables, false, pre_p);
14327 break;
14329 case CASE_LABEL_EXPR:
14330 ret = gimplify_case_label_expr (expr_p, pre_p);
14332 if (gimplify_ctxp->live_switch_vars)
14333 asan_poison_variables (gimplify_ctxp->live_switch_vars, false,
14334 pre_p);
14335 break;
14337 case RETURN_EXPR:
14338 ret = gimplify_return_expr (*expr_p, pre_p);
14339 break;
14341 case CONSTRUCTOR:
14342 /* Don't reduce this in place; let gimplify_init_constructor work its
14343 magic. Buf if we're just elaborating this for side effects, just
14344 gimplify any element that has side-effects. */
14345 if (fallback == fb_none)
14347 unsigned HOST_WIDE_INT ix;
14348 tree val;
14349 tree temp = NULL_TREE;
14350 FOR_EACH_CONSTRUCTOR_VALUE (CONSTRUCTOR_ELTS (*expr_p), ix, val)
14351 if (TREE_SIDE_EFFECTS (val))
14352 append_to_statement_list (val, &temp);
14354 *expr_p = temp;
14355 ret = temp ? GS_OK : GS_ALL_DONE;
14357 /* C99 code may assign to an array in a constructed
14358 structure or union, and this has undefined behavior only
14359 on execution, so create a temporary if an lvalue is
14360 required. */
14361 else if (fallback == fb_lvalue)
14363 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
14364 mark_addressable (*expr_p);
14365 ret = GS_OK;
14367 else
14368 ret = GS_ALL_DONE;
14369 break;
14371 /* The following are special cases that are not handled by the
14372 original GIMPLE grammar. */
14374 /* SAVE_EXPR nodes are converted into a GIMPLE identifier and
14375 eliminated. */
14376 case SAVE_EXPR:
14377 ret = gimplify_save_expr (expr_p, pre_p, post_p);
14378 break;
14380 case BIT_FIELD_REF:
14381 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
14382 post_p, is_gimple_lvalue, fb_either);
14383 recalculate_side_effects (*expr_p);
14384 break;
14386 case TARGET_MEM_REF:
14388 enum gimplify_status r0 = GS_ALL_DONE, r1 = GS_ALL_DONE;
14390 if (TMR_BASE (*expr_p))
14391 r0 = gimplify_expr (&TMR_BASE (*expr_p), pre_p,
14392 post_p, is_gimple_mem_ref_addr, fb_either);
14393 if (TMR_INDEX (*expr_p))
14394 r1 = gimplify_expr (&TMR_INDEX (*expr_p), pre_p,
14395 post_p, is_gimple_val, fb_rvalue);
14396 if (TMR_INDEX2 (*expr_p))
14397 r1 = gimplify_expr (&TMR_INDEX2 (*expr_p), pre_p,
14398 post_p, is_gimple_val, fb_rvalue);
14399 /* TMR_STEP and TMR_OFFSET are always integer constants. */
14400 ret = MIN (r0, r1);
14402 break;
14404 case NON_LVALUE_EXPR:
14405 /* This should have been stripped above. */
14406 gcc_unreachable ();
14408 case ASM_EXPR:
14409 ret = gimplify_asm_expr (expr_p, pre_p, post_p);
14410 break;
14412 case TRY_FINALLY_EXPR:
14413 case TRY_CATCH_EXPR:
14415 gimple_seq eval, cleanup;
14416 gtry *try_;
14418 /* Calls to destructors are generated automatically in FINALLY/CATCH
14419 block. They should have location as UNKNOWN_LOCATION. However,
14420 gimplify_call_expr will reset these call stmts to input_location
14421 if it finds stmt's location is unknown. To prevent resetting for
14422 destructors, we set the input_location to unknown.
14423 Note that this only affects the destructor calls in FINALLY/CATCH
14424 block, and will automatically reset to its original value by the
14425 end of gimplify_expr. */
14426 input_location = UNKNOWN_LOCATION;
14427 eval = cleanup = NULL;
14428 gimplify_and_add (TREE_OPERAND (*expr_p, 0), &eval);
14429 if (TREE_CODE (*expr_p) == TRY_FINALLY_EXPR
14430 && TREE_CODE (TREE_OPERAND (*expr_p, 1)) == EH_ELSE_EXPR)
14432 gimple_seq n = NULL, e = NULL;
14433 gimplify_and_add (TREE_OPERAND (TREE_OPERAND (*expr_p, 1),
14434 0), &n);
14435 gimplify_and_add (TREE_OPERAND (TREE_OPERAND (*expr_p, 1),
14436 1), &e);
14437 if (!gimple_seq_empty_p (n) && !gimple_seq_empty_p (e))
14439 geh_else *stmt = gimple_build_eh_else (n, e);
14440 gimple_seq_add_stmt (&cleanup, stmt);
14443 else
14444 gimplify_and_add (TREE_OPERAND (*expr_p, 1), &cleanup);
14445 /* Don't create bogus GIMPLE_TRY with empty cleanup. */
14446 if (gimple_seq_empty_p (cleanup))
14448 gimple_seq_add_seq (pre_p, eval);
14449 ret = GS_ALL_DONE;
14450 break;
14452 try_ = gimple_build_try (eval, cleanup,
14453 TREE_CODE (*expr_p) == TRY_FINALLY_EXPR
14454 ? GIMPLE_TRY_FINALLY
14455 : GIMPLE_TRY_CATCH);
14456 if (EXPR_HAS_LOCATION (save_expr))
14457 gimple_set_location (try_, EXPR_LOCATION (save_expr));
14458 else if (LOCATION_LOCUS (saved_location) != UNKNOWN_LOCATION)
14459 gimple_set_location (try_, saved_location);
14460 if (TREE_CODE (*expr_p) == TRY_CATCH_EXPR)
14461 gimple_try_set_catch_is_cleanup (try_,
14462 TRY_CATCH_IS_CLEANUP (*expr_p));
14463 gimplify_seq_add_stmt (pre_p, try_);
14464 ret = GS_ALL_DONE;
14465 break;
14468 case CLEANUP_POINT_EXPR:
14469 ret = gimplify_cleanup_point_expr (expr_p, pre_p);
14470 break;
14472 case TARGET_EXPR:
14473 ret = gimplify_target_expr (expr_p, pre_p, post_p);
14474 break;
14476 case CATCH_EXPR:
14478 gimple *c;
14479 gimple_seq handler = NULL;
14480 gimplify_and_add (CATCH_BODY (*expr_p), &handler);
14481 c = gimple_build_catch (CATCH_TYPES (*expr_p), handler);
14482 gimplify_seq_add_stmt (pre_p, c);
14483 ret = GS_ALL_DONE;
14484 break;
14487 case EH_FILTER_EXPR:
14489 gimple *ehf;
14490 gimple_seq failure = NULL;
14492 gimplify_and_add (EH_FILTER_FAILURE (*expr_p), &failure);
14493 ehf = gimple_build_eh_filter (EH_FILTER_TYPES (*expr_p), failure);
14494 gimple_set_no_warning (ehf, TREE_NO_WARNING (*expr_p));
14495 gimplify_seq_add_stmt (pre_p, ehf);
14496 ret = GS_ALL_DONE;
14497 break;
14500 case OBJ_TYPE_REF:
14502 enum gimplify_status r0, r1;
14503 r0 = gimplify_expr (&OBJ_TYPE_REF_OBJECT (*expr_p), pre_p,
14504 post_p, is_gimple_val, fb_rvalue);
14505 r1 = gimplify_expr (&OBJ_TYPE_REF_EXPR (*expr_p), pre_p,
14506 post_p, is_gimple_val, fb_rvalue);
14507 TREE_SIDE_EFFECTS (*expr_p) = 0;
14508 ret = MIN (r0, r1);
14510 break;
14512 case LABEL_DECL:
14513 /* We get here when taking the address of a label. We mark
14514 the label as "forced"; meaning it can never be removed and
14515 it is a potential target for any computed goto. */
14516 FORCED_LABEL (*expr_p) = 1;
14517 ret = GS_ALL_DONE;
14518 break;
14520 case STATEMENT_LIST:
14521 ret = gimplify_statement_list (expr_p, pre_p);
14522 break;
14524 case WITH_SIZE_EXPR:
14526 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
14527 post_p == &internal_post ? NULL : post_p,
14528 gimple_test_f, fallback);
14529 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
14530 is_gimple_val, fb_rvalue);
14531 ret = GS_ALL_DONE;
14533 break;
14535 case VAR_DECL:
14536 case PARM_DECL:
14537 ret = gimplify_var_or_parm_decl (expr_p);
14538 break;
14540 case RESULT_DECL:
14541 /* When within an OMP context, notice uses of variables. */
14542 if (gimplify_omp_ctxp)
14543 omp_notice_variable (gimplify_omp_ctxp, *expr_p, true);
14544 ret = GS_ALL_DONE;
14545 break;
14547 case DEBUG_EXPR_DECL:
14548 gcc_unreachable ();
14550 case DEBUG_BEGIN_STMT:
14551 gimplify_seq_add_stmt (pre_p,
14552 gimple_build_debug_begin_stmt
14553 (TREE_BLOCK (*expr_p),
14554 EXPR_LOCATION (*expr_p)));
14555 ret = GS_ALL_DONE;
14556 *expr_p = NULL;
14557 break;
14559 case SSA_NAME:
14560 /* Allow callbacks into the gimplifier during optimization. */
14561 ret = GS_ALL_DONE;
14562 break;
14564 case OMP_PARALLEL:
14565 gimplify_omp_parallel (expr_p, pre_p);
14566 ret = GS_ALL_DONE;
14567 break;
14569 case OMP_TASK:
14570 gimplify_omp_task (expr_p, pre_p);
14571 ret = GS_ALL_DONE;
14572 break;
14574 case OMP_FOR:
14575 case OMP_SIMD:
14576 case OMP_DISTRIBUTE:
14577 case OMP_TASKLOOP:
14578 case OACC_LOOP:
14579 ret = gimplify_omp_for (expr_p, pre_p);
14580 break;
14582 case OMP_LOOP:
14583 ret = gimplify_omp_loop (expr_p, pre_p);
14584 break;
14586 case OACC_CACHE:
14587 gimplify_oacc_cache (expr_p, pre_p);
14588 ret = GS_ALL_DONE;
14589 break;
14591 case OACC_DECLARE:
14592 gimplify_oacc_declare (expr_p, pre_p);
14593 ret = GS_ALL_DONE;
14594 break;
14596 case OACC_HOST_DATA:
14597 case OACC_DATA:
14598 case OACC_KERNELS:
14599 case OACC_PARALLEL:
14600 case OACC_SERIAL:
14601 case OMP_SECTIONS:
14602 case OMP_SINGLE:
14603 case OMP_TARGET:
14604 case OMP_TARGET_DATA:
14605 case OMP_TEAMS:
14606 gimplify_omp_workshare (expr_p, pre_p);
14607 ret = GS_ALL_DONE;
14608 break;
14610 case OACC_ENTER_DATA:
14611 case OACC_EXIT_DATA:
14612 case OACC_UPDATE:
14613 case OMP_TARGET_UPDATE:
14614 case OMP_TARGET_ENTER_DATA:
14615 case OMP_TARGET_EXIT_DATA:
14616 gimplify_omp_target_update (expr_p, pre_p);
14617 ret = GS_ALL_DONE;
14618 break;
14620 case OMP_SECTION:
14621 case OMP_MASTER:
14622 case OMP_ORDERED:
14623 case OMP_CRITICAL:
14624 case OMP_SCAN:
14626 gimple_seq body = NULL;
14627 gimple *g;
14628 bool saved_in_omp_construct = in_omp_construct;
14630 in_omp_construct = true;
14631 gimplify_and_add (OMP_BODY (*expr_p), &body);
14632 in_omp_construct = saved_in_omp_construct;
14633 switch (TREE_CODE (*expr_p))
14635 case OMP_SECTION:
14636 g = gimple_build_omp_section (body);
14637 break;
14638 case OMP_MASTER:
14639 g = gimple_build_omp_master (body);
14640 break;
14641 case OMP_ORDERED:
14642 g = gimplify_omp_ordered (*expr_p, body);
14643 break;
14644 case OMP_CRITICAL:
14645 gimplify_scan_omp_clauses (&OMP_CRITICAL_CLAUSES (*expr_p),
14646 pre_p, ORT_WORKSHARE, OMP_CRITICAL);
14647 gimplify_adjust_omp_clauses (pre_p, body,
14648 &OMP_CRITICAL_CLAUSES (*expr_p),
14649 OMP_CRITICAL);
14650 g = gimple_build_omp_critical (body,
14651 OMP_CRITICAL_NAME (*expr_p),
14652 OMP_CRITICAL_CLAUSES (*expr_p));
14653 break;
14654 case OMP_SCAN:
14655 gimplify_scan_omp_clauses (&OMP_SCAN_CLAUSES (*expr_p),
14656 pre_p, ORT_WORKSHARE, OMP_SCAN);
14657 gimplify_adjust_omp_clauses (pre_p, body,
14658 &OMP_SCAN_CLAUSES (*expr_p),
14659 OMP_SCAN);
14660 g = gimple_build_omp_scan (body, OMP_SCAN_CLAUSES (*expr_p));
14661 break;
14662 default:
14663 gcc_unreachable ();
14665 gimplify_seq_add_stmt (pre_p, g);
14666 ret = GS_ALL_DONE;
14667 break;
14670 case OMP_TASKGROUP:
14672 gimple_seq body = NULL;
14674 tree *pclauses = &OMP_TASKGROUP_CLAUSES (*expr_p);
14675 bool saved_in_omp_construct = in_omp_construct;
14676 gimplify_scan_omp_clauses (pclauses, pre_p, ORT_TASKGROUP,
14677 OMP_TASKGROUP);
14678 gimplify_adjust_omp_clauses (pre_p, NULL, pclauses, OMP_TASKGROUP);
14680 in_omp_construct = true;
14681 gimplify_and_add (OMP_BODY (*expr_p), &body);
14682 in_omp_construct = saved_in_omp_construct;
14683 gimple_seq cleanup = NULL;
14684 tree fn = builtin_decl_explicit (BUILT_IN_GOMP_TASKGROUP_END);
14685 gimple *g = gimple_build_call (fn, 0);
14686 gimple_seq_add_stmt (&cleanup, g);
14687 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
14688 body = NULL;
14689 gimple_seq_add_stmt (&body, g);
14690 g = gimple_build_omp_taskgroup (body, *pclauses);
14691 gimplify_seq_add_stmt (pre_p, g);
14692 ret = GS_ALL_DONE;
14693 break;
14696 case OMP_ATOMIC:
14697 case OMP_ATOMIC_READ:
14698 case OMP_ATOMIC_CAPTURE_OLD:
14699 case OMP_ATOMIC_CAPTURE_NEW:
14700 ret = gimplify_omp_atomic (expr_p, pre_p);
14701 break;
14703 case TRANSACTION_EXPR:
14704 ret = gimplify_transaction (expr_p, pre_p);
14705 break;
14707 case TRUTH_AND_EXPR:
14708 case TRUTH_OR_EXPR:
14709 case TRUTH_XOR_EXPR:
14711 tree orig_type = TREE_TYPE (*expr_p);
14712 tree new_type, xop0, xop1;
14713 *expr_p = gimple_boolify (*expr_p);
14714 new_type = TREE_TYPE (*expr_p);
14715 if (!useless_type_conversion_p (orig_type, new_type))
14717 *expr_p = fold_convert_loc (input_location, orig_type, *expr_p);
14718 ret = GS_OK;
14719 break;
14722 /* Boolified binary truth expressions are semantically equivalent
14723 to bitwise binary expressions. Canonicalize them to the
14724 bitwise variant. */
14725 switch (TREE_CODE (*expr_p))
14727 case TRUTH_AND_EXPR:
14728 TREE_SET_CODE (*expr_p, BIT_AND_EXPR);
14729 break;
14730 case TRUTH_OR_EXPR:
14731 TREE_SET_CODE (*expr_p, BIT_IOR_EXPR);
14732 break;
14733 case TRUTH_XOR_EXPR:
14734 TREE_SET_CODE (*expr_p, BIT_XOR_EXPR);
14735 break;
14736 default:
14737 break;
14739 /* Now make sure that operands have compatible type to
14740 expression's new_type. */
14741 xop0 = TREE_OPERAND (*expr_p, 0);
14742 xop1 = TREE_OPERAND (*expr_p, 1);
14743 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop0)))
14744 TREE_OPERAND (*expr_p, 0) = fold_convert_loc (input_location,
14745 new_type,
14746 xop0);
14747 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop1)))
14748 TREE_OPERAND (*expr_p, 1) = fold_convert_loc (input_location,
14749 new_type,
14750 xop1);
14751 /* Continue classified as tcc_binary. */
14752 goto expr_2;
14755 case VEC_COND_EXPR:
14756 goto expr_3;
14758 case VEC_PERM_EXPR:
14759 /* Classified as tcc_expression. */
14760 goto expr_3;
14762 case BIT_INSERT_EXPR:
14763 /* Argument 3 is a constant. */
14764 goto expr_2;
14766 case POINTER_PLUS_EXPR:
14768 enum gimplify_status r0, r1;
14769 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
14770 post_p, is_gimple_val, fb_rvalue);
14771 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
14772 post_p, is_gimple_val, fb_rvalue);
14773 recalculate_side_effects (*expr_p);
14774 ret = MIN (r0, r1);
14775 break;
14778 default:
14779 switch (TREE_CODE_CLASS (TREE_CODE (*expr_p)))
14781 case tcc_comparison:
14782 /* Handle comparison of objects of non scalar mode aggregates
14783 with a call to memcmp. It would be nice to only have to do
14784 this for variable-sized objects, but then we'd have to allow
14785 the same nest of reference nodes we allow for MODIFY_EXPR and
14786 that's too complex.
14788 Compare scalar mode aggregates as scalar mode values. Using
14789 memcmp for them would be very inefficient at best, and is
14790 plain wrong if bitfields are involved. */
14792 tree type = TREE_TYPE (TREE_OPERAND (*expr_p, 1));
14794 /* Vector comparisons need no boolification. */
14795 if (TREE_CODE (type) == VECTOR_TYPE)
14796 goto expr_2;
14797 else if (!AGGREGATE_TYPE_P (type))
14799 tree org_type = TREE_TYPE (*expr_p);
14800 *expr_p = gimple_boolify (*expr_p);
14801 if (!useless_type_conversion_p (org_type,
14802 TREE_TYPE (*expr_p)))
14804 *expr_p = fold_convert_loc (input_location,
14805 org_type, *expr_p);
14806 ret = GS_OK;
14808 else
14809 goto expr_2;
14811 else if (TYPE_MODE (type) != BLKmode)
14812 ret = gimplify_scalar_mode_aggregate_compare (expr_p);
14813 else
14814 ret = gimplify_variable_sized_compare (expr_p);
14816 break;
14819 /* If *EXPR_P does not need to be special-cased, handle it
14820 according to its class. */
14821 case tcc_unary:
14822 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
14823 post_p, is_gimple_val, fb_rvalue);
14824 break;
14826 case tcc_binary:
14827 expr_2:
14829 enum gimplify_status r0, r1;
14831 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
14832 post_p, is_gimple_val, fb_rvalue);
14833 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
14834 post_p, is_gimple_val, fb_rvalue);
14836 ret = MIN (r0, r1);
14837 break;
14840 expr_3:
14842 enum gimplify_status r0, r1, r2;
14844 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
14845 post_p, is_gimple_val, fb_rvalue);
14846 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
14847 post_p, is_gimple_val, fb_rvalue);
14848 r2 = gimplify_expr (&TREE_OPERAND (*expr_p, 2), pre_p,
14849 post_p, is_gimple_val, fb_rvalue);
14851 ret = MIN (MIN (r0, r1), r2);
14852 break;
14855 case tcc_declaration:
14856 case tcc_constant:
14857 ret = GS_ALL_DONE;
14858 goto dont_recalculate;
14860 default:
14861 gcc_unreachable ();
14864 recalculate_side_effects (*expr_p);
14866 dont_recalculate:
14867 break;
14870 gcc_assert (*expr_p || ret != GS_OK);
14872 while (ret == GS_OK);
14874 /* If we encountered an error_mark somewhere nested inside, either
14875 stub out the statement or propagate the error back out. */
14876 if (ret == GS_ERROR)
14878 if (is_statement)
14879 *expr_p = NULL;
14880 goto out;
14883 /* This was only valid as a return value from the langhook, which
14884 we handled. Make sure it doesn't escape from any other context. */
14885 gcc_assert (ret != GS_UNHANDLED);
14887 if (fallback == fb_none && *expr_p && !is_gimple_stmt (*expr_p))
14889 /* We aren't looking for a value, and we don't have a valid
14890 statement. If it doesn't have side-effects, throw it away.
14891 We can also get here with code such as "*&&L;", where L is
14892 a LABEL_DECL that is marked as FORCED_LABEL. */
14893 if (TREE_CODE (*expr_p) == LABEL_DECL
14894 || !TREE_SIDE_EFFECTS (*expr_p))
14895 *expr_p = NULL;
14896 else if (!TREE_THIS_VOLATILE (*expr_p))
14898 /* This is probably a _REF that contains something nested that
14899 has side effects. Recurse through the operands to find it. */
14900 enum tree_code code = TREE_CODE (*expr_p);
14902 switch (code)
14904 case COMPONENT_REF:
14905 case REALPART_EXPR:
14906 case IMAGPART_EXPR:
14907 case VIEW_CONVERT_EXPR:
14908 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
14909 gimple_test_f, fallback);
14910 break;
14912 case ARRAY_REF:
14913 case ARRAY_RANGE_REF:
14914 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
14915 gimple_test_f, fallback);
14916 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
14917 gimple_test_f, fallback);
14918 break;
14920 default:
14921 /* Anything else with side-effects must be converted to
14922 a valid statement before we get here. */
14923 gcc_unreachable ();
14926 *expr_p = NULL;
14928 else if (COMPLETE_TYPE_P (TREE_TYPE (*expr_p))
14929 && TYPE_MODE (TREE_TYPE (*expr_p)) != BLKmode)
14931 /* Historically, the compiler has treated a bare reference
14932 to a non-BLKmode volatile lvalue as forcing a load. */
14933 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (*expr_p));
14935 /* Normally, we do not want to create a temporary for a
14936 TREE_ADDRESSABLE type because such a type should not be
14937 copied by bitwise-assignment. However, we make an
14938 exception here, as all we are doing here is ensuring that
14939 we read the bytes that make up the type. We use
14940 create_tmp_var_raw because create_tmp_var will abort when
14941 given a TREE_ADDRESSABLE type. */
14942 tree tmp = create_tmp_var_raw (type, "vol");
14943 gimple_add_tmp_var (tmp);
14944 gimplify_assign (tmp, *expr_p, pre_p);
14945 *expr_p = NULL;
14947 else
14948 /* We can't do anything useful with a volatile reference to
14949 an incomplete type, so just throw it away. Likewise for
14950 a BLKmode type, since any implicit inner load should
14951 already have been turned into an explicit one by the
14952 gimplification process. */
14953 *expr_p = NULL;
14956 /* If we are gimplifying at the statement level, we're done. Tack
14957 everything together and return. */
14958 if (fallback == fb_none || is_statement)
14960 /* Since *EXPR_P has been converted into a GIMPLE tuple, clear
14961 it out for GC to reclaim it. */
14962 *expr_p = NULL_TREE;
14964 if (!gimple_seq_empty_p (internal_pre)
14965 || !gimple_seq_empty_p (internal_post))
14967 gimplify_seq_add_seq (&internal_pre, internal_post);
14968 gimplify_seq_add_seq (pre_p, internal_pre);
14971 /* The result of gimplifying *EXPR_P is going to be the last few
14972 statements in *PRE_P and *POST_P. Add location information
14973 to all the statements that were added by the gimplification
14974 helpers. */
14975 if (!gimple_seq_empty_p (*pre_p))
14976 annotate_all_with_location_after (*pre_p, pre_last_gsi, input_location);
14978 if (!gimple_seq_empty_p (*post_p))
14979 annotate_all_with_location_after (*post_p, post_last_gsi,
14980 input_location);
14982 goto out;
14985 #ifdef ENABLE_GIMPLE_CHECKING
14986 if (*expr_p)
14988 enum tree_code code = TREE_CODE (*expr_p);
14989 /* These expressions should already be in gimple IR form. */
14990 gcc_assert (code != MODIFY_EXPR
14991 && code != ASM_EXPR
14992 && code != BIND_EXPR
14993 && code != CATCH_EXPR
14994 && (code != COND_EXPR || gimplify_ctxp->allow_rhs_cond_expr)
14995 && code != EH_FILTER_EXPR
14996 && code != GOTO_EXPR
14997 && code != LABEL_EXPR
14998 && code != LOOP_EXPR
14999 && code != SWITCH_EXPR
15000 && code != TRY_FINALLY_EXPR
15001 && code != EH_ELSE_EXPR
15002 && code != OACC_PARALLEL
15003 && code != OACC_KERNELS
15004 && code != OACC_SERIAL
15005 && code != OACC_DATA
15006 && code != OACC_HOST_DATA
15007 && code != OACC_DECLARE
15008 && code != OACC_UPDATE
15009 && code != OACC_ENTER_DATA
15010 && code != OACC_EXIT_DATA
15011 && code != OACC_CACHE
15012 && code != OMP_CRITICAL
15013 && code != OMP_FOR
15014 && code != OACC_LOOP
15015 && code != OMP_MASTER
15016 && code != OMP_TASKGROUP
15017 && code != OMP_ORDERED
15018 && code != OMP_PARALLEL
15019 && code != OMP_SCAN
15020 && code != OMP_SECTIONS
15021 && code != OMP_SECTION
15022 && code != OMP_SINGLE);
15024 #endif
15026 /* Otherwise we're gimplifying a subexpression, so the resulting
15027 value is interesting. If it's a valid operand that matches
15028 GIMPLE_TEST_F, we're done. Unless we are handling some
15029 post-effects internally; if that's the case, we need to copy into
15030 a temporary before adding the post-effects to POST_P. */
15031 if (gimple_seq_empty_p (internal_post) && (*gimple_test_f) (*expr_p))
15032 goto out;
15034 /* Otherwise, we need to create a new temporary for the gimplified
15035 expression. */
15037 /* We can't return an lvalue if we have an internal postqueue. The
15038 object the lvalue refers to would (probably) be modified by the
15039 postqueue; we need to copy the value out first, which means an
15040 rvalue. */
15041 if ((fallback & fb_lvalue)
15042 && gimple_seq_empty_p (internal_post)
15043 && is_gimple_addressable (*expr_p))
15045 /* An lvalue will do. Take the address of the expression, store it
15046 in a temporary, and replace the expression with an INDIRECT_REF of
15047 that temporary. */
15048 tree ref_alias_type = reference_alias_ptr_type (*expr_p);
15049 unsigned int ref_align = get_object_alignment (*expr_p);
15050 tree ref_type = TREE_TYPE (*expr_p);
15051 tmp = build_fold_addr_expr_loc (input_location, *expr_p);
15052 gimplify_expr (&tmp, pre_p, post_p, is_gimple_reg, fb_rvalue);
15053 if (TYPE_ALIGN (ref_type) != ref_align)
15054 ref_type = build_aligned_type (ref_type, ref_align);
15055 *expr_p = build2 (MEM_REF, ref_type,
15056 tmp, build_zero_cst (ref_alias_type));
15058 else if ((fallback & fb_rvalue) && is_gimple_reg_rhs_or_call (*expr_p))
15060 /* An rvalue will do. Assign the gimplified expression into a
15061 new temporary TMP and replace the original expression with
15062 TMP. First, make sure that the expression has a type so that
15063 it can be assigned into a temporary. */
15064 gcc_assert (!VOID_TYPE_P (TREE_TYPE (*expr_p)));
15065 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
15067 else
15069 #ifdef ENABLE_GIMPLE_CHECKING
15070 if (!(fallback & fb_mayfail))
15072 fprintf (stderr, "gimplification failed:\n");
15073 print_generic_expr (stderr, *expr_p);
15074 debug_tree (*expr_p);
15075 internal_error ("gimplification failed");
15077 #endif
15078 gcc_assert (fallback & fb_mayfail);
15080 /* If this is an asm statement, and the user asked for the
15081 impossible, don't die. Fail and let gimplify_asm_expr
15082 issue an error. */
15083 ret = GS_ERROR;
15084 goto out;
15087 /* Make sure the temporary matches our predicate. */
15088 gcc_assert ((*gimple_test_f) (*expr_p));
15090 if (!gimple_seq_empty_p (internal_post))
15092 annotate_all_with_location (internal_post, input_location);
15093 gimplify_seq_add_seq (pre_p, internal_post);
15096 out:
15097 input_location = saved_location;
15098 return ret;
15101 /* Like gimplify_expr but make sure the gimplified result is not itself
15102 a SSA name (but a decl if it were). Temporaries required by
15103 evaluating *EXPR_P may be still SSA names. */
15105 static enum gimplify_status
15106 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
15107 bool (*gimple_test_f) (tree), fallback_t fallback,
15108 bool allow_ssa)
15110 bool was_ssa_name_p = TREE_CODE (*expr_p) == SSA_NAME;
15111 enum gimplify_status ret = gimplify_expr (expr_p, pre_p, post_p,
15112 gimple_test_f, fallback);
15113 if (! allow_ssa
15114 && TREE_CODE (*expr_p) == SSA_NAME)
15116 tree name = *expr_p;
15117 if (was_ssa_name_p)
15118 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, NULL, false);
15119 else
15121 /* Avoid the extra copy if possible. */
15122 *expr_p = create_tmp_reg (TREE_TYPE (name));
15123 if (!gimple_nop_p (SSA_NAME_DEF_STMT (name)))
15124 gimple_set_lhs (SSA_NAME_DEF_STMT (name), *expr_p);
15125 release_ssa_name (name);
15128 return ret;
15131 /* Look through TYPE for variable-sized objects and gimplify each such
15132 size that we find. Add to LIST_P any statements generated. */
15134 void
15135 gimplify_type_sizes (tree type, gimple_seq *list_p)
15137 if (type == NULL || type == error_mark_node)
15138 return;
15140 const bool ignored_p
15141 = TYPE_NAME (type)
15142 && TREE_CODE (TYPE_NAME (type)) == TYPE_DECL
15143 && DECL_IGNORED_P (TYPE_NAME (type));
15144 tree t;
15146 /* We first do the main variant, then copy into any other variants. */
15147 type = TYPE_MAIN_VARIANT (type);
15149 /* Avoid infinite recursion. */
15150 if (TYPE_SIZES_GIMPLIFIED (type))
15151 return;
15153 TYPE_SIZES_GIMPLIFIED (type) = 1;
15155 switch (TREE_CODE (type))
15157 case INTEGER_TYPE:
15158 case ENUMERAL_TYPE:
15159 case BOOLEAN_TYPE:
15160 case REAL_TYPE:
15161 case FIXED_POINT_TYPE:
15162 gimplify_one_sizepos (&TYPE_MIN_VALUE (type), list_p);
15163 gimplify_one_sizepos (&TYPE_MAX_VALUE (type), list_p);
15165 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
15167 TYPE_MIN_VALUE (t) = TYPE_MIN_VALUE (type);
15168 TYPE_MAX_VALUE (t) = TYPE_MAX_VALUE (type);
15170 break;
15172 case ARRAY_TYPE:
15173 /* These types may not have declarations, so handle them here. */
15174 gimplify_type_sizes (TREE_TYPE (type), list_p);
15175 gimplify_type_sizes (TYPE_DOMAIN (type), list_p);
15176 /* Ensure VLA bounds aren't removed, for -O0 they should be variables
15177 with assigned stack slots, for -O1+ -g they should be tracked
15178 by VTA. */
15179 if (!ignored_p
15180 && TYPE_DOMAIN (type)
15181 && INTEGRAL_TYPE_P (TYPE_DOMAIN (type)))
15183 t = TYPE_MIN_VALUE (TYPE_DOMAIN (type));
15184 if (t && VAR_P (t) && DECL_ARTIFICIAL (t))
15185 DECL_IGNORED_P (t) = 0;
15186 t = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
15187 if (t && VAR_P (t) && DECL_ARTIFICIAL (t))
15188 DECL_IGNORED_P (t) = 0;
15190 break;
15192 case RECORD_TYPE:
15193 case UNION_TYPE:
15194 case QUAL_UNION_TYPE:
15195 for (tree field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
15196 if (TREE_CODE (field) == FIELD_DECL)
15198 gimplify_one_sizepos (&DECL_FIELD_OFFSET (field), list_p);
15199 /* Likewise, ensure variable offsets aren't removed. */
15200 if (!ignored_p
15201 && (t = DECL_FIELD_OFFSET (field))
15202 && VAR_P (t)
15203 && DECL_ARTIFICIAL (t))
15204 DECL_IGNORED_P (t) = 0;
15205 gimplify_one_sizepos (&DECL_SIZE (field), list_p);
15206 gimplify_one_sizepos (&DECL_SIZE_UNIT (field), list_p);
15207 gimplify_type_sizes (TREE_TYPE (field), list_p);
15209 break;
15211 case POINTER_TYPE:
15212 case REFERENCE_TYPE:
15213 /* We used to recurse on the pointed-to type here, which turned out to
15214 be incorrect because its definition might refer to variables not
15215 yet initialized at this point if a forward declaration is involved.
15217 It was actually useful for anonymous pointed-to types to ensure
15218 that the sizes evaluation dominates every possible later use of the
15219 values. Restricting to such types here would be safe since there
15220 is no possible forward declaration around, but would introduce an
15221 undesirable middle-end semantic to anonymity. We then defer to
15222 front-ends the responsibility of ensuring that the sizes are
15223 evaluated both early and late enough, e.g. by attaching artificial
15224 type declarations to the tree. */
15225 break;
15227 default:
15228 break;
15231 gimplify_one_sizepos (&TYPE_SIZE (type), list_p);
15232 gimplify_one_sizepos (&TYPE_SIZE_UNIT (type), list_p);
15234 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
15236 TYPE_SIZE (t) = TYPE_SIZE (type);
15237 TYPE_SIZE_UNIT (t) = TYPE_SIZE_UNIT (type);
15238 TYPE_SIZES_GIMPLIFIED (t) = 1;
15242 /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
15243 a size or position, has had all of its SAVE_EXPRs evaluated.
15244 We add any required statements to *STMT_P. */
15246 void
15247 gimplify_one_sizepos (tree *expr_p, gimple_seq *stmt_p)
15249 tree expr = *expr_p;
15251 /* We don't do anything if the value isn't there, is constant, or contains
15252 A PLACEHOLDER_EXPR. We also don't want to do anything if it's already
15253 a VAR_DECL. If it's a VAR_DECL from another function, the gimplifier
15254 will want to replace it with a new variable, but that will cause problems
15255 if this type is from outside the function. It's OK to have that here. */
15256 if (expr == NULL_TREE
15257 || is_gimple_constant (expr)
15258 || TREE_CODE (expr) == VAR_DECL
15259 || CONTAINS_PLACEHOLDER_P (expr))
15260 return;
15262 *expr_p = unshare_expr (expr);
15264 /* SSA names in decl/type fields are a bad idea - they'll get reclaimed
15265 if the def vanishes. */
15266 gimplify_expr (expr_p, stmt_p, NULL, is_gimple_val, fb_rvalue, false);
15268 /* If expr wasn't already is_gimple_sizepos or is_gimple_constant from the
15269 FE, ensure that it is a VAR_DECL, otherwise we might handle some decls
15270 as gimplify_vla_decl even when they would have all sizes INTEGER_CSTs. */
15271 if (is_gimple_constant (*expr_p))
15272 *expr_p = get_initialized_tmp_var (*expr_p, stmt_p, NULL, false);
15275 /* Gimplify the body of statements of FNDECL and return a GIMPLE_BIND node
15276 containing the sequence of corresponding GIMPLE statements. If DO_PARMS
15277 is true, also gimplify the parameters. */
15279 gbind *
15280 gimplify_body (tree fndecl, bool do_parms)
15282 location_t saved_location = input_location;
15283 gimple_seq parm_stmts, parm_cleanup = NULL, seq;
15284 gimple *outer_stmt;
15285 gbind *outer_bind;
15287 timevar_push (TV_TREE_GIMPLIFY);
15289 init_tree_ssa (cfun);
15291 /* Initialize for optimize_insn_for_s{ize,peed}_p possibly called during
15292 gimplification. */
15293 default_rtl_profile ();
15295 gcc_assert (gimplify_ctxp == NULL);
15296 push_gimplify_context (true);
15298 if (flag_openacc || flag_openmp)
15300 gcc_assert (gimplify_omp_ctxp == NULL);
15301 if (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (fndecl)))
15302 gimplify_omp_ctxp = new_omp_context (ORT_IMPLICIT_TARGET);
15305 /* Unshare most shared trees in the body and in that of any nested functions.
15306 It would seem we don't have to do this for nested functions because
15307 they are supposed to be output and then the outer function gimplified
15308 first, but the g++ front end doesn't always do it that way. */
15309 unshare_body (fndecl);
15310 unvisit_body (fndecl);
15312 /* Make sure input_location isn't set to something weird. */
15313 input_location = DECL_SOURCE_LOCATION (fndecl);
15315 /* Resolve callee-copies. This has to be done before processing
15316 the body so that DECL_VALUE_EXPR gets processed correctly. */
15317 parm_stmts = do_parms ? gimplify_parameters (&parm_cleanup) : NULL;
15319 /* Gimplify the function's body. */
15320 seq = NULL;
15321 gimplify_stmt (&DECL_SAVED_TREE (fndecl), &seq);
15322 outer_stmt = gimple_seq_first_nondebug_stmt (seq);
15323 if (!outer_stmt)
15325 outer_stmt = gimple_build_nop ();
15326 gimplify_seq_add_stmt (&seq, outer_stmt);
15329 /* The body must contain exactly one statement, a GIMPLE_BIND. If this is
15330 not the case, wrap everything in a GIMPLE_BIND to make it so. */
15331 if (gimple_code (outer_stmt) == GIMPLE_BIND
15332 && (gimple_seq_first_nondebug_stmt (seq)
15333 == gimple_seq_last_nondebug_stmt (seq)))
15335 outer_bind = as_a <gbind *> (outer_stmt);
15336 if (gimple_seq_first_stmt (seq) != outer_stmt
15337 || gimple_seq_last_stmt (seq) != outer_stmt)
15339 /* If there are debug stmts before or after outer_stmt, move them
15340 inside of outer_bind body. */
15341 gimple_stmt_iterator gsi = gsi_for_stmt (outer_stmt, &seq);
15342 gimple_seq second_seq = NULL;
15343 if (gimple_seq_first_stmt (seq) != outer_stmt
15344 && gimple_seq_last_stmt (seq) != outer_stmt)
15346 second_seq = gsi_split_seq_after (gsi);
15347 gsi_remove (&gsi, false);
15349 else if (gimple_seq_first_stmt (seq) != outer_stmt)
15350 gsi_remove (&gsi, false);
15351 else
15353 gsi_remove (&gsi, false);
15354 second_seq = seq;
15355 seq = NULL;
15357 gimple_seq_add_seq_without_update (&seq,
15358 gimple_bind_body (outer_bind));
15359 gimple_seq_add_seq_without_update (&seq, second_seq);
15360 gimple_bind_set_body (outer_bind, seq);
15363 else
15364 outer_bind = gimple_build_bind (NULL_TREE, seq, NULL);
15366 DECL_SAVED_TREE (fndecl) = NULL_TREE;
15368 /* If we had callee-copies statements, insert them at the beginning
15369 of the function and clear DECL_VALUE_EXPR_P on the parameters. */
15370 if (!gimple_seq_empty_p (parm_stmts))
15372 tree parm;
15374 gimplify_seq_add_seq (&parm_stmts, gimple_bind_body (outer_bind));
15375 if (parm_cleanup)
15377 gtry *g = gimple_build_try (parm_stmts, parm_cleanup,
15378 GIMPLE_TRY_FINALLY);
15379 parm_stmts = NULL;
15380 gimple_seq_add_stmt (&parm_stmts, g);
15382 gimple_bind_set_body (outer_bind, parm_stmts);
15384 for (parm = DECL_ARGUMENTS (current_function_decl);
15385 parm; parm = DECL_CHAIN (parm))
15386 if (DECL_HAS_VALUE_EXPR_P (parm))
15388 DECL_HAS_VALUE_EXPR_P (parm) = 0;
15389 DECL_IGNORED_P (parm) = 0;
15393 if ((flag_openacc || flag_openmp || flag_openmp_simd)
15394 && gimplify_omp_ctxp)
15396 delete_omp_context (gimplify_omp_ctxp);
15397 gimplify_omp_ctxp = NULL;
15400 pop_gimplify_context (outer_bind);
15401 gcc_assert (gimplify_ctxp == NULL);
15403 if (flag_checking && !seen_error ())
15404 verify_gimple_in_seq (gimple_bind_body (outer_bind));
15406 timevar_pop (TV_TREE_GIMPLIFY);
15407 input_location = saved_location;
15409 return outer_bind;
15412 typedef char *char_p; /* For DEF_VEC_P. */
15414 /* Return whether we should exclude FNDECL from instrumentation. */
15416 static bool
15417 flag_instrument_functions_exclude_p (tree fndecl)
15419 vec<char_p> *v;
15421 v = (vec<char_p> *) flag_instrument_functions_exclude_functions;
15422 if (v && v->length () > 0)
15424 const char *name;
15425 int i;
15426 char *s;
15428 name = lang_hooks.decl_printable_name (fndecl, 1);
15429 FOR_EACH_VEC_ELT (*v, i, s)
15430 if (strstr (name, s) != NULL)
15431 return true;
15434 v = (vec<char_p> *) flag_instrument_functions_exclude_files;
15435 if (v && v->length () > 0)
15437 const char *name;
15438 int i;
15439 char *s;
15441 name = DECL_SOURCE_FILE (fndecl);
15442 FOR_EACH_VEC_ELT (*v, i, s)
15443 if (strstr (name, s) != NULL)
15444 return true;
15447 return false;
15450 /* Entry point to the gimplification pass. FNDECL is the FUNCTION_DECL
15451 node for the function we want to gimplify.
15453 Return the sequence of GIMPLE statements corresponding to the body
15454 of FNDECL. */
15456 void
15457 gimplify_function_tree (tree fndecl)
15459 gimple_seq seq;
15460 gbind *bind;
15462 gcc_assert (!gimple_body (fndecl));
15464 if (DECL_STRUCT_FUNCTION (fndecl))
15465 push_cfun (DECL_STRUCT_FUNCTION (fndecl));
15466 else
15467 push_struct_function (fndecl);
15469 /* Tentatively set PROP_gimple_lva here, and reset it in gimplify_va_arg_expr
15470 if necessary. */
15471 cfun->curr_properties |= PROP_gimple_lva;
15473 if (asan_sanitize_use_after_scope ())
15474 asan_poisoned_variables = new hash_set<tree> ();
15475 bind = gimplify_body (fndecl, true);
15476 if (asan_poisoned_variables)
15478 delete asan_poisoned_variables;
15479 asan_poisoned_variables = NULL;
15482 /* The tree body of the function is no longer needed, replace it
15483 with the new GIMPLE body. */
15484 seq = NULL;
15485 gimple_seq_add_stmt (&seq, bind);
15486 gimple_set_body (fndecl, seq);
15488 /* If we're instrumenting function entry/exit, then prepend the call to
15489 the entry hook and wrap the whole function in a TRY_FINALLY_EXPR to
15490 catch the exit hook. */
15491 /* ??? Add some way to ignore exceptions for this TFE. */
15492 if (flag_instrument_function_entry_exit
15493 && !DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT (fndecl)
15494 /* Do not instrument extern inline functions. */
15495 && !(DECL_DECLARED_INLINE_P (fndecl)
15496 && DECL_EXTERNAL (fndecl)
15497 && DECL_DISREGARD_INLINE_LIMITS (fndecl))
15498 && !flag_instrument_functions_exclude_p (fndecl))
15500 tree x;
15501 gbind *new_bind;
15502 gimple *tf;
15503 gimple_seq cleanup = NULL, body = NULL;
15504 tree tmp_var, this_fn_addr;
15505 gcall *call;
15507 /* The instrumentation hooks aren't going to call the instrumented
15508 function and the address they receive is expected to be matchable
15509 against symbol addresses. Make sure we don't create a trampoline,
15510 in case the current function is nested. */
15511 this_fn_addr = build_fold_addr_expr (current_function_decl);
15512 TREE_NO_TRAMPOLINE (this_fn_addr) = 1;
15514 x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
15515 call = gimple_build_call (x, 1, integer_zero_node);
15516 tmp_var = create_tmp_var (ptr_type_node, "return_addr");
15517 gimple_call_set_lhs (call, tmp_var);
15518 gimplify_seq_add_stmt (&cleanup, call);
15519 x = builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_EXIT);
15520 call = gimple_build_call (x, 2, this_fn_addr, tmp_var);
15521 gimplify_seq_add_stmt (&cleanup, call);
15522 tf = gimple_build_try (seq, cleanup, GIMPLE_TRY_FINALLY);
15524 x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
15525 call = gimple_build_call (x, 1, integer_zero_node);
15526 tmp_var = create_tmp_var (ptr_type_node, "return_addr");
15527 gimple_call_set_lhs (call, tmp_var);
15528 gimplify_seq_add_stmt (&body, call);
15529 x = builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_ENTER);
15530 call = gimple_build_call (x, 2, this_fn_addr, tmp_var);
15531 gimplify_seq_add_stmt (&body, call);
15532 gimplify_seq_add_stmt (&body, tf);
15533 new_bind = gimple_build_bind (NULL, body, NULL);
15535 /* Replace the current function body with the body
15536 wrapped in the try/finally TF. */
15537 seq = NULL;
15538 gimple_seq_add_stmt (&seq, new_bind);
15539 gimple_set_body (fndecl, seq);
15540 bind = new_bind;
15543 if (sanitize_flags_p (SANITIZE_THREAD)
15544 && param_tsan_instrument_func_entry_exit)
15546 gcall *call = gimple_build_call_internal (IFN_TSAN_FUNC_EXIT, 0);
15547 gimple *tf = gimple_build_try (seq, call, GIMPLE_TRY_FINALLY);
15548 gbind *new_bind = gimple_build_bind (NULL, tf, NULL);
15549 /* Replace the current function body with the body
15550 wrapped in the try/finally TF. */
15551 seq = NULL;
15552 gimple_seq_add_stmt (&seq, new_bind);
15553 gimple_set_body (fndecl, seq);
15556 DECL_SAVED_TREE (fndecl) = NULL_TREE;
15557 cfun->curr_properties |= PROP_gimple_any;
15559 pop_cfun ();
15561 dump_function (TDI_gimple, fndecl);
15564 /* Return a dummy expression of type TYPE in order to keep going after an
15565 error. */
15567 static tree
15568 dummy_object (tree type)
15570 tree t = build_int_cst (build_pointer_type (type), 0);
15571 return build2 (MEM_REF, type, t, t);
15574 /* Gimplify __builtin_va_arg, aka VA_ARG_EXPR, which is not really a
15575 builtin function, but a very special sort of operator. */
15577 enum gimplify_status
15578 gimplify_va_arg_expr (tree *expr_p, gimple_seq *pre_p,
15579 gimple_seq *post_p ATTRIBUTE_UNUSED)
15581 tree promoted_type, have_va_type;
15582 tree valist = TREE_OPERAND (*expr_p, 0);
15583 tree type = TREE_TYPE (*expr_p);
15584 tree t, tag, aptag;
15585 location_t loc = EXPR_LOCATION (*expr_p);
15587 /* Verify that valist is of the proper type. */
15588 have_va_type = TREE_TYPE (valist);
15589 if (have_va_type == error_mark_node)
15590 return GS_ERROR;
15591 have_va_type = targetm.canonical_va_list_type (have_va_type);
15592 if (have_va_type == NULL_TREE
15593 && POINTER_TYPE_P (TREE_TYPE (valist)))
15594 /* Handle 'Case 1: Not an array type' from c-common.c/build_va_arg. */
15595 have_va_type
15596 = targetm.canonical_va_list_type (TREE_TYPE (TREE_TYPE (valist)));
15597 gcc_assert (have_va_type != NULL_TREE);
15599 /* Generate a diagnostic for requesting data of a type that cannot
15600 be passed through `...' due to type promotion at the call site. */
15601 if ((promoted_type = lang_hooks.types.type_promotes_to (type))
15602 != type)
15604 static bool gave_help;
15605 bool warned;
15606 /* Use the expansion point to handle cases such as passing bool (defined
15607 in a system header) through `...'. */
15608 location_t xloc
15609 = expansion_point_location_if_in_system_header (loc);
15611 /* Unfortunately, this is merely undefined, rather than a constraint
15612 violation, so we cannot make this an error. If this call is never
15613 executed, the program is still strictly conforming. */
15614 auto_diagnostic_group d;
15615 warned = warning_at (xloc, 0,
15616 "%qT is promoted to %qT when passed through %<...%>",
15617 type, promoted_type);
15618 if (!gave_help && warned)
15620 gave_help = true;
15621 inform (xloc, "(so you should pass %qT not %qT to %<va_arg%>)",
15622 promoted_type, type);
15625 /* We can, however, treat "undefined" any way we please.
15626 Call abort to encourage the user to fix the program. */
15627 if (warned)
15628 inform (xloc, "if this code is reached, the program will abort");
15629 /* Before the abort, allow the evaluation of the va_list
15630 expression to exit or longjmp. */
15631 gimplify_and_add (valist, pre_p);
15632 t = build_call_expr_loc (loc,
15633 builtin_decl_implicit (BUILT_IN_TRAP), 0);
15634 gimplify_and_add (t, pre_p);
15636 /* This is dead code, but go ahead and finish so that the
15637 mode of the result comes out right. */
15638 *expr_p = dummy_object (type);
15639 return GS_ALL_DONE;
15642 tag = build_int_cst (build_pointer_type (type), 0);
15643 aptag = build_int_cst (TREE_TYPE (valist), 0);
15645 *expr_p = build_call_expr_internal_loc (loc, IFN_VA_ARG, type, 3,
15646 valist, tag, aptag);
15648 /* Clear the tentatively set PROP_gimple_lva, to indicate that IFN_VA_ARG
15649 needs to be expanded. */
15650 cfun->curr_properties &= ~PROP_gimple_lva;
15652 return GS_OK;
15655 /* Build a new GIMPLE_ASSIGN tuple and append it to the end of *SEQ_P.
15657 DST/SRC are the destination and source respectively. You can pass
15658 ungimplified trees in DST or SRC, in which case they will be
15659 converted to a gimple operand if necessary.
15661 This function returns the newly created GIMPLE_ASSIGN tuple. */
15663 gimple *
15664 gimplify_assign (tree dst, tree src, gimple_seq *seq_p)
15666 tree t = build2 (MODIFY_EXPR, TREE_TYPE (dst), dst, src);
15667 gimplify_and_add (t, seq_p);
15668 ggc_free (t);
15669 return gimple_seq_last_stmt (*seq_p);
15672 inline hashval_t
15673 gimplify_hasher::hash (const elt_t *p)
15675 tree t = p->val;
15676 return iterative_hash_expr (t, 0);
15679 inline bool
15680 gimplify_hasher::equal (const elt_t *p1, const elt_t *p2)
15682 tree t1 = p1->val;
15683 tree t2 = p2->val;
15684 enum tree_code code = TREE_CODE (t1);
15686 if (TREE_CODE (t2) != code
15687 || TREE_TYPE (t1) != TREE_TYPE (t2))
15688 return false;
15690 if (!operand_equal_p (t1, t2, 0))
15691 return false;
15693 /* Only allow them to compare equal if they also hash equal; otherwise
15694 results are nondeterminate, and we fail bootstrap comparison. */
15695 gcc_checking_assert (hash (p1) == hash (p2));
15697 return true;