fwprop: Fix single_use_p calculation
[official-gcc.git] / gcc / gimplify.c
blob6da66985ad62cc170158f76656fe3085b6246567
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 = 8388608,
131 GOVD_DATA_SHARE_CLASS = (GOVD_SHARED | GOVD_PRIVATE | GOVD_FIRSTPRIVATE
132 | GOVD_LASTPRIVATE | GOVD_REDUCTION | GOVD_LINEAR
133 | GOVD_LOCAL)
137 enum omp_region_type
139 ORT_WORKSHARE = 0x00,
140 ORT_TASKGROUP = 0x01,
141 ORT_SIMD = 0x04,
143 ORT_PARALLEL = 0x08,
144 ORT_COMBINED_PARALLEL = ORT_PARALLEL | 1,
146 ORT_TASK = 0x10,
147 ORT_UNTIED_TASK = ORT_TASK | 1,
148 ORT_TASKLOOP = ORT_TASK | 2,
149 ORT_UNTIED_TASKLOOP = ORT_UNTIED_TASK | 2,
151 ORT_TEAMS = 0x20,
152 ORT_COMBINED_TEAMS = ORT_TEAMS | 1,
153 ORT_HOST_TEAMS = ORT_TEAMS | 2,
154 ORT_COMBINED_HOST_TEAMS = ORT_COMBINED_TEAMS | 2,
156 /* Data region. */
157 ORT_TARGET_DATA = 0x40,
159 /* Data region with offloading. */
160 ORT_TARGET = 0x80,
161 ORT_COMBINED_TARGET = ORT_TARGET | 1,
162 ORT_IMPLICIT_TARGET = ORT_TARGET | 2,
164 /* OpenACC variants. */
165 ORT_ACC = 0x100, /* A generic OpenACC region. */
166 ORT_ACC_DATA = ORT_ACC | ORT_TARGET_DATA, /* Data construct. */
167 ORT_ACC_PARALLEL = ORT_ACC | ORT_TARGET, /* Parallel construct */
168 ORT_ACC_KERNELS = ORT_ACC | ORT_TARGET | 2, /* Kernels construct. */
169 ORT_ACC_SERIAL = ORT_ACC | ORT_TARGET | 4, /* Serial construct. */
170 ORT_ACC_HOST_DATA = ORT_ACC | ORT_TARGET_DATA | 2, /* Host data. */
172 /* Dummy OpenMP region, used to disable expansion of
173 DECL_VALUE_EXPRs in taskloop pre body. */
174 ORT_NONE = 0x200
177 /* Gimplify hashtable helper. */
179 struct gimplify_hasher : free_ptr_hash <elt_t>
181 static inline hashval_t hash (const elt_t *);
182 static inline bool equal (const elt_t *, const elt_t *);
185 struct gimplify_ctx
187 struct gimplify_ctx *prev_context;
189 vec<gbind *> bind_expr_stack;
190 tree temps;
191 gimple_seq conditional_cleanups;
192 tree exit_label;
193 tree return_temp;
195 vec<tree> case_labels;
196 hash_set<tree> *live_switch_vars;
197 /* The formal temporary table. Should this be persistent? */
198 hash_table<gimplify_hasher> *temp_htab;
200 int conditions;
201 unsigned into_ssa : 1;
202 unsigned allow_rhs_cond_expr : 1;
203 unsigned in_cleanup_point_expr : 1;
204 unsigned keep_stack : 1;
205 unsigned save_stack : 1;
206 unsigned in_switch_expr : 1;
209 enum gimplify_defaultmap_kind
211 GDMK_SCALAR,
212 GDMK_AGGREGATE,
213 GDMK_ALLOCATABLE,
214 GDMK_POINTER
217 struct gimplify_omp_ctx
219 struct gimplify_omp_ctx *outer_context;
220 splay_tree variables;
221 hash_set<tree> *privatized_types;
222 tree clauses;
223 /* Iteration variables in an OMP_FOR. */
224 vec<tree> loop_iter_var;
225 location_t location;
226 enum omp_clause_default_kind default_kind;
227 enum omp_region_type region_type;
228 enum tree_code code;
229 bool combined_loop;
230 bool distribute;
231 bool target_firstprivatize_array_bases;
232 bool add_safelen1;
233 bool order_concurrent;
234 bool has_depend;
235 bool in_for_exprs;
236 int defaultmap[4];
239 static struct gimplify_ctx *gimplify_ctxp;
240 static struct gimplify_omp_ctx *gimplify_omp_ctxp;
241 static bool in_omp_construct;
243 /* Forward declaration. */
244 static enum gimplify_status gimplify_compound_expr (tree *, gimple_seq *, bool);
245 static hash_map<tree, tree> *oacc_declare_returns;
246 static enum gimplify_status gimplify_expr (tree *, gimple_seq *, gimple_seq *,
247 bool (*) (tree), fallback_t, bool);
249 /* Shorter alias name for the above function for use in gimplify.c
250 only. */
252 static inline void
253 gimplify_seq_add_stmt (gimple_seq *seq_p, gimple *gs)
255 gimple_seq_add_stmt_without_update (seq_p, gs);
258 /* Append sequence SRC to the end of sequence *DST_P. If *DST_P is
259 NULL, a new sequence is allocated. This function is
260 similar to gimple_seq_add_seq, but does not scan the operands.
261 During gimplification, we need to manipulate statement sequences
262 before the def/use vectors have been constructed. */
264 static void
265 gimplify_seq_add_seq (gimple_seq *dst_p, gimple_seq src)
267 gimple_stmt_iterator si;
269 if (src == NULL)
270 return;
272 si = gsi_last (*dst_p);
273 gsi_insert_seq_after_without_update (&si, src, GSI_NEW_STMT);
277 /* Pointer to a list of allocated gimplify_ctx structs to be used for pushing
278 and popping gimplify contexts. */
280 static struct gimplify_ctx *ctx_pool = NULL;
282 /* Return a gimplify context struct from the pool. */
284 static inline struct gimplify_ctx *
285 ctx_alloc (void)
287 struct gimplify_ctx * c = ctx_pool;
289 if (c)
290 ctx_pool = c->prev_context;
291 else
292 c = XNEW (struct gimplify_ctx);
294 memset (c, '\0', sizeof (*c));
295 return c;
298 /* Put gimplify context C back into the pool. */
300 static inline void
301 ctx_free (struct gimplify_ctx *c)
303 c->prev_context = ctx_pool;
304 ctx_pool = c;
307 /* Free allocated ctx stack memory. */
309 void
310 free_gimplify_stack (void)
312 struct gimplify_ctx *c;
314 while ((c = ctx_pool))
316 ctx_pool = c->prev_context;
317 free (c);
322 /* Set up a context for the gimplifier. */
324 void
325 push_gimplify_context (bool in_ssa, bool rhs_cond_ok)
327 struct gimplify_ctx *c = ctx_alloc ();
329 c->prev_context = gimplify_ctxp;
330 gimplify_ctxp = c;
331 gimplify_ctxp->into_ssa = in_ssa;
332 gimplify_ctxp->allow_rhs_cond_expr = rhs_cond_ok;
335 /* Tear down a context for the gimplifier. If BODY is non-null, then
336 put the temporaries into the outer BIND_EXPR. Otherwise, put them
337 in the local_decls.
339 BODY is not a sequence, but the first tuple in a sequence. */
341 void
342 pop_gimplify_context (gimple *body)
344 struct gimplify_ctx *c = gimplify_ctxp;
346 gcc_assert (c
347 && (!c->bind_expr_stack.exists ()
348 || c->bind_expr_stack.is_empty ()));
349 c->bind_expr_stack.release ();
350 gimplify_ctxp = c->prev_context;
352 if (body)
353 declare_vars (c->temps, body, false);
354 else
355 record_vars (c->temps);
357 delete c->temp_htab;
358 c->temp_htab = NULL;
359 ctx_free (c);
362 /* Push a GIMPLE_BIND tuple onto the stack of bindings. */
364 static void
365 gimple_push_bind_expr (gbind *bind_stmt)
367 gimplify_ctxp->bind_expr_stack.reserve (8);
368 gimplify_ctxp->bind_expr_stack.safe_push (bind_stmt);
371 /* Pop the first element off the stack of bindings. */
373 static void
374 gimple_pop_bind_expr (void)
376 gimplify_ctxp->bind_expr_stack.pop ();
379 /* Return the first element of the stack of bindings. */
381 gbind *
382 gimple_current_bind_expr (void)
384 return gimplify_ctxp->bind_expr_stack.last ();
387 /* Return the stack of bindings created during gimplification. */
389 vec<gbind *>
390 gimple_bind_expr_stack (void)
392 return gimplify_ctxp->bind_expr_stack;
395 /* Return true iff there is a COND_EXPR between us and the innermost
396 CLEANUP_POINT_EXPR. This info is used by gimple_push_cleanup. */
398 static bool
399 gimple_conditional_context (void)
401 return gimplify_ctxp->conditions > 0;
404 /* Note that we've entered a COND_EXPR. */
406 static void
407 gimple_push_condition (void)
409 #ifdef ENABLE_GIMPLE_CHECKING
410 if (gimplify_ctxp->conditions == 0)
411 gcc_assert (gimple_seq_empty_p (gimplify_ctxp->conditional_cleanups));
412 #endif
413 ++(gimplify_ctxp->conditions);
416 /* Note that we've left a COND_EXPR. If we're back at unconditional scope
417 now, add any conditional cleanups we've seen to the prequeue. */
419 static void
420 gimple_pop_condition (gimple_seq *pre_p)
422 int conds = --(gimplify_ctxp->conditions);
424 gcc_assert (conds >= 0);
425 if (conds == 0)
427 gimplify_seq_add_seq (pre_p, gimplify_ctxp->conditional_cleanups);
428 gimplify_ctxp->conditional_cleanups = NULL;
432 /* A stable comparison routine for use with splay trees and DECLs. */
434 static int
435 splay_tree_compare_decl_uid (splay_tree_key xa, splay_tree_key xb)
437 tree a = (tree) xa;
438 tree b = (tree) xb;
440 return DECL_UID (a) - DECL_UID (b);
443 /* Create a new omp construct that deals with variable remapping. */
445 static struct gimplify_omp_ctx *
446 new_omp_context (enum omp_region_type region_type)
448 struct gimplify_omp_ctx *c;
450 c = XCNEW (struct gimplify_omp_ctx);
451 c->outer_context = gimplify_omp_ctxp;
452 c->variables = splay_tree_new (splay_tree_compare_decl_uid, 0, 0);
453 c->privatized_types = new hash_set<tree>;
454 c->location = input_location;
455 c->region_type = region_type;
456 if ((region_type & ORT_TASK) == 0)
457 c->default_kind = OMP_CLAUSE_DEFAULT_SHARED;
458 else
459 c->default_kind = OMP_CLAUSE_DEFAULT_UNSPECIFIED;
460 c->defaultmap[GDMK_SCALAR] = GOVD_MAP;
461 c->defaultmap[GDMK_AGGREGATE] = GOVD_MAP;
462 c->defaultmap[GDMK_ALLOCATABLE] = GOVD_MAP;
463 c->defaultmap[GDMK_POINTER] = GOVD_MAP;
465 return c;
468 /* Destroy an omp construct that deals with variable remapping. */
470 static void
471 delete_omp_context (struct gimplify_omp_ctx *c)
473 splay_tree_delete (c->variables);
474 delete c->privatized_types;
475 c->loop_iter_var.release ();
476 XDELETE (c);
479 static void omp_add_variable (struct gimplify_omp_ctx *, tree, unsigned int);
480 static bool omp_notice_variable (struct gimplify_omp_ctx *, tree, bool);
482 /* Both gimplify the statement T and append it to *SEQ_P. This function
483 behaves exactly as gimplify_stmt, but you don't have to pass T as a
484 reference. */
486 void
487 gimplify_and_add (tree t, gimple_seq *seq_p)
489 gimplify_stmt (&t, seq_p);
492 /* Gimplify statement T into sequence *SEQ_P, and return the first
493 tuple in the sequence of generated tuples for this statement.
494 Return NULL if gimplifying T produced no tuples. */
496 static gimple *
497 gimplify_and_return_first (tree t, gimple_seq *seq_p)
499 gimple_stmt_iterator last = gsi_last (*seq_p);
501 gimplify_and_add (t, seq_p);
503 if (!gsi_end_p (last))
505 gsi_next (&last);
506 return gsi_stmt (last);
508 else
509 return gimple_seq_first_stmt (*seq_p);
512 /* Returns true iff T is a valid RHS for an assignment to an un-renamed
513 LHS, or for a call argument. */
515 static bool
516 is_gimple_mem_rhs (tree t)
518 /* If we're dealing with a renamable type, either source or dest must be
519 a renamed variable. */
520 if (is_gimple_reg_type (TREE_TYPE (t)))
521 return is_gimple_val (t);
522 else
523 return is_gimple_val (t) || is_gimple_lvalue (t);
526 /* Return true if T is a CALL_EXPR or an expression that can be
527 assigned to a temporary. Note that this predicate should only be
528 used during gimplification. See the rationale for this in
529 gimplify_modify_expr. */
531 static bool
532 is_gimple_reg_rhs_or_call (tree t)
534 return (get_gimple_rhs_class (TREE_CODE (t)) != GIMPLE_INVALID_RHS
535 || TREE_CODE (t) == CALL_EXPR);
538 /* Return true if T is a valid memory RHS or a CALL_EXPR. Note that
539 this predicate should only be used during gimplification. See the
540 rationale for this in gimplify_modify_expr. */
542 static bool
543 is_gimple_mem_rhs_or_call (tree t)
545 /* If we're dealing with a renamable type, either source or dest must be
546 a renamed variable. */
547 if (is_gimple_reg_type (TREE_TYPE (t)))
548 return is_gimple_val (t);
549 else
550 return (is_gimple_val (t)
551 || is_gimple_lvalue (t)
552 || TREE_CLOBBER_P (t)
553 || TREE_CODE (t) == CALL_EXPR);
556 /* Create a temporary with a name derived from VAL. Subroutine of
557 lookup_tmp_var; nobody else should call this function. */
559 static inline tree
560 create_tmp_from_val (tree val)
562 /* Drop all qualifiers and address-space information from the value type. */
563 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (val));
564 tree var = create_tmp_var (type, get_name (val));
565 return var;
568 /* Create a temporary to hold the value of VAL. If IS_FORMAL, try to reuse
569 an existing expression temporary. */
571 static tree
572 lookup_tmp_var (tree val, bool is_formal)
574 tree ret;
576 /* If not optimizing, never really reuse a temporary. local-alloc
577 won't allocate any variable that is used in more than one basic
578 block, which means it will go into memory, causing much extra
579 work in reload and final and poorer code generation, outweighing
580 the extra memory allocation here. */
581 if (!optimize || !is_formal || TREE_SIDE_EFFECTS (val))
582 ret = create_tmp_from_val (val);
583 else
585 elt_t elt, *elt_p;
586 elt_t **slot;
588 elt.val = val;
589 if (!gimplify_ctxp->temp_htab)
590 gimplify_ctxp->temp_htab = new hash_table<gimplify_hasher> (1000);
591 slot = gimplify_ctxp->temp_htab->find_slot (&elt, INSERT);
592 if (*slot == NULL)
594 elt_p = XNEW (elt_t);
595 elt_p->val = val;
596 elt_p->temp = ret = create_tmp_from_val (val);
597 *slot = elt_p;
599 else
601 elt_p = *slot;
602 ret = elt_p->temp;
606 return ret;
609 /* Helper for get_formal_tmp_var and get_initialized_tmp_var. */
611 static tree
612 internal_get_tmp_var (tree val, gimple_seq *pre_p, gimple_seq *post_p,
613 bool is_formal, bool allow_ssa)
615 tree t, mod;
617 /* Notice that we explicitly allow VAL to be a CALL_EXPR so that we
618 can create an INIT_EXPR and convert it into a GIMPLE_CALL below. */
619 gimplify_expr (&val, pre_p, post_p, is_gimple_reg_rhs_or_call,
620 fb_rvalue);
622 if (allow_ssa
623 && gimplify_ctxp->into_ssa
624 && is_gimple_reg_type (TREE_TYPE (val)))
626 t = make_ssa_name (TYPE_MAIN_VARIANT (TREE_TYPE (val)));
627 if (! gimple_in_ssa_p (cfun))
629 const char *name = get_name (val);
630 if (name)
631 SET_SSA_NAME_VAR_OR_IDENTIFIER (t, create_tmp_var_name (name));
634 else
635 t = lookup_tmp_var (val, is_formal);
637 mod = build2 (INIT_EXPR, TREE_TYPE (t), t, unshare_expr (val));
639 SET_EXPR_LOCATION (mod, EXPR_LOC_OR_LOC (val, input_location));
641 /* gimplify_modify_expr might want to reduce this further. */
642 gimplify_and_add (mod, pre_p);
643 ggc_free (mod);
645 return t;
648 /* Return a formal temporary variable initialized with VAL. PRE_P is as
649 in gimplify_expr. Only use this function if:
651 1) The value of the unfactored expression represented by VAL will not
652 change between the initialization and use of the temporary, and
653 2) The temporary will not be otherwise modified.
655 For instance, #1 means that this is inappropriate for SAVE_EXPR temps,
656 and #2 means it is inappropriate for && temps.
658 For other cases, use get_initialized_tmp_var instead. */
660 tree
661 get_formal_tmp_var (tree val, gimple_seq *pre_p)
663 return internal_get_tmp_var (val, pre_p, NULL, true, true);
666 /* Return a temporary variable initialized with VAL. PRE_P and POST_P
667 are as in gimplify_expr. */
669 tree
670 get_initialized_tmp_var (tree val, gimple_seq *pre_p,
671 gimple_seq *post_p /* = NULL */,
672 bool allow_ssa /* = true */)
674 return internal_get_tmp_var (val, pre_p, post_p, false, allow_ssa);
677 /* Declare all the variables in VARS in SCOPE. If DEBUG_INFO is true,
678 generate debug info for them; otherwise don't. */
680 void
681 declare_vars (tree vars, gimple *gs, bool debug_info)
683 tree last = vars;
684 if (last)
686 tree temps, block;
688 gbind *scope = as_a <gbind *> (gs);
690 temps = nreverse (last);
692 block = gimple_bind_block (scope);
693 gcc_assert (!block || TREE_CODE (block) == BLOCK);
694 if (!block || !debug_info)
696 DECL_CHAIN (last) = gimple_bind_vars (scope);
697 gimple_bind_set_vars (scope, temps);
699 else
701 /* We need to attach the nodes both to the BIND_EXPR and to its
702 associated BLOCK for debugging purposes. The key point here
703 is that the BLOCK_VARS of the BIND_EXPR_BLOCK of a BIND_EXPR
704 is a subchain of the BIND_EXPR_VARS of the BIND_EXPR. */
705 if (BLOCK_VARS (block))
706 BLOCK_VARS (block) = chainon (BLOCK_VARS (block), temps);
707 else
709 gimple_bind_set_vars (scope,
710 chainon (gimple_bind_vars (scope), temps));
711 BLOCK_VARS (block) = temps;
717 /* For VAR a VAR_DECL of variable size, try to find a constant upper bound
718 for the size and adjust DECL_SIZE/DECL_SIZE_UNIT accordingly. Abort if
719 no such upper bound can be obtained. */
721 static void
722 force_constant_size (tree var)
724 /* The only attempt we make is by querying the maximum size of objects
725 of the variable's type. */
727 HOST_WIDE_INT max_size;
729 gcc_assert (VAR_P (var));
731 max_size = max_int_size_in_bytes (TREE_TYPE (var));
733 gcc_assert (max_size >= 0);
735 DECL_SIZE_UNIT (var)
736 = build_int_cst (TREE_TYPE (DECL_SIZE_UNIT (var)), max_size);
737 DECL_SIZE (var)
738 = build_int_cst (TREE_TYPE (DECL_SIZE (var)), max_size * BITS_PER_UNIT);
741 /* Push the temporary variable TMP into the current binding. */
743 void
744 gimple_add_tmp_var_fn (struct function *fn, tree tmp)
746 gcc_assert (!DECL_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
748 /* Later processing assumes that the object size is constant, which might
749 not be true at this point. Force the use of a constant upper bound in
750 this case. */
751 if (!tree_fits_poly_uint64_p (DECL_SIZE_UNIT (tmp)))
752 force_constant_size (tmp);
754 DECL_CONTEXT (tmp) = fn->decl;
755 DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
757 record_vars_into (tmp, fn->decl);
760 /* Push the temporary variable TMP into the current binding. */
762 void
763 gimple_add_tmp_var (tree tmp)
765 gcc_assert (!DECL_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
767 /* Later processing assumes that the object size is constant, which might
768 not be true at this point. Force the use of a constant upper bound in
769 this case. */
770 if (!tree_fits_poly_uint64_p (DECL_SIZE_UNIT (tmp)))
771 force_constant_size (tmp);
773 DECL_CONTEXT (tmp) = current_function_decl;
774 DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
776 if (gimplify_ctxp)
778 DECL_CHAIN (tmp) = gimplify_ctxp->temps;
779 gimplify_ctxp->temps = tmp;
781 /* Mark temporaries local within the nearest enclosing parallel. */
782 if (gimplify_omp_ctxp)
784 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
785 int flag = GOVD_LOCAL | GOVD_SEEN;
786 while (ctx
787 && (ctx->region_type == ORT_WORKSHARE
788 || ctx->region_type == ORT_TASKGROUP
789 || ctx->region_type == ORT_SIMD
790 || ctx->region_type == ORT_ACC))
792 if (ctx->region_type == ORT_SIMD
793 && TREE_ADDRESSABLE (tmp)
794 && !TREE_STATIC (tmp))
796 if (TREE_CODE (DECL_SIZE_UNIT (tmp)) != INTEGER_CST)
797 ctx->add_safelen1 = true;
798 else if (ctx->in_for_exprs)
799 flag = GOVD_PRIVATE;
800 else
801 flag = GOVD_PRIVATE | GOVD_SEEN;
802 break;
804 ctx = ctx->outer_context;
806 if (ctx)
807 omp_add_variable (ctx, tmp, flag);
810 else if (cfun)
811 record_vars (tmp);
812 else
814 gimple_seq body_seq;
816 /* This case is for nested functions. We need to expose the locals
817 they create. */
818 body_seq = gimple_body (current_function_decl);
819 declare_vars (tmp, gimple_seq_first_stmt (body_seq), false);
825 /* This page contains routines to unshare tree nodes, i.e. to duplicate tree
826 nodes that are referenced more than once in GENERIC functions. This is
827 necessary because gimplification (translation into GIMPLE) is performed
828 by modifying tree nodes in-place, so gimplication of a shared node in a
829 first context could generate an invalid GIMPLE form in a second context.
831 This is achieved with a simple mark/copy/unmark algorithm that walks the
832 GENERIC representation top-down, marks nodes with TREE_VISITED the first
833 time it encounters them, duplicates them if they already have TREE_VISITED
834 set, and finally removes the TREE_VISITED marks it has set.
836 The algorithm works only at the function level, i.e. it generates a GENERIC
837 representation of a function with no nodes shared within the function when
838 passed a GENERIC function (except for nodes that are allowed to be shared).
840 At the global level, it is also necessary to unshare tree nodes that are
841 referenced in more than one function, for the same aforementioned reason.
842 This requires some cooperation from the front-end. There are 2 strategies:
844 1. Manual unsharing. The front-end needs to call unshare_expr on every
845 expression that might end up being shared across functions.
847 2. Deep unsharing. This is an extension of regular unsharing. Instead
848 of calling unshare_expr on expressions that might be shared across
849 functions, the front-end pre-marks them with TREE_VISITED. This will
850 ensure that they are unshared on the first reference within functions
851 when the regular unsharing algorithm runs. The counterpart is that
852 this algorithm must look deeper than for manual unsharing, which is
853 specified by LANG_HOOKS_DEEP_UNSHARING.
855 If there are only few specific cases of node sharing across functions, it is
856 probably easier for a front-end to unshare the expressions manually. On the
857 contrary, if the expressions generated at the global level are as widespread
858 as expressions generated within functions, deep unsharing is very likely the
859 way to go. */
861 /* Similar to copy_tree_r but do not copy SAVE_EXPR or TARGET_EXPR nodes.
862 These nodes model computations that must be done once. If we were to
863 unshare something like SAVE_EXPR(i++), the gimplification process would
864 create wrong code. However, if DATA is non-null, it must hold a pointer
865 set that is used to unshare the subtrees of these nodes. */
867 static tree
868 mostly_copy_tree_r (tree *tp, int *walk_subtrees, void *data)
870 tree t = *tp;
871 enum tree_code code = TREE_CODE (t);
873 /* Do not copy SAVE_EXPR, TARGET_EXPR or BIND_EXPR nodes themselves, but
874 copy their subtrees if we can make sure to do it only once. */
875 if (code == SAVE_EXPR || code == TARGET_EXPR || code == BIND_EXPR)
877 if (data && !((hash_set<tree> *)data)->add (t))
879 else
880 *walk_subtrees = 0;
883 /* Stop at types, decls, constants like copy_tree_r. */
884 else if (TREE_CODE_CLASS (code) == tcc_type
885 || TREE_CODE_CLASS (code) == tcc_declaration
886 || TREE_CODE_CLASS (code) == tcc_constant)
887 *walk_subtrees = 0;
889 /* Cope with the statement expression extension. */
890 else if (code == STATEMENT_LIST)
893 /* Leave the bulk of the work to copy_tree_r itself. */
894 else
895 copy_tree_r (tp, walk_subtrees, NULL);
897 return NULL_TREE;
900 /* Callback for walk_tree to unshare most of the shared trees rooted at *TP.
901 If *TP has been visited already, then *TP is deeply copied by calling
902 mostly_copy_tree_r. DATA is passed to mostly_copy_tree_r unmodified. */
904 static tree
905 copy_if_shared_r (tree *tp, int *walk_subtrees, void *data)
907 tree t = *tp;
908 enum tree_code code = TREE_CODE (t);
910 /* Skip types, decls, and constants. But we do want to look at their
911 types and the bounds of types. Mark them as visited so we properly
912 unmark their subtrees on the unmark pass. If we've already seen them,
913 don't look down further. */
914 if (TREE_CODE_CLASS (code) == tcc_type
915 || TREE_CODE_CLASS (code) == tcc_declaration
916 || TREE_CODE_CLASS (code) == tcc_constant)
918 if (TREE_VISITED (t))
919 *walk_subtrees = 0;
920 else
921 TREE_VISITED (t) = 1;
924 /* If this node has been visited already, unshare it and don't look
925 any deeper. */
926 else if (TREE_VISITED (t))
928 walk_tree (tp, mostly_copy_tree_r, data, NULL);
929 *walk_subtrees = 0;
932 /* Otherwise, mark the node as visited and keep looking. */
933 else
934 TREE_VISITED (t) = 1;
936 return NULL_TREE;
939 /* Unshare most of the shared trees rooted at *TP. DATA is passed to the
940 copy_if_shared_r callback unmodified. */
942 void
943 copy_if_shared (tree *tp, void *data)
945 walk_tree (tp, copy_if_shared_r, data, NULL);
948 /* Unshare all the trees in the body of FNDECL, as well as in the bodies of
949 any nested functions. */
951 static void
952 unshare_body (tree fndecl)
954 struct cgraph_node *cgn = cgraph_node::get (fndecl);
955 /* If the language requires deep unsharing, we need a pointer set to make
956 sure we don't repeatedly unshare subtrees of unshareable nodes. */
957 hash_set<tree> *visited
958 = lang_hooks.deep_unsharing ? new hash_set<tree> : NULL;
960 copy_if_shared (&DECL_SAVED_TREE (fndecl), visited);
961 copy_if_shared (&DECL_SIZE (DECL_RESULT (fndecl)), visited);
962 copy_if_shared (&DECL_SIZE_UNIT (DECL_RESULT (fndecl)), visited);
964 delete visited;
966 if (cgn)
967 for (cgn = first_nested_function (cgn); cgn;
968 cgn = next_nested_function (cgn))
969 unshare_body (cgn->decl);
972 /* Callback for walk_tree to unmark the visited trees rooted at *TP.
973 Subtrees are walked until the first unvisited node is encountered. */
975 static tree
976 unmark_visited_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
978 tree t = *tp;
980 /* If this node has been visited, unmark it and keep looking. */
981 if (TREE_VISITED (t))
982 TREE_VISITED (t) = 0;
984 /* Otherwise, don't look any deeper. */
985 else
986 *walk_subtrees = 0;
988 return NULL_TREE;
991 /* Unmark the visited trees rooted at *TP. */
993 static inline void
994 unmark_visited (tree *tp)
996 walk_tree (tp, unmark_visited_r, NULL, NULL);
999 /* Likewise, but mark all trees as not visited. */
1001 static void
1002 unvisit_body (tree fndecl)
1004 struct cgraph_node *cgn = cgraph_node::get (fndecl);
1006 unmark_visited (&DECL_SAVED_TREE (fndecl));
1007 unmark_visited (&DECL_SIZE (DECL_RESULT (fndecl)));
1008 unmark_visited (&DECL_SIZE_UNIT (DECL_RESULT (fndecl)));
1010 if (cgn)
1011 for (cgn = first_nested_function (cgn);
1012 cgn; cgn = next_nested_function (cgn))
1013 unvisit_body (cgn->decl);
1016 /* Unconditionally make an unshared copy of EXPR. This is used when using
1017 stored expressions which span multiple functions, such as BINFO_VTABLE,
1018 as the normal unsharing process can't tell that they're shared. */
1020 tree
1021 unshare_expr (tree expr)
1023 walk_tree (&expr, mostly_copy_tree_r, NULL, NULL);
1024 return expr;
1027 /* Worker for unshare_expr_without_location. */
1029 static tree
1030 prune_expr_location (tree *tp, int *walk_subtrees, void *)
1032 if (EXPR_P (*tp))
1033 SET_EXPR_LOCATION (*tp, UNKNOWN_LOCATION);
1034 else
1035 *walk_subtrees = 0;
1036 return NULL_TREE;
1039 /* Similar to unshare_expr but also prune all expression locations
1040 from EXPR. */
1042 tree
1043 unshare_expr_without_location (tree expr)
1045 walk_tree (&expr, mostly_copy_tree_r, NULL, NULL);
1046 if (EXPR_P (expr))
1047 walk_tree (&expr, prune_expr_location, NULL, NULL);
1048 return expr;
1051 /* Return the EXPR_LOCATION of EXPR, if it (maybe recursively) has
1052 one, OR_ELSE otherwise. The location of a STATEMENT_LISTs
1053 comprising at least one DEBUG_BEGIN_STMT followed by exactly one
1054 EXPR is the location of the EXPR. */
1056 static location_t
1057 rexpr_location (tree expr, location_t or_else = UNKNOWN_LOCATION)
1059 if (!expr)
1060 return or_else;
1062 if (EXPR_HAS_LOCATION (expr))
1063 return EXPR_LOCATION (expr);
1065 if (TREE_CODE (expr) != STATEMENT_LIST)
1066 return or_else;
1068 tree_stmt_iterator i = tsi_start (expr);
1070 bool found = false;
1071 while (!tsi_end_p (i) && TREE_CODE (tsi_stmt (i)) == DEBUG_BEGIN_STMT)
1073 found = true;
1074 tsi_next (&i);
1077 if (!found || !tsi_one_before_end_p (i))
1078 return or_else;
1080 return rexpr_location (tsi_stmt (i), or_else);
1083 /* Return TRUE iff EXPR (maybe recursively) has a location; see
1084 rexpr_location for the potential recursion. */
1086 static inline bool
1087 rexpr_has_location (tree expr)
1089 return rexpr_location (expr) != UNKNOWN_LOCATION;
1093 /* WRAPPER is a code such as BIND_EXPR or CLEANUP_POINT_EXPR which can both
1094 contain statements and have a value. Assign its value to a temporary
1095 and give it void_type_node. Return the temporary, or NULL_TREE if
1096 WRAPPER was already void. */
1098 tree
1099 voidify_wrapper_expr (tree wrapper, tree temp)
1101 tree type = TREE_TYPE (wrapper);
1102 if (type && !VOID_TYPE_P (type))
1104 tree *p;
1106 /* Set p to point to the body of the wrapper. Loop until we find
1107 something that isn't a wrapper. */
1108 for (p = &wrapper; p && *p; )
1110 switch (TREE_CODE (*p))
1112 case BIND_EXPR:
1113 TREE_SIDE_EFFECTS (*p) = 1;
1114 TREE_TYPE (*p) = void_type_node;
1115 /* For a BIND_EXPR, the body is operand 1. */
1116 p = &BIND_EXPR_BODY (*p);
1117 break;
1119 case CLEANUP_POINT_EXPR:
1120 case TRY_FINALLY_EXPR:
1121 case TRY_CATCH_EXPR:
1122 TREE_SIDE_EFFECTS (*p) = 1;
1123 TREE_TYPE (*p) = void_type_node;
1124 p = &TREE_OPERAND (*p, 0);
1125 break;
1127 case STATEMENT_LIST:
1129 tree_stmt_iterator i = tsi_last (*p);
1130 TREE_SIDE_EFFECTS (*p) = 1;
1131 TREE_TYPE (*p) = void_type_node;
1132 p = tsi_end_p (i) ? NULL : tsi_stmt_ptr (i);
1134 break;
1136 case COMPOUND_EXPR:
1137 /* Advance to the last statement. Set all container types to
1138 void. */
1139 for (; TREE_CODE (*p) == COMPOUND_EXPR; p = &TREE_OPERAND (*p, 1))
1141 TREE_SIDE_EFFECTS (*p) = 1;
1142 TREE_TYPE (*p) = void_type_node;
1144 break;
1146 case TRANSACTION_EXPR:
1147 TREE_SIDE_EFFECTS (*p) = 1;
1148 TREE_TYPE (*p) = void_type_node;
1149 p = &TRANSACTION_EXPR_BODY (*p);
1150 break;
1152 default:
1153 /* Assume that any tree upon which voidify_wrapper_expr is
1154 directly called is a wrapper, and that its body is op0. */
1155 if (p == &wrapper)
1157 TREE_SIDE_EFFECTS (*p) = 1;
1158 TREE_TYPE (*p) = void_type_node;
1159 p = &TREE_OPERAND (*p, 0);
1160 break;
1162 goto out;
1166 out:
1167 if (p == NULL || IS_EMPTY_STMT (*p))
1168 temp = NULL_TREE;
1169 else if (temp)
1171 /* The wrapper is on the RHS of an assignment that we're pushing
1172 down. */
1173 gcc_assert (TREE_CODE (temp) == INIT_EXPR
1174 || TREE_CODE (temp) == MODIFY_EXPR);
1175 TREE_OPERAND (temp, 1) = *p;
1176 *p = temp;
1178 else
1180 temp = create_tmp_var (type, "retval");
1181 *p = build2 (INIT_EXPR, type, temp, *p);
1184 return temp;
1187 return NULL_TREE;
1190 /* Prepare calls to builtins to SAVE and RESTORE the stack as well as
1191 a temporary through which they communicate. */
1193 static void
1194 build_stack_save_restore (gcall **save, gcall **restore)
1196 tree tmp_var;
1198 *save = gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_SAVE), 0);
1199 tmp_var = create_tmp_var (ptr_type_node, "saved_stack");
1200 gimple_call_set_lhs (*save, tmp_var);
1202 *restore
1203 = gimple_build_call (builtin_decl_implicit (BUILT_IN_STACK_RESTORE),
1204 1, tmp_var);
1207 /* Generate IFN_ASAN_MARK call that poisons shadow of a for DECL variable. */
1209 static tree
1210 build_asan_poison_call_expr (tree decl)
1212 /* Do not poison variables that have size equal to zero. */
1213 tree unit_size = DECL_SIZE_UNIT (decl);
1214 if (zerop (unit_size))
1215 return NULL_TREE;
1217 tree base = build_fold_addr_expr (decl);
1219 return build_call_expr_internal_loc (UNKNOWN_LOCATION, IFN_ASAN_MARK,
1220 void_type_node, 3,
1221 build_int_cst (integer_type_node,
1222 ASAN_MARK_POISON),
1223 base, unit_size);
1226 /* Generate IFN_ASAN_MARK call that would poison or unpoison, depending
1227 on POISON flag, shadow memory of a DECL variable. The call will be
1228 put on location identified by IT iterator, where BEFORE flag drives
1229 position where the stmt will be put. */
1231 static void
1232 asan_poison_variable (tree decl, bool poison, gimple_stmt_iterator *it,
1233 bool before)
1235 tree unit_size = DECL_SIZE_UNIT (decl);
1236 tree base = build_fold_addr_expr (decl);
1238 /* Do not poison variables that have size equal to zero. */
1239 if (zerop (unit_size))
1240 return;
1242 /* It's necessary to have all stack variables aligned to ASAN granularity
1243 bytes. */
1244 gcc_assert (!hwasan_sanitize_p () || hwasan_sanitize_stack_p ());
1245 unsigned shadow_granularity
1246 = hwasan_sanitize_p () ? HWASAN_TAG_GRANULE_SIZE : ASAN_SHADOW_GRANULARITY;
1247 if (DECL_ALIGN_UNIT (decl) <= shadow_granularity)
1248 SET_DECL_ALIGN (decl, BITS_PER_UNIT * shadow_granularity);
1250 HOST_WIDE_INT flags = poison ? ASAN_MARK_POISON : ASAN_MARK_UNPOISON;
1252 gimple *g
1253 = gimple_build_call_internal (IFN_ASAN_MARK, 3,
1254 build_int_cst (integer_type_node, flags),
1255 base, unit_size);
1257 if (before)
1258 gsi_insert_before (it, g, GSI_NEW_STMT);
1259 else
1260 gsi_insert_after (it, g, GSI_NEW_STMT);
1263 /* Generate IFN_ASAN_MARK internal call that depending on POISON flag
1264 either poisons or unpoisons a DECL. Created statement is appended
1265 to SEQ_P gimple sequence. */
1267 static void
1268 asan_poison_variable (tree decl, bool poison, gimple_seq *seq_p)
1270 gimple_stmt_iterator it = gsi_last (*seq_p);
1271 bool before = false;
1273 if (gsi_end_p (it))
1274 before = true;
1276 asan_poison_variable (decl, poison, &it, before);
1279 /* Sort pair of VAR_DECLs A and B by DECL_UID. */
1281 static int
1282 sort_by_decl_uid (const void *a, const void *b)
1284 const tree *t1 = (const tree *)a;
1285 const tree *t2 = (const tree *)b;
1287 int uid1 = DECL_UID (*t1);
1288 int uid2 = DECL_UID (*t2);
1290 if (uid1 < uid2)
1291 return -1;
1292 else if (uid1 > uid2)
1293 return 1;
1294 else
1295 return 0;
1298 /* Generate IFN_ASAN_MARK internal call for all VARIABLES
1299 depending on POISON flag. Created statement is appended
1300 to SEQ_P gimple sequence. */
1302 static void
1303 asan_poison_variables (hash_set<tree> *variables, bool poison, gimple_seq *seq_p)
1305 unsigned c = variables->elements ();
1306 if (c == 0)
1307 return;
1309 auto_vec<tree> sorted_variables (c);
1311 for (hash_set<tree>::iterator it = variables->begin ();
1312 it != variables->end (); ++it)
1313 sorted_variables.safe_push (*it);
1315 sorted_variables.qsort (sort_by_decl_uid);
1317 unsigned i;
1318 tree var;
1319 FOR_EACH_VEC_ELT (sorted_variables, i, var)
1321 asan_poison_variable (var, poison, seq_p);
1323 /* Add use_after_scope_memory attribute for the variable in order
1324 to prevent re-written into SSA. */
1325 if (!lookup_attribute (ASAN_USE_AFTER_SCOPE_ATTRIBUTE,
1326 DECL_ATTRIBUTES (var)))
1327 DECL_ATTRIBUTES (var)
1328 = tree_cons (get_identifier (ASAN_USE_AFTER_SCOPE_ATTRIBUTE),
1329 integer_one_node,
1330 DECL_ATTRIBUTES (var));
1334 /* Gimplify a BIND_EXPR. Just voidify and recurse. */
1336 static enum gimplify_status
1337 gimplify_bind_expr (tree *expr_p, gimple_seq *pre_p)
1339 tree bind_expr = *expr_p;
1340 bool old_keep_stack = gimplify_ctxp->keep_stack;
1341 bool old_save_stack = gimplify_ctxp->save_stack;
1342 tree t;
1343 gbind *bind_stmt;
1344 gimple_seq body, cleanup;
1345 gcall *stack_save;
1346 location_t start_locus = 0, end_locus = 0;
1347 tree ret_clauses = NULL;
1349 tree temp = voidify_wrapper_expr (bind_expr, NULL);
1351 /* Mark variables seen in this bind expr. */
1352 for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
1354 if (VAR_P (t))
1356 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
1358 /* Mark variable as local. */
1359 if (ctx && ctx->region_type != ORT_NONE && !DECL_EXTERNAL (t))
1361 if (! DECL_SEEN_IN_BIND_EXPR_P (t)
1362 || splay_tree_lookup (ctx->variables,
1363 (splay_tree_key) t) == NULL)
1365 int flag = GOVD_LOCAL;
1366 if (ctx->region_type == ORT_SIMD
1367 && TREE_ADDRESSABLE (t)
1368 && !TREE_STATIC (t))
1370 if (TREE_CODE (DECL_SIZE_UNIT (t)) != INTEGER_CST)
1371 ctx->add_safelen1 = true;
1372 else
1373 flag = GOVD_PRIVATE;
1375 omp_add_variable (ctx, t, flag | GOVD_SEEN);
1377 /* Static locals inside of target construct or offloaded
1378 routines need to be "omp declare target". */
1379 if (TREE_STATIC (t))
1380 for (; ctx; ctx = ctx->outer_context)
1381 if ((ctx->region_type & ORT_TARGET) != 0)
1383 if (!lookup_attribute ("omp declare target",
1384 DECL_ATTRIBUTES (t)))
1386 tree id = get_identifier ("omp declare target");
1387 DECL_ATTRIBUTES (t)
1388 = tree_cons (id, NULL_TREE, DECL_ATTRIBUTES (t));
1389 varpool_node *node = varpool_node::get (t);
1390 if (node)
1392 node->offloadable = 1;
1393 if (ENABLE_OFFLOADING && !DECL_EXTERNAL (t))
1395 g->have_offload = true;
1396 if (!in_lto_p)
1397 vec_safe_push (offload_vars, t);
1401 break;
1405 DECL_SEEN_IN_BIND_EXPR_P (t) = 1;
1407 if (DECL_HARD_REGISTER (t) && !is_global_var (t) && cfun)
1408 cfun->has_local_explicit_reg_vars = true;
1412 bind_stmt = gimple_build_bind (BIND_EXPR_VARS (bind_expr), NULL,
1413 BIND_EXPR_BLOCK (bind_expr));
1414 gimple_push_bind_expr (bind_stmt);
1416 gimplify_ctxp->keep_stack = false;
1417 gimplify_ctxp->save_stack = false;
1419 /* Gimplify the body into the GIMPLE_BIND tuple's body. */
1420 body = NULL;
1421 gimplify_stmt (&BIND_EXPR_BODY (bind_expr), &body);
1422 gimple_bind_set_body (bind_stmt, body);
1424 /* Source location wise, the cleanup code (stack_restore and clobbers)
1425 belongs to the end of the block, so propagate what we have. The
1426 stack_save operation belongs to the beginning of block, which we can
1427 infer from the bind_expr directly if the block has no explicit
1428 assignment. */
1429 if (BIND_EXPR_BLOCK (bind_expr))
1431 end_locus = BLOCK_SOURCE_END_LOCATION (BIND_EXPR_BLOCK (bind_expr));
1432 start_locus = BLOCK_SOURCE_LOCATION (BIND_EXPR_BLOCK (bind_expr));
1434 if (start_locus == 0)
1435 start_locus = EXPR_LOCATION (bind_expr);
1437 cleanup = NULL;
1438 stack_save = NULL;
1440 /* If the code both contains VLAs and calls alloca, then we cannot reclaim
1441 the stack space allocated to the VLAs. */
1442 if (gimplify_ctxp->save_stack && !gimplify_ctxp->keep_stack)
1444 gcall *stack_restore;
1446 /* Save stack on entry and restore it on exit. Add a try_finally
1447 block to achieve this. */
1448 build_stack_save_restore (&stack_save, &stack_restore);
1450 gimple_set_location (stack_save, start_locus);
1451 gimple_set_location (stack_restore, end_locus);
1453 gimplify_seq_add_stmt (&cleanup, stack_restore);
1456 /* Add clobbers for all variables that go out of scope. */
1457 for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
1459 if (VAR_P (t)
1460 && !is_global_var (t)
1461 && DECL_CONTEXT (t) == current_function_decl)
1463 if (!DECL_HARD_REGISTER (t)
1464 && !TREE_THIS_VOLATILE (t)
1465 && !DECL_HAS_VALUE_EXPR_P (t)
1466 /* Only care for variables that have to be in memory. Others
1467 will be rewritten into SSA names, hence moved to the
1468 top-level. */
1469 && !is_gimple_reg (t)
1470 && flag_stack_reuse != SR_NONE)
1472 tree clobber = build_clobber (TREE_TYPE (t));
1473 gimple *clobber_stmt;
1474 clobber_stmt = gimple_build_assign (t, clobber);
1475 gimple_set_location (clobber_stmt, end_locus);
1476 gimplify_seq_add_stmt (&cleanup, clobber_stmt);
1479 if (flag_openacc && oacc_declare_returns != NULL)
1481 tree key = t;
1482 if (DECL_HAS_VALUE_EXPR_P (key))
1484 key = DECL_VALUE_EXPR (key);
1485 if (TREE_CODE (key) == INDIRECT_REF)
1486 key = TREE_OPERAND (key, 0);
1488 tree *c = oacc_declare_returns->get (key);
1489 if (c != NULL)
1491 if (ret_clauses)
1492 OMP_CLAUSE_CHAIN (*c) = ret_clauses;
1494 ret_clauses = unshare_expr (*c);
1496 oacc_declare_returns->remove (key);
1498 if (oacc_declare_returns->is_empty ())
1500 delete oacc_declare_returns;
1501 oacc_declare_returns = NULL;
1507 if (asan_poisoned_variables != NULL
1508 && asan_poisoned_variables->contains (t))
1510 asan_poisoned_variables->remove (t);
1511 asan_poison_variable (t, true, &cleanup);
1514 if (gimplify_ctxp->live_switch_vars != NULL
1515 && gimplify_ctxp->live_switch_vars->contains (t))
1516 gimplify_ctxp->live_switch_vars->remove (t);
1519 if (ret_clauses)
1521 gomp_target *stmt;
1522 gimple_stmt_iterator si = gsi_start (cleanup);
1524 stmt = gimple_build_omp_target (NULL, GF_OMP_TARGET_KIND_OACC_DECLARE,
1525 ret_clauses);
1526 gsi_insert_seq_before_without_update (&si, stmt, GSI_NEW_STMT);
1529 if (cleanup)
1531 gtry *gs;
1532 gimple_seq new_body;
1534 new_body = NULL;
1535 gs = gimple_build_try (gimple_bind_body (bind_stmt), cleanup,
1536 GIMPLE_TRY_FINALLY);
1538 if (stack_save)
1539 gimplify_seq_add_stmt (&new_body, stack_save);
1540 gimplify_seq_add_stmt (&new_body, gs);
1541 gimple_bind_set_body (bind_stmt, new_body);
1544 /* keep_stack propagates all the way up to the outermost BIND_EXPR. */
1545 if (!gimplify_ctxp->keep_stack)
1546 gimplify_ctxp->keep_stack = old_keep_stack;
1547 gimplify_ctxp->save_stack = old_save_stack;
1549 gimple_pop_bind_expr ();
1551 gimplify_seq_add_stmt (pre_p, bind_stmt);
1553 if (temp)
1555 *expr_p = temp;
1556 return GS_OK;
1559 *expr_p = NULL_TREE;
1560 return GS_ALL_DONE;
1563 /* Maybe add early return predict statement to PRE_P sequence. */
1565 static void
1566 maybe_add_early_return_predict_stmt (gimple_seq *pre_p)
1568 /* If we are not in a conditional context, add PREDICT statement. */
1569 if (gimple_conditional_context ())
1571 gimple *predict = gimple_build_predict (PRED_TREE_EARLY_RETURN,
1572 NOT_TAKEN);
1573 gimplify_seq_add_stmt (pre_p, predict);
1577 /* Gimplify a RETURN_EXPR. If the expression to be returned is not a
1578 GIMPLE value, it is assigned to a new temporary and the statement is
1579 re-written to return the temporary.
1581 PRE_P points to the sequence where side effects that must happen before
1582 STMT should be stored. */
1584 static enum gimplify_status
1585 gimplify_return_expr (tree stmt, gimple_seq *pre_p)
1587 greturn *ret;
1588 tree ret_expr = TREE_OPERAND (stmt, 0);
1589 tree result_decl, result;
1591 if (ret_expr == error_mark_node)
1592 return GS_ERROR;
1594 if (!ret_expr
1595 || TREE_CODE (ret_expr) == RESULT_DECL)
1597 maybe_add_early_return_predict_stmt (pre_p);
1598 greturn *ret = gimple_build_return (ret_expr);
1599 gimple_set_no_warning (ret, TREE_NO_WARNING (stmt));
1600 gimplify_seq_add_stmt (pre_p, ret);
1601 return GS_ALL_DONE;
1604 if (VOID_TYPE_P (TREE_TYPE (TREE_TYPE (current_function_decl))))
1605 result_decl = NULL_TREE;
1606 else if (TREE_CODE (ret_expr) == COMPOUND_EXPR)
1608 /* Used in C++ for handling EH cleanup of the return value if a local
1609 cleanup throws. Assume the front-end knows what it's doing. */
1610 result_decl = DECL_RESULT (current_function_decl);
1611 /* But crash if we end up trying to modify ret_expr below. */
1612 ret_expr = NULL_TREE;
1614 else
1616 result_decl = TREE_OPERAND (ret_expr, 0);
1618 /* See through a return by reference. */
1619 if (TREE_CODE (result_decl) == INDIRECT_REF)
1620 result_decl = TREE_OPERAND (result_decl, 0);
1622 gcc_assert ((TREE_CODE (ret_expr) == MODIFY_EXPR
1623 || TREE_CODE (ret_expr) == INIT_EXPR)
1624 && TREE_CODE (result_decl) == RESULT_DECL);
1627 /* If aggregate_value_p is true, then we can return the bare RESULT_DECL.
1628 Recall that aggregate_value_p is FALSE for any aggregate type that is
1629 returned in registers. If we're returning values in registers, then
1630 we don't want to extend the lifetime of the RESULT_DECL, particularly
1631 across another call. In addition, for those aggregates for which
1632 hard_function_value generates a PARALLEL, we'll die during normal
1633 expansion of structure assignments; there's special code in expand_return
1634 to handle this case that does not exist in expand_expr. */
1635 if (!result_decl)
1636 result = NULL_TREE;
1637 else if (aggregate_value_p (result_decl, TREE_TYPE (current_function_decl)))
1639 if (!poly_int_tree_p (DECL_SIZE (result_decl)))
1641 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (result_decl)))
1642 gimplify_type_sizes (TREE_TYPE (result_decl), pre_p);
1643 /* Note that we don't use gimplify_vla_decl because the RESULT_DECL
1644 should be effectively allocated by the caller, i.e. all calls to
1645 this function must be subject to the Return Slot Optimization. */
1646 gimplify_one_sizepos (&DECL_SIZE (result_decl), pre_p);
1647 gimplify_one_sizepos (&DECL_SIZE_UNIT (result_decl), pre_p);
1649 result = result_decl;
1651 else if (gimplify_ctxp->return_temp)
1652 result = gimplify_ctxp->return_temp;
1653 else
1655 result = create_tmp_reg (TREE_TYPE (result_decl));
1657 /* ??? With complex control flow (usually involving abnormal edges),
1658 we can wind up warning about an uninitialized value for this. Due
1659 to how this variable is constructed and initialized, this is never
1660 true. Give up and never warn. */
1661 TREE_NO_WARNING (result) = 1;
1663 gimplify_ctxp->return_temp = result;
1666 /* Smash the lhs of the MODIFY_EXPR to the temporary we plan to use.
1667 Then gimplify the whole thing. */
1668 if (result != result_decl)
1669 TREE_OPERAND (ret_expr, 0) = result;
1671 gimplify_and_add (TREE_OPERAND (stmt, 0), pre_p);
1673 maybe_add_early_return_predict_stmt (pre_p);
1674 ret = gimple_build_return (result);
1675 gimple_set_no_warning (ret, TREE_NO_WARNING (stmt));
1676 gimplify_seq_add_stmt (pre_p, ret);
1678 return GS_ALL_DONE;
1681 /* Gimplify a variable-length array DECL. */
1683 static void
1684 gimplify_vla_decl (tree decl, gimple_seq *seq_p)
1686 /* This is a variable-sized decl. Simplify its size and mark it
1687 for deferred expansion. */
1688 tree t, addr, ptr_type;
1690 gimplify_one_sizepos (&DECL_SIZE (decl), seq_p);
1691 gimplify_one_sizepos (&DECL_SIZE_UNIT (decl), seq_p);
1693 /* Don't mess with a DECL_VALUE_EXPR set by the front-end. */
1694 if (DECL_HAS_VALUE_EXPR_P (decl))
1695 return;
1697 /* All occurrences of this decl in final gimplified code will be
1698 replaced by indirection. Setting DECL_VALUE_EXPR does two
1699 things: First, it lets the rest of the gimplifier know what
1700 replacement to use. Second, it lets the debug info know
1701 where to find the value. */
1702 ptr_type = build_pointer_type (TREE_TYPE (decl));
1703 addr = create_tmp_var (ptr_type, get_name (decl));
1704 DECL_IGNORED_P (addr) = 0;
1705 t = build_fold_indirect_ref (addr);
1706 TREE_THIS_NOTRAP (t) = 1;
1707 SET_DECL_VALUE_EXPR (decl, t);
1708 DECL_HAS_VALUE_EXPR_P (decl) = 1;
1710 t = build_alloca_call_expr (DECL_SIZE_UNIT (decl), DECL_ALIGN (decl),
1711 max_int_size_in_bytes (TREE_TYPE (decl)));
1712 /* The call has been built for a variable-sized object. */
1713 CALL_ALLOCA_FOR_VAR_P (t) = 1;
1714 t = fold_convert (ptr_type, t);
1715 t = build2 (MODIFY_EXPR, TREE_TYPE (addr), addr, t);
1717 gimplify_and_add (t, seq_p);
1719 /* Record the dynamic allocation associated with DECL if requested. */
1720 if (flag_callgraph_info & CALLGRAPH_INFO_DYNAMIC_ALLOC)
1721 record_dynamic_alloc (decl);
1724 /* A helper function to be called via walk_tree. Mark all labels under *TP
1725 as being forced. To be called for DECL_INITIAL of static variables. */
1727 static tree
1728 force_labels_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
1730 if (TYPE_P (*tp))
1731 *walk_subtrees = 0;
1732 if (TREE_CODE (*tp) == LABEL_DECL)
1734 FORCED_LABEL (*tp) = 1;
1735 cfun->has_forced_label_in_static = 1;
1738 return NULL_TREE;
1741 /* Gimplify a DECL_EXPR node *STMT_P by making any necessary allocation
1742 and initialization explicit. */
1744 static enum gimplify_status
1745 gimplify_decl_expr (tree *stmt_p, gimple_seq *seq_p)
1747 tree stmt = *stmt_p;
1748 tree decl = DECL_EXPR_DECL (stmt);
1750 *stmt_p = NULL_TREE;
1752 if (TREE_TYPE (decl) == error_mark_node)
1753 return GS_ERROR;
1755 if ((TREE_CODE (decl) == TYPE_DECL
1756 || VAR_P (decl))
1757 && !TYPE_SIZES_GIMPLIFIED (TREE_TYPE (decl)))
1759 gimplify_type_sizes (TREE_TYPE (decl), seq_p);
1760 if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE)
1761 gimplify_type_sizes (TREE_TYPE (TREE_TYPE (decl)), seq_p);
1764 /* ??? DECL_ORIGINAL_TYPE is streamed for LTO so it needs to be gimplified
1765 in case its size expressions contain problematic nodes like CALL_EXPR. */
1766 if (TREE_CODE (decl) == TYPE_DECL
1767 && DECL_ORIGINAL_TYPE (decl)
1768 && !TYPE_SIZES_GIMPLIFIED (DECL_ORIGINAL_TYPE (decl)))
1770 gimplify_type_sizes (DECL_ORIGINAL_TYPE (decl), seq_p);
1771 if (TREE_CODE (DECL_ORIGINAL_TYPE (decl)) == REFERENCE_TYPE)
1772 gimplify_type_sizes (TREE_TYPE (DECL_ORIGINAL_TYPE (decl)), seq_p);
1775 if (VAR_P (decl) && !DECL_EXTERNAL (decl))
1777 tree init = DECL_INITIAL (decl);
1778 bool is_vla = false;
1780 poly_uint64 size;
1781 if (!poly_int_tree_p (DECL_SIZE_UNIT (decl), &size)
1782 || (!TREE_STATIC (decl)
1783 && flag_stack_check == GENERIC_STACK_CHECK
1784 && maybe_gt (size,
1785 (unsigned HOST_WIDE_INT) STACK_CHECK_MAX_VAR_SIZE)))
1787 gimplify_vla_decl (decl, seq_p);
1788 is_vla = true;
1791 if (asan_poisoned_variables
1792 && !is_vla
1793 && TREE_ADDRESSABLE (decl)
1794 && !TREE_STATIC (decl)
1795 && !DECL_HAS_VALUE_EXPR_P (decl)
1796 && DECL_ALIGN (decl) <= MAX_SUPPORTED_STACK_ALIGNMENT
1797 && dbg_cnt (asan_use_after_scope)
1798 && !gimplify_omp_ctxp
1799 /* GNAT introduces temporaries to hold return values of calls in
1800 initializers of variables defined in other units, so the
1801 declaration of the variable is discarded completely. We do not
1802 want to issue poison calls for such dropped variables. */
1803 && (DECL_SEEN_IN_BIND_EXPR_P (decl)
1804 || (DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)))
1806 asan_poisoned_variables->add (decl);
1807 asan_poison_variable (decl, false, seq_p);
1808 if (!DECL_ARTIFICIAL (decl) && gimplify_ctxp->live_switch_vars)
1809 gimplify_ctxp->live_switch_vars->add (decl);
1812 /* Some front ends do not explicitly declare all anonymous
1813 artificial variables. We compensate here by declaring the
1814 variables, though it would be better if the front ends would
1815 explicitly declare them. */
1816 if (!DECL_SEEN_IN_BIND_EXPR_P (decl)
1817 && DECL_ARTIFICIAL (decl) && DECL_NAME (decl) == NULL_TREE)
1818 gimple_add_tmp_var (decl);
1820 if (init && init != error_mark_node)
1822 if (!TREE_STATIC (decl))
1824 DECL_INITIAL (decl) = NULL_TREE;
1825 init = build2 (INIT_EXPR, void_type_node, decl, init);
1826 gimplify_and_add (init, seq_p);
1827 ggc_free (init);
1829 else
1830 /* We must still examine initializers for static variables
1831 as they may contain a label address. */
1832 walk_tree (&init, force_labels_r, NULL, NULL);
1836 return GS_ALL_DONE;
1839 /* Gimplify a LOOP_EXPR. Normally this just involves gimplifying the body
1840 and replacing the LOOP_EXPR with goto, but if the loop contains an
1841 EXIT_EXPR, we need to append a label for it to jump to. */
1843 static enum gimplify_status
1844 gimplify_loop_expr (tree *expr_p, gimple_seq *pre_p)
1846 tree saved_label = gimplify_ctxp->exit_label;
1847 tree start_label = create_artificial_label (UNKNOWN_LOCATION);
1849 gimplify_seq_add_stmt (pre_p, gimple_build_label (start_label));
1851 gimplify_ctxp->exit_label = NULL_TREE;
1853 gimplify_and_add (LOOP_EXPR_BODY (*expr_p), pre_p);
1855 gimplify_seq_add_stmt (pre_p, gimple_build_goto (start_label));
1857 if (gimplify_ctxp->exit_label)
1858 gimplify_seq_add_stmt (pre_p,
1859 gimple_build_label (gimplify_ctxp->exit_label));
1861 gimplify_ctxp->exit_label = saved_label;
1863 *expr_p = NULL;
1864 return GS_ALL_DONE;
1867 /* Gimplify a statement list onto a sequence. These may be created either
1868 by an enlightened front-end, or by shortcut_cond_expr. */
1870 static enum gimplify_status
1871 gimplify_statement_list (tree *expr_p, gimple_seq *pre_p)
1873 tree temp = voidify_wrapper_expr (*expr_p, NULL);
1875 tree_stmt_iterator i = tsi_start (*expr_p);
1877 while (!tsi_end_p (i))
1879 gimplify_stmt (tsi_stmt_ptr (i), pre_p);
1880 tsi_delink (&i);
1883 if (temp)
1885 *expr_p = temp;
1886 return GS_OK;
1889 return GS_ALL_DONE;
1892 /* Callback for walk_gimple_seq. */
1894 static tree
1895 warn_switch_unreachable_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
1896 struct walk_stmt_info *wi)
1898 gimple *stmt = gsi_stmt (*gsi_p);
1900 *handled_ops_p = true;
1901 switch (gimple_code (stmt))
1903 case GIMPLE_TRY:
1904 /* A compiler-generated cleanup or a user-written try block.
1905 If it's empty, don't dive into it--that would result in
1906 worse location info. */
1907 if (gimple_try_eval (stmt) == NULL)
1909 wi->info = stmt;
1910 return integer_zero_node;
1912 /* Fall through. */
1913 case GIMPLE_BIND:
1914 case GIMPLE_CATCH:
1915 case GIMPLE_EH_FILTER:
1916 case GIMPLE_TRANSACTION:
1917 /* Walk the sub-statements. */
1918 *handled_ops_p = false;
1919 break;
1921 case GIMPLE_DEBUG:
1922 /* Ignore these. We may generate them before declarations that
1923 are never executed. If there's something to warn about,
1924 there will be non-debug stmts too, and we'll catch those. */
1925 break;
1927 case GIMPLE_CALL:
1928 if (gimple_call_internal_p (stmt, IFN_ASAN_MARK))
1930 *handled_ops_p = false;
1931 break;
1933 /* Fall through. */
1934 default:
1935 /* Save the first "real" statement (not a decl/lexical scope/...). */
1936 wi->info = stmt;
1937 return integer_zero_node;
1939 return NULL_TREE;
1942 /* Possibly warn about unreachable statements between switch's controlling
1943 expression and the first case. SEQ is the body of a switch expression. */
1945 static void
1946 maybe_warn_switch_unreachable (gimple_seq seq)
1948 if (!warn_switch_unreachable
1949 /* This warning doesn't play well with Fortran when optimizations
1950 are on. */
1951 || lang_GNU_Fortran ()
1952 || seq == NULL)
1953 return;
1955 struct walk_stmt_info wi;
1956 memset (&wi, 0, sizeof (wi));
1957 walk_gimple_seq (seq, warn_switch_unreachable_r, NULL, &wi);
1958 gimple *stmt = (gimple *) wi.info;
1960 if (stmt && gimple_code (stmt) != GIMPLE_LABEL)
1962 if (gimple_code (stmt) == GIMPLE_GOTO
1963 && TREE_CODE (gimple_goto_dest (stmt)) == LABEL_DECL
1964 && DECL_ARTIFICIAL (gimple_goto_dest (stmt)))
1965 /* Don't warn for compiler-generated gotos. These occur
1966 in Duff's devices, for example. */;
1967 else
1968 warning_at (gimple_location (stmt), OPT_Wswitch_unreachable,
1969 "statement will never be executed");
1974 /* A label entry that pairs label and a location. */
1975 struct label_entry
1977 tree label;
1978 location_t loc;
1981 /* Find LABEL in vector of label entries VEC. */
1983 static struct label_entry *
1984 find_label_entry (const auto_vec<struct label_entry> *vec, tree label)
1986 unsigned int i;
1987 struct label_entry *l;
1989 FOR_EACH_VEC_ELT (*vec, i, l)
1990 if (l->label == label)
1991 return l;
1992 return NULL;
1995 /* Return true if LABEL, a LABEL_DECL, represents a case label
1996 in a vector of labels CASES. */
1998 static bool
1999 case_label_p (const vec<tree> *cases, tree label)
2001 unsigned int i;
2002 tree l;
2004 FOR_EACH_VEC_ELT (*cases, i, l)
2005 if (CASE_LABEL (l) == label)
2006 return true;
2007 return false;
2010 /* Find the last nondebug statement in a scope STMT. */
2012 static gimple *
2013 last_stmt_in_scope (gimple *stmt)
2015 if (!stmt)
2016 return NULL;
2018 switch (gimple_code (stmt))
2020 case GIMPLE_BIND:
2022 gbind *bind = as_a <gbind *> (stmt);
2023 stmt = gimple_seq_last_nondebug_stmt (gimple_bind_body (bind));
2024 return last_stmt_in_scope (stmt);
2027 case GIMPLE_TRY:
2029 gtry *try_stmt = as_a <gtry *> (stmt);
2030 stmt = gimple_seq_last_nondebug_stmt (gimple_try_eval (try_stmt));
2031 gimple *last_eval = last_stmt_in_scope (stmt);
2032 if (gimple_stmt_may_fallthru (last_eval)
2033 && (last_eval == NULL
2034 || !gimple_call_internal_p (last_eval, IFN_FALLTHROUGH))
2035 && gimple_try_kind (try_stmt) == GIMPLE_TRY_FINALLY)
2037 stmt = gimple_seq_last_nondebug_stmt (gimple_try_cleanup (try_stmt));
2038 return last_stmt_in_scope (stmt);
2040 else
2041 return last_eval;
2044 case GIMPLE_DEBUG:
2045 gcc_unreachable ();
2047 default:
2048 return stmt;
2052 /* Collect interesting labels in LABELS and return the statement preceding
2053 another case label, or a user-defined label. Store a location useful
2054 to give warnings at *PREVLOC (usually the location of the returned
2055 statement or of its surrounding scope). */
2057 static gimple *
2058 collect_fallthrough_labels (gimple_stmt_iterator *gsi_p,
2059 auto_vec <struct label_entry> *labels,
2060 location_t *prevloc)
2062 gimple *prev = NULL;
2064 *prevloc = UNKNOWN_LOCATION;
2067 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_BIND)
2069 /* Recognize the special GIMPLE_BIND added by gimplify_switch_expr,
2070 which starts on a GIMPLE_SWITCH and ends with a break label.
2071 Handle that as a single statement that can fall through. */
2072 gbind *bind = as_a <gbind *> (gsi_stmt (*gsi_p));
2073 gimple *first = gimple_seq_first_stmt (gimple_bind_body (bind));
2074 gimple *last = gimple_seq_last_stmt (gimple_bind_body (bind));
2075 if (last
2076 && gimple_code (first) == GIMPLE_SWITCH
2077 && gimple_code (last) == GIMPLE_LABEL)
2079 tree label = gimple_label_label (as_a <glabel *> (last));
2080 if (SWITCH_BREAK_LABEL_P (label))
2082 prev = bind;
2083 gsi_next (gsi_p);
2084 continue;
2088 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_BIND
2089 || gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_TRY)
2091 /* Nested scope. Only look at the last statement of
2092 the innermost scope. */
2093 location_t bind_loc = gimple_location (gsi_stmt (*gsi_p));
2094 gimple *last = last_stmt_in_scope (gsi_stmt (*gsi_p));
2095 if (last)
2097 prev = last;
2098 /* It might be a label without a location. Use the
2099 location of the scope then. */
2100 if (!gimple_has_location (prev))
2101 *prevloc = bind_loc;
2103 gsi_next (gsi_p);
2104 continue;
2107 /* Ifs are tricky. */
2108 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_COND)
2110 gcond *cond_stmt = as_a <gcond *> (gsi_stmt (*gsi_p));
2111 tree false_lab = gimple_cond_false_label (cond_stmt);
2112 location_t if_loc = gimple_location (cond_stmt);
2114 /* If we have e.g.
2115 if (i > 1) goto <D.2259>; else goto D;
2116 we can't do much with the else-branch. */
2117 if (!DECL_ARTIFICIAL (false_lab))
2118 break;
2120 /* Go on until the false label, then one step back. */
2121 for (; !gsi_end_p (*gsi_p); gsi_next (gsi_p))
2123 gimple *stmt = gsi_stmt (*gsi_p);
2124 if (gimple_code (stmt) == GIMPLE_LABEL
2125 && gimple_label_label (as_a <glabel *> (stmt)) == false_lab)
2126 break;
2129 /* Not found? Oops. */
2130 if (gsi_end_p (*gsi_p))
2131 break;
2133 struct label_entry l = { false_lab, if_loc };
2134 labels->safe_push (l);
2136 /* Go to the last statement of the then branch. */
2137 gsi_prev (gsi_p);
2139 /* if (i != 0) goto <D.1759>; else goto <D.1760>;
2140 <D.1759>:
2141 <stmt>;
2142 goto <D.1761>;
2143 <D.1760>:
2145 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_GOTO
2146 && !gimple_has_location (gsi_stmt (*gsi_p)))
2148 /* Look at the statement before, it might be
2149 attribute fallthrough, in which case don't warn. */
2150 gsi_prev (gsi_p);
2151 bool fallthru_before_dest
2152 = gimple_call_internal_p (gsi_stmt (*gsi_p), IFN_FALLTHROUGH);
2153 gsi_next (gsi_p);
2154 tree goto_dest = gimple_goto_dest (gsi_stmt (*gsi_p));
2155 if (!fallthru_before_dest)
2157 struct label_entry l = { goto_dest, if_loc };
2158 labels->safe_push (l);
2161 /* And move back. */
2162 gsi_next (gsi_p);
2165 /* Remember the last statement. Skip labels that are of no interest
2166 to us. */
2167 if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_LABEL)
2169 tree label = gimple_label_label (as_a <glabel *> (gsi_stmt (*gsi_p)));
2170 if (find_label_entry (labels, label))
2171 prev = gsi_stmt (*gsi_p);
2173 else if (gimple_call_internal_p (gsi_stmt (*gsi_p), IFN_ASAN_MARK))
2175 else if (gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_PREDICT)
2177 else if (!is_gimple_debug (gsi_stmt (*gsi_p)))
2178 prev = gsi_stmt (*gsi_p);
2179 gsi_next (gsi_p);
2181 while (!gsi_end_p (*gsi_p)
2182 /* Stop if we find a case or a user-defined label. */
2183 && (gimple_code (gsi_stmt (*gsi_p)) != GIMPLE_LABEL
2184 || !gimple_has_location (gsi_stmt (*gsi_p))));
2186 if (prev && gimple_has_location (prev))
2187 *prevloc = gimple_location (prev);
2188 return prev;
2191 /* Return true if the switch fallthough warning should occur. LABEL is
2192 the label statement that we're falling through to. */
2194 static bool
2195 should_warn_for_implicit_fallthrough (gimple_stmt_iterator *gsi_p, tree label)
2197 gimple_stmt_iterator gsi = *gsi_p;
2199 /* Don't warn if the label is marked with a "falls through" comment. */
2200 if (FALLTHROUGH_LABEL_P (label))
2201 return false;
2203 /* Don't warn for non-case labels followed by a statement:
2204 case 0:
2205 foo ();
2206 label:
2207 bar ();
2208 as these are likely intentional. */
2209 if (!case_label_p (&gimplify_ctxp->case_labels, label))
2211 tree l;
2212 while (!gsi_end_p (gsi)
2213 && gimple_code (gsi_stmt (gsi)) == GIMPLE_LABEL
2214 && (l = gimple_label_label (as_a <glabel *> (gsi_stmt (gsi))))
2215 && !case_label_p (&gimplify_ctxp->case_labels, l))
2216 gsi_next_nondebug (&gsi);
2217 if (gsi_end_p (gsi) || gimple_code (gsi_stmt (gsi)) != GIMPLE_LABEL)
2218 return false;
2221 /* Don't warn for terminated branches, i.e. when the subsequent case labels
2222 immediately breaks. */
2223 gsi = *gsi_p;
2225 /* Skip all immediately following labels. */
2226 while (!gsi_end_p (gsi)
2227 && (gimple_code (gsi_stmt (gsi)) == GIMPLE_LABEL
2228 || gimple_code (gsi_stmt (gsi)) == GIMPLE_PREDICT))
2229 gsi_next_nondebug (&gsi);
2231 /* { ... something; default:; } */
2232 if (gsi_end_p (gsi)
2233 /* { ... something; default: break; } or
2234 { ... something; default: goto L; } */
2235 || gimple_code (gsi_stmt (gsi)) == GIMPLE_GOTO
2236 /* { ... something; default: return; } */
2237 || gimple_code (gsi_stmt (gsi)) == GIMPLE_RETURN)
2238 return false;
2240 return true;
2243 /* Callback for walk_gimple_seq. */
2245 static tree
2246 warn_implicit_fallthrough_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
2247 struct walk_stmt_info *)
2249 gimple *stmt = gsi_stmt (*gsi_p);
2251 *handled_ops_p = true;
2252 switch (gimple_code (stmt))
2254 case GIMPLE_TRY:
2255 case GIMPLE_BIND:
2256 case GIMPLE_CATCH:
2257 case GIMPLE_EH_FILTER:
2258 case GIMPLE_TRANSACTION:
2259 /* Walk the sub-statements. */
2260 *handled_ops_p = false;
2261 break;
2263 /* Find a sequence of form:
2265 GIMPLE_LABEL
2266 [...]
2267 <may fallthru stmt>
2268 GIMPLE_LABEL
2270 and possibly warn. */
2271 case GIMPLE_LABEL:
2273 /* Found a label. Skip all immediately following labels. */
2274 while (!gsi_end_p (*gsi_p)
2275 && gimple_code (gsi_stmt (*gsi_p)) == GIMPLE_LABEL)
2276 gsi_next_nondebug (gsi_p);
2278 /* There might be no more statements. */
2279 if (gsi_end_p (*gsi_p))
2280 return integer_zero_node;
2282 /* Vector of labels that fall through. */
2283 auto_vec <struct label_entry> labels;
2284 location_t prevloc;
2285 gimple *prev = collect_fallthrough_labels (gsi_p, &labels, &prevloc);
2287 /* There might be no more statements. */
2288 if (gsi_end_p (*gsi_p))
2289 return integer_zero_node;
2291 gimple *next = gsi_stmt (*gsi_p);
2292 tree label;
2293 /* If what follows is a label, then we may have a fallthrough. */
2294 if (gimple_code (next) == GIMPLE_LABEL
2295 && gimple_has_location (next)
2296 && (label = gimple_label_label (as_a <glabel *> (next)))
2297 && prev != NULL)
2299 struct label_entry *l;
2300 bool warned_p = false;
2301 auto_diagnostic_group d;
2302 if (!should_warn_for_implicit_fallthrough (gsi_p, label))
2303 /* Quiet. */;
2304 else if (gimple_code (prev) == GIMPLE_LABEL
2305 && (label = gimple_label_label (as_a <glabel *> (prev)))
2306 && (l = find_label_entry (&labels, label)))
2307 warned_p = warning_at (l->loc, OPT_Wimplicit_fallthrough_,
2308 "this statement may fall through");
2309 else if (!gimple_call_internal_p (prev, IFN_FALLTHROUGH)
2310 /* Try to be clever and don't warn when the statement
2311 can't actually fall through. */
2312 && gimple_stmt_may_fallthru (prev)
2313 && prevloc != UNKNOWN_LOCATION)
2314 warned_p = warning_at (prevloc,
2315 OPT_Wimplicit_fallthrough_,
2316 "this statement may fall through");
2317 if (warned_p)
2318 inform (gimple_location (next), "here");
2320 /* Mark this label as processed so as to prevent multiple
2321 warnings in nested switches. */
2322 FALLTHROUGH_LABEL_P (label) = true;
2324 /* So that next warn_implicit_fallthrough_r will start looking for
2325 a new sequence starting with this label. */
2326 gsi_prev (gsi_p);
2329 break;
2330 default:
2331 break;
2333 return NULL_TREE;
2336 /* Warn when a switch case falls through. */
2338 static void
2339 maybe_warn_implicit_fallthrough (gimple_seq seq)
2341 if (!warn_implicit_fallthrough)
2342 return;
2344 /* This warning is meant for C/C++/ObjC/ObjC++ only. */
2345 if (!(lang_GNU_C ()
2346 || lang_GNU_CXX ()
2347 || lang_GNU_OBJC ()))
2348 return;
2350 struct walk_stmt_info wi;
2351 memset (&wi, 0, sizeof (wi));
2352 walk_gimple_seq (seq, warn_implicit_fallthrough_r, NULL, &wi);
2355 /* Callback for walk_gimple_seq. */
2357 static tree
2358 expand_FALLTHROUGH_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
2359 struct walk_stmt_info *wi)
2361 gimple *stmt = gsi_stmt (*gsi_p);
2363 *handled_ops_p = true;
2364 switch (gimple_code (stmt))
2366 case GIMPLE_TRY:
2367 case GIMPLE_BIND:
2368 case GIMPLE_CATCH:
2369 case GIMPLE_EH_FILTER:
2370 case GIMPLE_TRANSACTION:
2371 /* Walk the sub-statements. */
2372 *handled_ops_p = false;
2373 break;
2374 case GIMPLE_CALL:
2375 if (gimple_call_internal_p (stmt, IFN_FALLTHROUGH))
2377 gsi_remove (gsi_p, true);
2378 if (gsi_end_p (*gsi_p))
2380 *static_cast<location_t *>(wi->info) = gimple_location (stmt);
2381 return integer_zero_node;
2384 bool found = false;
2385 location_t loc = gimple_location (stmt);
2387 gimple_stmt_iterator gsi2 = *gsi_p;
2388 stmt = gsi_stmt (gsi2);
2389 if (gimple_code (stmt) == GIMPLE_GOTO && !gimple_has_location (stmt))
2391 /* Go on until the artificial label. */
2392 tree goto_dest = gimple_goto_dest (stmt);
2393 for (; !gsi_end_p (gsi2); gsi_next (&gsi2))
2395 if (gimple_code (gsi_stmt (gsi2)) == GIMPLE_LABEL
2396 && gimple_label_label (as_a <glabel *> (gsi_stmt (gsi2)))
2397 == goto_dest)
2398 break;
2401 /* Not found? Stop. */
2402 if (gsi_end_p (gsi2))
2403 break;
2405 /* Look one past it. */
2406 gsi_next (&gsi2);
2409 /* We're looking for a case label or default label here. */
2410 while (!gsi_end_p (gsi2))
2412 stmt = gsi_stmt (gsi2);
2413 if (gimple_code (stmt) == GIMPLE_LABEL)
2415 tree label = gimple_label_label (as_a <glabel *> (stmt));
2416 if (gimple_has_location (stmt) && DECL_ARTIFICIAL (label))
2418 found = true;
2419 break;
2422 else if (gimple_call_internal_p (stmt, IFN_ASAN_MARK))
2424 else if (!is_gimple_debug (stmt))
2425 /* Anything else is not expected. */
2426 break;
2427 gsi_next (&gsi2);
2429 if (!found)
2430 pedwarn (loc, 0, "attribute %<fallthrough%> not preceding "
2431 "a case label or default label");
2433 break;
2434 default:
2435 break;
2437 return NULL_TREE;
2440 /* Expand all FALLTHROUGH () calls in SEQ. */
2442 static void
2443 expand_FALLTHROUGH (gimple_seq *seq_p)
2445 struct walk_stmt_info wi;
2446 location_t loc;
2447 memset (&wi, 0, sizeof (wi));
2448 wi.info = (void *) &loc;
2449 walk_gimple_seq_mod (seq_p, expand_FALLTHROUGH_r, NULL, &wi);
2450 if (wi.callback_result == integer_zero_node)
2451 /* We've found [[fallthrough]]; at the end of a switch, which the C++
2452 standard says is ill-formed; see [dcl.attr.fallthrough]. */
2453 pedwarn (loc, 0, "attribute %<fallthrough%> not preceding "
2454 "a case label or default label");
2458 /* Gimplify a SWITCH_EXPR, and collect the vector of labels it can
2459 branch to. */
2461 static enum gimplify_status
2462 gimplify_switch_expr (tree *expr_p, gimple_seq *pre_p)
2464 tree switch_expr = *expr_p;
2465 gimple_seq switch_body_seq = NULL;
2466 enum gimplify_status ret;
2467 tree index_type = TREE_TYPE (switch_expr);
2468 if (index_type == NULL_TREE)
2469 index_type = TREE_TYPE (SWITCH_COND (switch_expr));
2471 ret = gimplify_expr (&SWITCH_COND (switch_expr), pre_p, NULL, is_gimple_val,
2472 fb_rvalue);
2473 if (ret == GS_ERROR || ret == GS_UNHANDLED)
2474 return ret;
2476 if (SWITCH_BODY (switch_expr))
2478 vec<tree> labels;
2479 vec<tree> saved_labels;
2480 hash_set<tree> *saved_live_switch_vars = NULL;
2481 tree default_case = NULL_TREE;
2482 gswitch *switch_stmt;
2484 /* Save old labels, get new ones from body, then restore the old
2485 labels. Save all the things from the switch body to append after. */
2486 saved_labels = gimplify_ctxp->case_labels;
2487 gimplify_ctxp->case_labels.create (8);
2489 /* Do not create live_switch_vars if SWITCH_BODY is not a BIND_EXPR. */
2490 saved_live_switch_vars = gimplify_ctxp->live_switch_vars;
2491 tree_code body_type = TREE_CODE (SWITCH_BODY (switch_expr));
2492 if (body_type == BIND_EXPR || body_type == STATEMENT_LIST)
2493 gimplify_ctxp->live_switch_vars = new hash_set<tree> (4);
2494 else
2495 gimplify_ctxp->live_switch_vars = NULL;
2497 bool old_in_switch_expr = gimplify_ctxp->in_switch_expr;
2498 gimplify_ctxp->in_switch_expr = true;
2500 gimplify_stmt (&SWITCH_BODY (switch_expr), &switch_body_seq);
2502 gimplify_ctxp->in_switch_expr = old_in_switch_expr;
2503 maybe_warn_switch_unreachable (switch_body_seq);
2504 maybe_warn_implicit_fallthrough (switch_body_seq);
2505 /* Only do this for the outermost GIMPLE_SWITCH. */
2506 if (!gimplify_ctxp->in_switch_expr)
2507 expand_FALLTHROUGH (&switch_body_seq);
2509 labels = gimplify_ctxp->case_labels;
2510 gimplify_ctxp->case_labels = saved_labels;
2512 if (gimplify_ctxp->live_switch_vars)
2514 gcc_assert (gimplify_ctxp->live_switch_vars->is_empty ());
2515 delete gimplify_ctxp->live_switch_vars;
2517 gimplify_ctxp->live_switch_vars = saved_live_switch_vars;
2519 preprocess_case_label_vec_for_gimple (labels, index_type,
2520 &default_case);
2522 bool add_bind = false;
2523 if (!default_case)
2525 glabel *new_default;
2527 default_case
2528 = build_case_label (NULL_TREE, NULL_TREE,
2529 create_artificial_label (UNKNOWN_LOCATION));
2530 if (old_in_switch_expr)
2532 SWITCH_BREAK_LABEL_P (CASE_LABEL (default_case)) = 1;
2533 add_bind = true;
2535 new_default = gimple_build_label (CASE_LABEL (default_case));
2536 gimplify_seq_add_stmt (&switch_body_seq, new_default);
2538 else if (old_in_switch_expr)
2540 gimple *last = gimple_seq_last_stmt (switch_body_seq);
2541 if (last && gimple_code (last) == GIMPLE_LABEL)
2543 tree label = gimple_label_label (as_a <glabel *> (last));
2544 if (SWITCH_BREAK_LABEL_P (label))
2545 add_bind = true;
2549 switch_stmt = gimple_build_switch (SWITCH_COND (switch_expr),
2550 default_case, labels);
2551 /* For the benefit of -Wimplicit-fallthrough, if switch_body_seq
2552 ends with a GIMPLE_LABEL holding SWITCH_BREAK_LABEL_P LABEL_DECL,
2553 wrap the GIMPLE_SWITCH up to that GIMPLE_LABEL into a GIMPLE_BIND,
2554 so that we can easily find the start and end of the switch
2555 statement. */
2556 if (add_bind)
2558 gimple_seq bind_body = NULL;
2559 gimplify_seq_add_stmt (&bind_body, switch_stmt);
2560 gimple_seq_add_seq (&bind_body, switch_body_seq);
2561 gbind *bind = gimple_build_bind (NULL_TREE, bind_body, NULL_TREE);
2562 gimple_set_location (bind, EXPR_LOCATION (switch_expr));
2563 gimplify_seq_add_stmt (pre_p, bind);
2565 else
2567 gimplify_seq_add_stmt (pre_p, switch_stmt);
2568 gimplify_seq_add_seq (pre_p, switch_body_seq);
2570 labels.release ();
2572 else
2573 gcc_unreachable ();
2575 return GS_ALL_DONE;
2578 /* Gimplify the LABEL_EXPR pointed to by EXPR_P. */
2580 static enum gimplify_status
2581 gimplify_label_expr (tree *expr_p, gimple_seq *pre_p)
2583 gcc_assert (decl_function_context (LABEL_EXPR_LABEL (*expr_p))
2584 == current_function_decl);
2586 tree label = LABEL_EXPR_LABEL (*expr_p);
2587 glabel *label_stmt = gimple_build_label (label);
2588 gimple_set_location (label_stmt, EXPR_LOCATION (*expr_p));
2589 gimplify_seq_add_stmt (pre_p, label_stmt);
2591 if (lookup_attribute ("cold", DECL_ATTRIBUTES (label)))
2592 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_COLD_LABEL,
2593 NOT_TAKEN));
2594 else if (lookup_attribute ("hot", DECL_ATTRIBUTES (label)))
2595 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_HOT_LABEL,
2596 TAKEN));
2598 return GS_ALL_DONE;
2601 /* Gimplify the CASE_LABEL_EXPR pointed to by EXPR_P. */
2603 static enum gimplify_status
2604 gimplify_case_label_expr (tree *expr_p, gimple_seq *pre_p)
2606 struct gimplify_ctx *ctxp;
2607 glabel *label_stmt;
2609 /* Invalid programs can play Duff's Device type games with, for example,
2610 #pragma omp parallel. At least in the C front end, we don't
2611 detect such invalid branches until after gimplification, in the
2612 diagnose_omp_blocks pass. */
2613 for (ctxp = gimplify_ctxp; ; ctxp = ctxp->prev_context)
2614 if (ctxp->case_labels.exists ())
2615 break;
2617 tree label = CASE_LABEL (*expr_p);
2618 label_stmt = gimple_build_label (label);
2619 gimple_set_location (label_stmt, EXPR_LOCATION (*expr_p));
2620 ctxp->case_labels.safe_push (*expr_p);
2621 gimplify_seq_add_stmt (pre_p, label_stmt);
2623 if (lookup_attribute ("cold", DECL_ATTRIBUTES (label)))
2624 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_COLD_LABEL,
2625 NOT_TAKEN));
2626 else if (lookup_attribute ("hot", DECL_ATTRIBUTES (label)))
2627 gimple_seq_add_stmt (pre_p, gimple_build_predict (PRED_HOT_LABEL,
2628 TAKEN));
2630 return GS_ALL_DONE;
2633 /* Build a GOTO to the LABEL_DECL pointed to by LABEL_P, building it first
2634 if necessary. */
2636 tree
2637 build_and_jump (tree *label_p)
2639 if (label_p == NULL)
2640 /* If there's nowhere to jump, just fall through. */
2641 return NULL_TREE;
2643 if (*label_p == NULL_TREE)
2645 tree label = create_artificial_label (UNKNOWN_LOCATION);
2646 *label_p = label;
2649 return build1 (GOTO_EXPR, void_type_node, *label_p);
2652 /* Gimplify an EXIT_EXPR by converting to a GOTO_EXPR inside a COND_EXPR.
2653 This also involves building a label to jump to and communicating it to
2654 gimplify_loop_expr through gimplify_ctxp->exit_label. */
2656 static enum gimplify_status
2657 gimplify_exit_expr (tree *expr_p)
2659 tree cond = TREE_OPERAND (*expr_p, 0);
2660 tree expr;
2662 expr = build_and_jump (&gimplify_ctxp->exit_label);
2663 expr = build3 (COND_EXPR, void_type_node, cond, expr, NULL_TREE);
2664 *expr_p = expr;
2666 return GS_OK;
2669 /* *EXPR_P is a COMPONENT_REF being used as an rvalue. If its type is
2670 different from its canonical type, wrap the whole thing inside a
2671 NOP_EXPR and force the type of the COMPONENT_REF to be the canonical
2672 type.
2674 The canonical type of a COMPONENT_REF is the type of the field being
2675 referenced--unless the field is a bit-field which can be read directly
2676 in a smaller mode, in which case the canonical type is the
2677 sign-appropriate type corresponding to that mode. */
2679 static void
2680 canonicalize_component_ref (tree *expr_p)
2682 tree expr = *expr_p;
2683 tree type;
2685 gcc_assert (TREE_CODE (expr) == COMPONENT_REF);
2687 if (INTEGRAL_TYPE_P (TREE_TYPE (expr)))
2688 type = TREE_TYPE (get_unwidened (expr, NULL_TREE));
2689 else
2690 type = TREE_TYPE (TREE_OPERAND (expr, 1));
2692 /* One could argue that all the stuff below is not necessary for
2693 the non-bitfield case and declare it a FE error if type
2694 adjustment would be needed. */
2695 if (TREE_TYPE (expr) != type)
2697 #ifdef ENABLE_TYPES_CHECKING
2698 tree old_type = TREE_TYPE (expr);
2699 #endif
2700 int type_quals;
2702 /* We need to preserve qualifiers and propagate them from
2703 operand 0. */
2704 type_quals = TYPE_QUALS (type)
2705 | TYPE_QUALS (TREE_TYPE (TREE_OPERAND (expr, 0)));
2706 if (TYPE_QUALS (type) != type_quals)
2707 type = build_qualified_type (TYPE_MAIN_VARIANT (type), type_quals);
2709 /* Set the type of the COMPONENT_REF to the underlying type. */
2710 TREE_TYPE (expr) = type;
2712 #ifdef ENABLE_TYPES_CHECKING
2713 /* It is now a FE error, if the conversion from the canonical
2714 type to the original expression type is not useless. */
2715 gcc_assert (useless_type_conversion_p (old_type, type));
2716 #endif
2720 /* If a NOP conversion is changing a pointer to array of foo to a pointer
2721 to foo, embed that change in the ADDR_EXPR by converting
2722 T array[U];
2723 (T *)&array
2725 &array[L]
2726 where L is the lower bound. For simplicity, only do this for constant
2727 lower bound.
2728 The constraint is that the type of &array[L] is trivially convertible
2729 to T *. */
2731 static void
2732 canonicalize_addr_expr (tree *expr_p)
2734 tree expr = *expr_p;
2735 tree addr_expr = TREE_OPERAND (expr, 0);
2736 tree datype, ddatype, pddatype;
2738 /* We simplify only conversions from an ADDR_EXPR to a pointer type. */
2739 if (!POINTER_TYPE_P (TREE_TYPE (expr))
2740 || TREE_CODE (addr_expr) != ADDR_EXPR)
2741 return;
2743 /* The addr_expr type should be a pointer to an array. */
2744 datype = TREE_TYPE (TREE_TYPE (addr_expr));
2745 if (TREE_CODE (datype) != ARRAY_TYPE)
2746 return;
2748 /* The pointer to element type shall be trivially convertible to
2749 the expression pointer type. */
2750 ddatype = TREE_TYPE (datype);
2751 pddatype = build_pointer_type (ddatype);
2752 if (!useless_type_conversion_p (TYPE_MAIN_VARIANT (TREE_TYPE (expr)),
2753 pddatype))
2754 return;
2756 /* The lower bound and element sizes must be constant. */
2757 if (!TYPE_SIZE_UNIT (ddatype)
2758 || TREE_CODE (TYPE_SIZE_UNIT (ddatype)) != INTEGER_CST
2759 || !TYPE_DOMAIN (datype) || !TYPE_MIN_VALUE (TYPE_DOMAIN (datype))
2760 || TREE_CODE (TYPE_MIN_VALUE (TYPE_DOMAIN (datype))) != INTEGER_CST)
2761 return;
2763 /* All checks succeeded. Build a new node to merge the cast. */
2764 *expr_p = build4 (ARRAY_REF, ddatype, TREE_OPERAND (addr_expr, 0),
2765 TYPE_MIN_VALUE (TYPE_DOMAIN (datype)),
2766 NULL_TREE, NULL_TREE);
2767 *expr_p = build1 (ADDR_EXPR, pddatype, *expr_p);
2769 /* We can have stripped a required restrict qualifier above. */
2770 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
2771 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
2774 /* *EXPR_P is a NOP_EXPR or CONVERT_EXPR. Remove it and/or other conversions
2775 underneath as appropriate. */
2777 static enum gimplify_status
2778 gimplify_conversion (tree *expr_p)
2780 location_t loc = EXPR_LOCATION (*expr_p);
2781 gcc_assert (CONVERT_EXPR_P (*expr_p));
2783 /* Then strip away all but the outermost conversion. */
2784 STRIP_SIGN_NOPS (TREE_OPERAND (*expr_p, 0));
2786 /* And remove the outermost conversion if it's useless. */
2787 if (tree_ssa_useless_type_conversion (*expr_p))
2788 *expr_p = TREE_OPERAND (*expr_p, 0);
2790 /* If we still have a conversion at the toplevel,
2791 then canonicalize some constructs. */
2792 if (CONVERT_EXPR_P (*expr_p))
2794 tree sub = TREE_OPERAND (*expr_p, 0);
2796 /* If a NOP conversion is changing the type of a COMPONENT_REF
2797 expression, then canonicalize its type now in order to expose more
2798 redundant conversions. */
2799 if (TREE_CODE (sub) == COMPONENT_REF)
2800 canonicalize_component_ref (&TREE_OPERAND (*expr_p, 0));
2802 /* If a NOP conversion is changing a pointer to array of foo
2803 to a pointer to foo, embed that change in the ADDR_EXPR. */
2804 else if (TREE_CODE (sub) == ADDR_EXPR)
2805 canonicalize_addr_expr (expr_p);
2808 /* If we have a conversion to a non-register type force the
2809 use of a VIEW_CONVERT_EXPR instead. */
2810 if (CONVERT_EXPR_P (*expr_p) && !is_gimple_reg_type (TREE_TYPE (*expr_p)))
2811 *expr_p = fold_build1_loc (loc, VIEW_CONVERT_EXPR, TREE_TYPE (*expr_p),
2812 TREE_OPERAND (*expr_p, 0));
2814 /* Canonicalize CONVERT_EXPR to NOP_EXPR. */
2815 if (TREE_CODE (*expr_p) == CONVERT_EXPR)
2816 TREE_SET_CODE (*expr_p, NOP_EXPR);
2818 return GS_OK;
2821 /* Gimplify a VAR_DECL or PARM_DECL. Return GS_OK if we expanded a
2822 DECL_VALUE_EXPR, and it's worth re-examining things. */
2824 static enum gimplify_status
2825 gimplify_var_or_parm_decl (tree *expr_p)
2827 tree decl = *expr_p;
2829 /* ??? If this is a local variable, and it has not been seen in any
2830 outer BIND_EXPR, then it's probably the result of a duplicate
2831 declaration, for which we've already issued an error. It would
2832 be really nice if the front end wouldn't leak these at all.
2833 Currently the only known culprit is C++ destructors, as seen
2834 in g++.old-deja/g++.jason/binding.C. */
2835 if (VAR_P (decl)
2836 && !DECL_SEEN_IN_BIND_EXPR_P (decl)
2837 && !TREE_STATIC (decl) && !DECL_EXTERNAL (decl)
2838 && decl_function_context (decl) == current_function_decl)
2840 gcc_assert (seen_error ());
2841 return GS_ERROR;
2844 /* When within an OMP context, notice uses of variables. */
2845 if (gimplify_omp_ctxp && omp_notice_variable (gimplify_omp_ctxp, decl, true))
2846 return GS_ALL_DONE;
2848 /* If the decl is an alias for another expression, substitute it now. */
2849 if (DECL_HAS_VALUE_EXPR_P (decl))
2851 *expr_p = unshare_expr (DECL_VALUE_EXPR (decl));
2852 return GS_OK;
2855 return GS_ALL_DONE;
2858 /* Recalculate the value of the TREE_SIDE_EFFECTS flag for T. */
2860 static void
2861 recalculate_side_effects (tree t)
2863 enum tree_code code = TREE_CODE (t);
2864 int len = TREE_OPERAND_LENGTH (t);
2865 int i;
2867 switch (TREE_CODE_CLASS (code))
2869 case tcc_expression:
2870 switch (code)
2872 case INIT_EXPR:
2873 case MODIFY_EXPR:
2874 case VA_ARG_EXPR:
2875 case PREDECREMENT_EXPR:
2876 case PREINCREMENT_EXPR:
2877 case POSTDECREMENT_EXPR:
2878 case POSTINCREMENT_EXPR:
2879 /* All of these have side-effects, no matter what their
2880 operands are. */
2881 return;
2883 default:
2884 break;
2886 /* Fall through. */
2888 case tcc_comparison: /* a comparison expression */
2889 case tcc_unary: /* a unary arithmetic expression */
2890 case tcc_binary: /* a binary arithmetic expression */
2891 case tcc_reference: /* a reference */
2892 case tcc_vl_exp: /* a function call */
2893 TREE_SIDE_EFFECTS (t) = TREE_THIS_VOLATILE (t);
2894 for (i = 0; i < len; ++i)
2896 tree op = TREE_OPERAND (t, i);
2897 if (op && TREE_SIDE_EFFECTS (op))
2898 TREE_SIDE_EFFECTS (t) = 1;
2900 break;
2902 case tcc_constant:
2903 /* No side-effects. */
2904 return;
2906 default:
2907 gcc_unreachable ();
2911 /* Gimplify the COMPONENT_REF, ARRAY_REF, REALPART_EXPR or IMAGPART_EXPR
2912 node *EXPR_P.
2914 compound_lval
2915 : min_lval '[' val ']'
2916 | min_lval '.' ID
2917 | compound_lval '[' val ']'
2918 | compound_lval '.' ID
2920 This is not part of the original SIMPLE definition, which separates
2921 array and member references, but it seems reasonable to handle them
2922 together. Also, this way we don't run into problems with union
2923 aliasing; gcc requires that for accesses through a union to alias, the
2924 union reference must be explicit, which was not always the case when we
2925 were splitting up array and member refs.
2927 PRE_P points to the sequence where side effects that must happen before
2928 *EXPR_P should be stored.
2930 POST_P points to the sequence where side effects that must happen after
2931 *EXPR_P should be stored. */
2933 static enum gimplify_status
2934 gimplify_compound_lval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
2935 fallback_t fallback)
2937 tree *p;
2938 enum gimplify_status ret = GS_ALL_DONE, tret;
2939 int i;
2940 location_t loc = EXPR_LOCATION (*expr_p);
2941 tree expr = *expr_p;
2943 /* Create a stack of the subexpressions so later we can walk them in
2944 order from inner to outer. */
2945 auto_vec<tree, 10> expr_stack;
2947 /* We can handle anything that get_inner_reference can deal with. */
2948 for (p = expr_p; ; p = &TREE_OPERAND (*p, 0))
2950 restart:
2951 /* Fold INDIRECT_REFs now to turn them into ARRAY_REFs. */
2952 if (TREE_CODE (*p) == INDIRECT_REF)
2953 *p = fold_indirect_ref_loc (loc, *p);
2955 if (handled_component_p (*p))
2957 /* Expand DECL_VALUE_EXPR now. In some cases that may expose
2958 additional COMPONENT_REFs. */
2959 else if ((VAR_P (*p) || TREE_CODE (*p) == PARM_DECL)
2960 && gimplify_var_or_parm_decl (p) == GS_OK)
2961 goto restart;
2962 else
2963 break;
2965 expr_stack.safe_push (*p);
2968 gcc_assert (expr_stack.length ());
2970 /* Now EXPR_STACK is a stack of pointers to all the refs we've
2971 walked through and P points to the innermost expression.
2973 Java requires that we elaborated nodes in source order. That
2974 means we must gimplify the inner expression followed by each of
2975 the indices, in order. But we can't gimplify the inner
2976 expression until we deal with any variable bounds, sizes, or
2977 positions in order to deal with PLACEHOLDER_EXPRs.
2979 So we do this in three steps. First we deal with the annotations
2980 for any variables in the components, then we gimplify the base,
2981 then we gimplify any indices, from left to right. */
2982 for (i = expr_stack.length () - 1; i >= 0; i--)
2984 tree t = expr_stack[i];
2986 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
2988 /* Gimplify the low bound and element type size and put them into
2989 the ARRAY_REF. If these values are set, they have already been
2990 gimplified. */
2991 if (TREE_OPERAND (t, 2) == NULL_TREE)
2993 tree low = unshare_expr (array_ref_low_bound (t));
2994 if (!is_gimple_min_invariant (low))
2996 TREE_OPERAND (t, 2) = low;
2997 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
2998 post_p, is_gimple_reg,
2999 fb_rvalue);
3000 ret = MIN (ret, tret);
3003 else
3005 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
3006 is_gimple_reg, fb_rvalue);
3007 ret = MIN (ret, tret);
3010 if (TREE_OPERAND (t, 3) == NULL_TREE)
3012 tree elmt_size = array_ref_element_size (t);
3013 if (!is_gimple_min_invariant (elmt_size))
3015 elmt_size = unshare_expr (elmt_size);
3016 tree elmt_type = TREE_TYPE (TREE_TYPE (TREE_OPERAND (t, 0)));
3017 tree factor = size_int (TYPE_ALIGN_UNIT (elmt_type));
3019 /* Divide the element size by the alignment of the element
3020 type (above). */
3021 elmt_size = size_binop_loc (loc, EXACT_DIV_EXPR,
3022 elmt_size, factor);
3024 TREE_OPERAND (t, 3) = elmt_size;
3025 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p,
3026 post_p, is_gimple_reg,
3027 fb_rvalue);
3028 ret = MIN (ret, tret);
3031 else
3033 tret = gimplify_expr (&TREE_OPERAND (t, 3), pre_p, post_p,
3034 is_gimple_reg, fb_rvalue);
3035 ret = MIN (ret, tret);
3038 else if (TREE_CODE (t) == COMPONENT_REF)
3040 /* Set the field offset into T and gimplify it. */
3041 if (TREE_OPERAND (t, 2) == NULL_TREE)
3043 tree offset = component_ref_field_offset (t);
3044 if (!is_gimple_min_invariant (offset))
3046 offset = unshare_expr (offset);
3047 tree field = TREE_OPERAND (t, 1);
3048 tree factor
3049 = size_int (DECL_OFFSET_ALIGN (field) / BITS_PER_UNIT);
3051 /* Divide the offset by its alignment. */
3052 offset = size_binop_loc (loc, EXACT_DIV_EXPR,
3053 offset, factor);
3055 TREE_OPERAND (t, 2) = offset;
3056 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p,
3057 post_p, is_gimple_reg,
3058 fb_rvalue);
3059 ret = MIN (ret, tret);
3062 else
3064 tret = gimplify_expr (&TREE_OPERAND (t, 2), pre_p, post_p,
3065 is_gimple_reg, fb_rvalue);
3066 ret = MIN (ret, tret);
3071 /* Step 2 is to gimplify the base expression. Make sure lvalue is set
3072 so as to match the min_lval predicate. Failure to do so may result
3073 in the creation of large aggregate temporaries. */
3074 tret = gimplify_expr (p, pre_p, post_p, is_gimple_min_lval,
3075 fallback | fb_lvalue);
3076 ret = MIN (ret, tret);
3078 /* And finally, the indices and operands of ARRAY_REF. During this
3079 loop we also remove any useless conversions. */
3080 for (; expr_stack.length () > 0; )
3082 tree t = expr_stack.pop ();
3084 if (TREE_CODE (t) == ARRAY_REF || TREE_CODE (t) == ARRAY_RANGE_REF)
3086 /* Gimplify the dimension. */
3087 if (!is_gimple_min_invariant (TREE_OPERAND (t, 1)))
3089 tret = gimplify_expr (&TREE_OPERAND (t, 1), pre_p, post_p,
3090 is_gimple_val, fb_rvalue);
3091 ret = MIN (ret, tret);
3095 STRIP_USELESS_TYPE_CONVERSION (TREE_OPERAND (t, 0));
3097 /* The innermost expression P may have originally had
3098 TREE_SIDE_EFFECTS set which would have caused all the outer
3099 expressions in *EXPR_P leading to P to also have had
3100 TREE_SIDE_EFFECTS set. */
3101 recalculate_side_effects (t);
3104 /* If the outermost expression is a COMPONENT_REF, canonicalize its type. */
3105 if ((fallback & fb_rvalue) && TREE_CODE (*expr_p) == COMPONENT_REF)
3107 canonicalize_component_ref (expr_p);
3110 expr_stack.release ();
3112 gcc_assert (*expr_p == expr || ret != GS_ALL_DONE);
3114 return ret;
3117 /* Gimplify the self modifying expression pointed to by EXPR_P
3118 (++, --, +=, -=).
3120 PRE_P points to the list where side effects that must happen before
3121 *EXPR_P should be stored.
3123 POST_P points to the list where side effects that must happen after
3124 *EXPR_P should be stored.
3126 WANT_VALUE is nonzero iff we want to use the value of this expression
3127 in another expression.
3129 ARITH_TYPE is the type the computation should be performed in. */
3131 enum gimplify_status
3132 gimplify_self_mod_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
3133 bool want_value, tree arith_type)
3135 enum tree_code code;
3136 tree lhs, lvalue, rhs, t1;
3137 gimple_seq post = NULL, *orig_post_p = post_p;
3138 bool postfix;
3139 enum tree_code arith_code;
3140 enum gimplify_status ret;
3141 location_t loc = EXPR_LOCATION (*expr_p);
3143 code = TREE_CODE (*expr_p);
3145 gcc_assert (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR
3146 || code == PREINCREMENT_EXPR || code == PREDECREMENT_EXPR);
3148 /* Prefix or postfix? */
3149 if (code == POSTINCREMENT_EXPR || code == POSTDECREMENT_EXPR)
3150 /* Faster to treat as prefix if result is not used. */
3151 postfix = want_value;
3152 else
3153 postfix = false;
3155 /* For postfix, make sure the inner expression's post side effects
3156 are executed after side effects from this expression. */
3157 if (postfix)
3158 post_p = &post;
3160 /* Add or subtract? */
3161 if (code == PREINCREMENT_EXPR || code == POSTINCREMENT_EXPR)
3162 arith_code = PLUS_EXPR;
3163 else
3164 arith_code = MINUS_EXPR;
3166 /* Gimplify the LHS into a GIMPLE lvalue. */
3167 lvalue = TREE_OPERAND (*expr_p, 0);
3168 ret = gimplify_expr (&lvalue, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
3169 if (ret == GS_ERROR)
3170 return ret;
3172 /* Extract the operands to the arithmetic operation. */
3173 lhs = lvalue;
3174 rhs = TREE_OPERAND (*expr_p, 1);
3176 /* For postfix operator, we evaluate the LHS to an rvalue and then use
3177 that as the result value and in the postqueue operation. */
3178 if (postfix)
3180 ret = gimplify_expr (&lhs, pre_p, post_p, is_gimple_val, fb_rvalue);
3181 if (ret == GS_ERROR)
3182 return ret;
3184 lhs = get_initialized_tmp_var (lhs, pre_p);
3187 /* For POINTERs increment, use POINTER_PLUS_EXPR. */
3188 if (POINTER_TYPE_P (TREE_TYPE (lhs)))
3190 rhs = convert_to_ptrofftype_loc (loc, rhs);
3191 if (arith_code == MINUS_EXPR)
3192 rhs = fold_build1_loc (loc, NEGATE_EXPR, TREE_TYPE (rhs), rhs);
3193 t1 = fold_build2 (POINTER_PLUS_EXPR, TREE_TYPE (*expr_p), lhs, rhs);
3195 else
3196 t1 = fold_convert (TREE_TYPE (*expr_p),
3197 fold_build2 (arith_code, arith_type,
3198 fold_convert (arith_type, lhs),
3199 fold_convert (arith_type, rhs)));
3201 if (postfix)
3203 gimplify_assign (lvalue, t1, pre_p);
3204 gimplify_seq_add_seq (orig_post_p, post);
3205 *expr_p = lhs;
3206 return GS_ALL_DONE;
3208 else
3210 *expr_p = build2 (MODIFY_EXPR, TREE_TYPE (lvalue), lvalue, t1);
3211 return GS_OK;
3215 /* If *EXPR_P has a variable sized type, wrap it in a WITH_SIZE_EXPR. */
3217 static void
3218 maybe_with_size_expr (tree *expr_p)
3220 tree expr = *expr_p;
3221 tree type = TREE_TYPE (expr);
3222 tree size;
3224 /* If we've already wrapped this or the type is error_mark_node, we can't do
3225 anything. */
3226 if (TREE_CODE (expr) == WITH_SIZE_EXPR
3227 || type == error_mark_node)
3228 return;
3230 /* If the size isn't known or is a constant, we have nothing to do. */
3231 size = TYPE_SIZE_UNIT (type);
3232 if (!size || poly_int_tree_p (size))
3233 return;
3235 /* Otherwise, make a WITH_SIZE_EXPR. */
3236 size = unshare_expr (size);
3237 size = SUBSTITUTE_PLACEHOLDER_IN_EXPR (size, expr);
3238 *expr_p = build2 (WITH_SIZE_EXPR, type, expr, size);
3241 /* Helper for gimplify_call_expr. Gimplify a single argument *ARG_P
3242 Store any side-effects in PRE_P. CALL_LOCATION is the location of
3243 the CALL_EXPR. If ALLOW_SSA is set the actual parameter may be
3244 gimplified to an SSA name. */
3246 enum gimplify_status
3247 gimplify_arg (tree *arg_p, gimple_seq *pre_p, location_t call_location,
3248 bool allow_ssa)
3250 bool (*test) (tree);
3251 fallback_t fb;
3253 /* In general, we allow lvalues for function arguments to avoid
3254 extra overhead of copying large aggregates out of even larger
3255 aggregates into temporaries only to copy the temporaries to
3256 the argument list. Make optimizers happy by pulling out to
3257 temporaries those types that fit in registers. */
3258 if (is_gimple_reg_type (TREE_TYPE (*arg_p)))
3259 test = is_gimple_val, fb = fb_rvalue;
3260 else
3262 test = is_gimple_lvalue, fb = fb_either;
3263 /* Also strip a TARGET_EXPR that would force an extra copy. */
3264 if (TREE_CODE (*arg_p) == TARGET_EXPR)
3266 tree init = TARGET_EXPR_INITIAL (*arg_p);
3267 if (init
3268 && !VOID_TYPE_P (TREE_TYPE (init)))
3269 *arg_p = init;
3273 /* If this is a variable sized type, we must remember the size. */
3274 maybe_with_size_expr (arg_p);
3276 /* FIXME diagnostics: This will mess up gcc.dg/Warray-bounds.c. */
3277 /* Make sure arguments have the same location as the function call
3278 itself. */
3279 protected_set_expr_location (*arg_p, call_location);
3281 /* There is a sequence point before a function call. Side effects in
3282 the argument list must occur before the actual call. So, when
3283 gimplifying arguments, force gimplify_expr to use an internal
3284 post queue which is then appended to the end of PRE_P. */
3285 return gimplify_expr (arg_p, pre_p, NULL, test, fb, allow_ssa);
3288 /* Don't fold inside offloading or taskreg regions: it can break code by
3289 adding decl references that weren't in the source. We'll do it during
3290 omplower pass instead. */
3292 static bool
3293 maybe_fold_stmt (gimple_stmt_iterator *gsi)
3295 struct gimplify_omp_ctx *ctx;
3296 for (ctx = gimplify_omp_ctxp; ctx; ctx = ctx->outer_context)
3297 if ((ctx->region_type & (ORT_TARGET | ORT_PARALLEL | ORT_TASK)) != 0)
3298 return false;
3299 else if ((ctx->region_type & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
3300 return false;
3301 /* Delay folding of builtins until the IL is in consistent state
3302 so the diagnostic machinery can do a better job. */
3303 if (gimple_call_builtin_p (gsi_stmt (*gsi)))
3304 return false;
3305 return fold_stmt (gsi);
3308 /* Gimplify the CALL_EXPR node *EXPR_P into the GIMPLE sequence PRE_P.
3309 WANT_VALUE is true if the result of the call is desired. */
3311 static enum gimplify_status
3312 gimplify_call_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
3314 tree fndecl, parms, p, fnptrtype;
3315 enum gimplify_status ret;
3316 int i, nargs;
3317 gcall *call;
3318 bool builtin_va_start_p = false;
3319 location_t loc = EXPR_LOCATION (*expr_p);
3321 gcc_assert (TREE_CODE (*expr_p) == CALL_EXPR);
3323 /* For reliable diagnostics during inlining, it is necessary that
3324 every call_expr be annotated with file and line. */
3325 if (! EXPR_HAS_LOCATION (*expr_p))
3326 SET_EXPR_LOCATION (*expr_p, input_location);
3328 /* Gimplify internal functions created in the FEs. */
3329 if (CALL_EXPR_FN (*expr_p) == NULL_TREE)
3331 if (want_value)
3332 return GS_ALL_DONE;
3334 nargs = call_expr_nargs (*expr_p);
3335 enum internal_fn ifn = CALL_EXPR_IFN (*expr_p);
3336 auto_vec<tree> vargs (nargs);
3338 for (i = 0; i < nargs; i++)
3340 gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
3341 EXPR_LOCATION (*expr_p));
3342 vargs.quick_push (CALL_EXPR_ARG (*expr_p, i));
3345 gcall *call = gimple_build_call_internal_vec (ifn, vargs);
3346 gimple_call_set_nothrow (call, TREE_NOTHROW (*expr_p));
3347 gimplify_seq_add_stmt (pre_p, call);
3348 return GS_ALL_DONE;
3351 /* This may be a call to a builtin function.
3353 Builtin function calls may be transformed into different
3354 (and more efficient) builtin function calls under certain
3355 circumstances. Unfortunately, gimplification can muck things
3356 up enough that the builtin expanders are not aware that certain
3357 transformations are still valid.
3359 So we attempt transformation/gimplification of the call before
3360 we gimplify the CALL_EXPR. At this time we do not manage to
3361 transform all calls in the same manner as the expanders do, but
3362 we do transform most of them. */
3363 fndecl = get_callee_fndecl (*expr_p);
3364 if (fndecl && fndecl_built_in_p (fndecl, BUILT_IN_NORMAL))
3365 switch (DECL_FUNCTION_CODE (fndecl))
3367 CASE_BUILT_IN_ALLOCA:
3368 /* If the call has been built for a variable-sized object, then we
3369 want to restore the stack level when the enclosing BIND_EXPR is
3370 exited to reclaim the allocated space; otherwise, we precisely
3371 need to do the opposite and preserve the latest stack level. */
3372 if (CALL_ALLOCA_FOR_VAR_P (*expr_p))
3373 gimplify_ctxp->save_stack = true;
3374 else
3375 gimplify_ctxp->keep_stack = true;
3376 break;
3378 case BUILT_IN_VA_START:
3380 builtin_va_start_p = TRUE;
3381 if (call_expr_nargs (*expr_p) < 2)
3383 error ("too few arguments to function %<va_start%>");
3384 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
3385 return GS_OK;
3388 if (fold_builtin_next_arg (*expr_p, true))
3390 *expr_p = build_empty_stmt (EXPR_LOCATION (*expr_p));
3391 return GS_OK;
3393 break;
3396 case BUILT_IN_EH_RETURN:
3397 cfun->calls_eh_return = true;
3398 break;
3400 case BUILT_IN_CLEAR_PADDING:
3401 if (call_expr_nargs (*expr_p) == 1)
3403 /* Remember the original type of the argument in an internal
3404 dummy second argument, as in GIMPLE pointer conversions are
3405 useless. */
3406 p = CALL_EXPR_ARG (*expr_p, 0);
3407 *expr_p
3408 = build_call_expr_loc (EXPR_LOCATION (*expr_p), fndecl, 2, p,
3409 build_zero_cst (TREE_TYPE (p)));
3410 return GS_OK;
3412 break;
3414 default:
3417 if (fndecl && fndecl_built_in_p (fndecl))
3419 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
3420 if (new_tree && new_tree != *expr_p)
3422 /* There was a transformation of this call which computes the
3423 same value, but in a more efficient way. Return and try
3424 again. */
3425 *expr_p = new_tree;
3426 return GS_OK;
3430 /* Remember the original function pointer type. */
3431 fnptrtype = TREE_TYPE (CALL_EXPR_FN (*expr_p));
3433 if (flag_openmp
3434 && fndecl
3435 && cfun
3436 && (cfun->curr_properties & PROP_gimple_any) == 0)
3438 tree variant = omp_resolve_declare_variant (fndecl);
3439 if (variant != fndecl)
3440 CALL_EXPR_FN (*expr_p) = build1 (ADDR_EXPR, fnptrtype, variant);
3443 /* There is a sequence point before the call, so any side effects in
3444 the calling expression must occur before the actual call. Force
3445 gimplify_expr to use an internal post queue. */
3446 ret = gimplify_expr (&CALL_EXPR_FN (*expr_p), pre_p, NULL,
3447 is_gimple_call_addr, fb_rvalue);
3449 nargs = call_expr_nargs (*expr_p);
3451 /* Get argument types for verification. */
3452 fndecl = get_callee_fndecl (*expr_p);
3453 parms = NULL_TREE;
3454 if (fndecl)
3455 parms = TYPE_ARG_TYPES (TREE_TYPE (fndecl));
3456 else
3457 parms = TYPE_ARG_TYPES (TREE_TYPE (fnptrtype));
3459 if (fndecl && DECL_ARGUMENTS (fndecl))
3460 p = DECL_ARGUMENTS (fndecl);
3461 else if (parms)
3462 p = parms;
3463 else
3464 p = NULL_TREE;
3465 for (i = 0; i < nargs && p; i++, p = TREE_CHAIN (p))
3468 /* If the last argument is __builtin_va_arg_pack () and it is not
3469 passed as a named argument, decrease the number of CALL_EXPR
3470 arguments and set instead the CALL_EXPR_VA_ARG_PACK flag. */
3471 if (!p
3472 && i < nargs
3473 && TREE_CODE (CALL_EXPR_ARG (*expr_p, nargs - 1)) == CALL_EXPR)
3475 tree last_arg = CALL_EXPR_ARG (*expr_p, nargs - 1);
3476 tree last_arg_fndecl = get_callee_fndecl (last_arg);
3478 if (last_arg_fndecl
3479 && fndecl_built_in_p (last_arg_fndecl, BUILT_IN_VA_ARG_PACK))
3481 tree call = *expr_p;
3483 --nargs;
3484 *expr_p = build_call_array_loc (loc, TREE_TYPE (call),
3485 CALL_EXPR_FN (call),
3486 nargs, CALL_EXPR_ARGP (call));
3488 /* Copy all CALL_EXPR flags, location and block, except
3489 CALL_EXPR_VA_ARG_PACK flag. */
3490 CALL_EXPR_STATIC_CHAIN (*expr_p) = CALL_EXPR_STATIC_CHAIN (call);
3491 CALL_EXPR_TAILCALL (*expr_p) = CALL_EXPR_TAILCALL (call);
3492 CALL_EXPR_RETURN_SLOT_OPT (*expr_p)
3493 = CALL_EXPR_RETURN_SLOT_OPT (call);
3494 CALL_FROM_THUNK_P (*expr_p) = CALL_FROM_THUNK_P (call);
3495 SET_EXPR_LOCATION (*expr_p, EXPR_LOCATION (call));
3497 /* Set CALL_EXPR_VA_ARG_PACK. */
3498 CALL_EXPR_VA_ARG_PACK (*expr_p) = 1;
3502 /* If the call returns twice then after building the CFG the call
3503 argument computations will no longer dominate the call because
3504 we add an abnormal incoming edge to the call. So do not use SSA
3505 vars there. */
3506 bool returns_twice = call_expr_flags (*expr_p) & ECF_RETURNS_TWICE;
3508 /* Gimplify the function arguments. */
3509 if (nargs > 0)
3511 for (i = (PUSH_ARGS_REVERSED ? nargs - 1 : 0);
3512 PUSH_ARGS_REVERSED ? i >= 0 : i < nargs;
3513 PUSH_ARGS_REVERSED ? i-- : i++)
3515 enum gimplify_status t;
3517 /* Avoid gimplifying the second argument to va_start, which needs to
3518 be the plain PARM_DECL. */
3519 if ((i != 1) || !builtin_va_start_p)
3521 t = gimplify_arg (&CALL_EXPR_ARG (*expr_p, i), pre_p,
3522 EXPR_LOCATION (*expr_p), ! returns_twice);
3524 if (t == GS_ERROR)
3525 ret = GS_ERROR;
3530 /* Gimplify the static chain. */
3531 if (CALL_EXPR_STATIC_CHAIN (*expr_p))
3533 if (fndecl && !DECL_STATIC_CHAIN (fndecl))
3534 CALL_EXPR_STATIC_CHAIN (*expr_p) = NULL;
3535 else
3537 enum gimplify_status t;
3538 t = gimplify_arg (&CALL_EXPR_STATIC_CHAIN (*expr_p), pre_p,
3539 EXPR_LOCATION (*expr_p), ! returns_twice);
3540 if (t == GS_ERROR)
3541 ret = GS_ERROR;
3545 /* Verify the function result. */
3546 if (want_value && fndecl
3547 && VOID_TYPE_P (TREE_TYPE (TREE_TYPE (fnptrtype))))
3549 error_at (loc, "using result of function returning %<void%>");
3550 ret = GS_ERROR;
3553 /* Try this again in case gimplification exposed something. */
3554 if (ret != GS_ERROR)
3556 tree new_tree = fold_call_expr (input_location, *expr_p, !want_value);
3558 if (new_tree && new_tree != *expr_p)
3560 /* There was a transformation of this call which computes the
3561 same value, but in a more efficient way. Return and try
3562 again. */
3563 *expr_p = new_tree;
3564 return GS_OK;
3567 else
3569 *expr_p = error_mark_node;
3570 return GS_ERROR;
3573 /* If the function is "const" or "pure", then clear TREE_SIDE_EFFECTS on its
3574 decl. This allows us to eliminate redundant or useless
3575 calls to "const" functions. */
3576 if (TREE_CODE (*expr_p) == CALL_EXPR)
3578 int flags = call_expr_flags (*expr_p);
3579 if (flags & (ECF_CONST | ECF_PURE)
3580 /* An infinite loop is considered a side effect. */
3581 && !(flags & (ECF_LOOPING_CONST_OR_PURE)))
3582 TREE_SIDE_EFFECTS (*expr_p) = 0;
3585 /* If the value is not needed by the caller, emit a new GIMPLE_CALL
3586 and clear *EXPR_P. Otherwise, leave *EXPR_P in its gimplified
3587 form and delegate the creation of a GIMPLE_CALL to
3588 gimplify_modify_expr. This is always possible because when
3589 WANT_VALUE is true, the caller wants the result of this call into
3590 a temporary, which means that we will emit an INIT_EXPR in
3591 internal_get_tmp_var which will then be handled by
3592 gimplify_modify_expr. */
3593 if (!want_value)
3595 /* The CALL_EXPR in *EXPR_P is already in GIMPLE form, so all we
3596 have to do is replicate it as a GIMPLE_CALL tuple. */
3597 gimple_stmt_iterator gsi;
3598 call = gimple_build_call_from_tree (*expr_p, fnptrtype);
3599 notice_special_calls (call);
3600 gimplify_seq_add_stmt (pre_p, call);
3601 gsi = gsi_last (*pre_p);
3602 maybe_fold_stmt (&gsi);
3603 *expr_p = NULL_TREE;
3605 else
3606 /* Remember the original function type. */
3607 CALL_EXPR_FN (*expr_p) = build1 (NOP_EXPR, fnptrtype,
3608 CALL_EXPR_FN (*expr_p));
3610 return ret;
3613 /* Handle shortcut semantics in the predicate operand of a COND_EXPR by
3614 rewriting it into multiple COND_EXPRs, and possibly GOTO_EXPRs.
3616 TRUE_LABEL_P and FALSE_LABEL_P point to the labels to jump to if the
3617 condition is true or false, respectively. If null, we should generate
3618 our own to skip over the evaluation of this specific expression.
3620 LOCUS is the source location of the COND_EXPR.
3622 This function is the tree equivalent of do_jump.
3624 shortcut_cond_r should only be called by shortcut_cond_expr. */
3626 static tree
3627 shortcut_cond_r (tree pred, tree *true_label_p, tree *false_label_p,
3628 location_t locus)
3630 tree local_label = NULL_TREE;
3631 tree t, expr = NULL;
3633 /* OK, it's not a simple case; we need to pull apart the COND_EXPR to
3634 retain the shortcut semantics. Just insert the gotos here;
3635 shortcut_cond_expr will append the real blocks later. */
3636 if (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
3638 location_t new_locus;
3640 /* Turn if (a && b) into
3642 if (a); else goto no;
3643 if (b) goto yes; else goto no;
3644 (no:) */
3646 if (false_label_p == NULL)
3647 false_label_p = &local_label;
3649 /* Keep the original source location on the first 'if'. */
3650 t = shortcut_cond_r (TREE_OPERAND (pred, 0), NULL, false_label_p, locus);
3651 append_to_statement_list (t, &expr);
3653 /* Set the source location of the && on the second 'if'. */
3654 new_locus = rexpr_location (pred, locus);
3655 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
3656 new_locus);
3657 append_to_statement_list (t, &expr);
3659 else if (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
3661 location_t new_locus;
3663 /* Turn if (a || b) into
3665 if (a) goto yes;
3666 if (b) goto yes; else goto no;
3667 (yes:) */
3669 if (true_label_p == NULL)
3670 true_label_p = &local_label;
3672 /* Keep the original source location on the first 'if'. */
3673 t = shortcut_cond_r (TREE_OPERAND (pred, 0), true_label_p, NULL, locus);
3674 append_to_statement_list (t, &expr);
3676 /* Set the source location of the || on the second 'if'. */
3677 new_locus = rexpr_location (pred, locus);
3678 t = shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p, false_label_p,
3679 new_locus);
3680 append_to_statement_list (t, &expr);
3682 else if (TREE_CODE (pred) == COND_EXPR
3683 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 1)))
3684 && !VOID_TYPE_P (TREE_TYPE (TREE_OPERAND (pred, 2))))
3686 location_t new_locus;
3688 /* As long as we're messing with gotos, turn if (a ? b : c) into
3689 if (a)
3690 if (b) goto yes; else goto no;
3691 else
3692 if (c) goto yes; else goto no;
3694 Don't do this if one of the arms has void type, which can happen
3695 in C++ when the arm is throw. */
3697 /* Keep the original source location on the first 'if'. Set the source
3698 location of the ? on the second 'if'. */
3699 new_locus = rexpr_location (pred, locus);
3700 expr = build3 (COND_EXPR, void_type_node, TREE_OPERAND (pred, 0),
3701 shortcut_cond_r (TREE_OPERAND (pred, 1), true_label_p,
3702 false_label_p, locus),
3703 shortcut_cond_r (TREE_OPERAND (pred, 2), true_label_p,
3704 false_label_p, new_locus));
3706 else
3708 expr = build3 (COND_EXPR, void_type_node, pred,
3709 build_and_jump (true_label_p),
3710 build_and_jump (false_label_p));
3711 SET_EXPR_LOCATION (expr, locus);
3714 if (local_label)
3716 t = build1 (LABEL_EXPR, void_type_node, local_label);
3717 append_to_statement_list (t, &expr);
3720 return expr;
3723 /* If EXPR is a GOTO_EXPR, return it. If it is a STATEMENT_LIST, skip
3724 any of its leading DEBUG_BEGIN_STMTS and recurse on the subsequent
3725 statement, if it is the last one. Otherwise, return NULL. */
3727 static tree
3728 find_goto (tree expr)
3730 if (!expr)
3731 return NULL_TREE;
3733 if (TREE_CODE (expr) == GOTO_EXPR)
3734 return expr;
3736 if (TREE_CODE (expr) != STATEMENT_LIST)
3737 return NULL_TREE;
3739 tree_stmt_iterator i = tsi_start (expr);
3741 while (!tsi_end_p (i) && TREE_CODE (tsi_stmt (i)) == DEBUG_BEGIN_STMT)
3742 tsi_next (&i);
3744 if (!tsi_one_before_end_p (i))
3745 return NULL_TREE;
3747 return find_goto (tsi_stmt (i));
3750 /* Same as find_goto, except that it returns NULL if the destination
3751 is not a LABEL_DECL. */
3753 static inline tree
3754 find_goto_label (tree expr)
3756 tree dest = find_goto (expr);
3757 if (dest && TREE_CODE (GOTO_DESTINATION (dest)) == LABEL_DECL)
3758 return dest;
3759 return NULL_TREE;
3762 /* Given a conditional expression EXPR with short-circuit boolean
3763 predicates using TRUTH_ANDIF_EXPR or TRUTH_ORIF_EXPR, break the
3764 predicate apart into the equivalent sequence of conditionals. */
3766 static tree
3767 shortcut_cond_expr (tree expr)
3769 tree pred = TREE_OPERAND (expr, 0);
3770 tree then_ = TREE_OPERAND (expr, 1);
3771 tree else_ = TREE_OPERAND (expr, 2);
3772 tree true_label, false_label, end_label, t;
3773 tree *true_label_p;
3774 tree *false_label_p;
3775 bool emit_end, emit_false, jump_over_else;
3776 bool then_se = then_ && TREE_SIDE_EFFECTS (then_);
3777 bool else_se = else_ && TREE_SIDE_EFFECTS (else_);
3779 /* First do simple transformations. */
3780 if (!else_se)
3782 /* If there is no 'else', turn
3783 if (a && b) then c
3784 into
3785 if (a) if (b) then c. */
3786 while (TREE_CODE (pred) == TRUTH_ANDIF_EXPR)
3788 /* Keep the original source location on the first 'if'. */
3789 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
3790 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
3791 /* Set the source location of the && on the second 'if'. */
3792 if (rexpr_has_location (pred))
3793 SET_EXPR_LOCATION (expr, rexpr_location (pred));
3794 then_ = shortcut_cond_expr (expr);
3795 then_se = then_ && TREE_SIDE_EFFECTS (then_);
3796 pred = TREE_OPERAND (pred, 0);
3797 expr = build3 (COND_EXPR, void_type_node, pred, then_, NULL_TREE);
3798 SET_EXPR_LOCATION (expr, locus);
3802 if (!then_se)
3804 /* If there is no 'then', turn
3805 if (a || b); else d
3806 into
3807 if (a); else if (b); else d. */
3808 while (TREE_CODE (pred) == TRUTH_ORIF_EXPR)
3810 /* Keep the original source location on the first 'if'. */
3811 location_t locus = EXPR_LOC_OR_LOC (expr, input_location);
3812 TREE_OPERAND (expr, 0) = TREE_OPERAND (pred, 1);
3813 /* Set the source location of the || on the second 'if'. */
3814 if (rexpr_has_location (pred))
3815 SET_EXPR_LOCATION (expr, rexpr_location (pred));
3816 else_ = shortcut_cond_expr (expr);
3817 else_se = else_ && TREE_SIDE_EFFECTS (else_);
3818 pred = TREE_OPERAND (pred, 0);
3819 expr = build3 (COND_EXPR, void_type_node, pred, NULL_TREE, else_);
3820 SET_EXPR_LOCATION (expr, locus);
3824 /* If we're done, great. */
3825 if (TREE_CODE (pred) != TRUTH_ANDIF_EXPR
3826 && TREE_CODE (pred) != TRUTH_ORIF_EXPR)
3827 return expr;
3829 /* Otherwise we need to mess with gotos. Change
3830 if (a) c; else d;
3832 if (a); else goto no;
3833 c; goto end;
3834 no: d; end:
3835 and recursively gimplify the condition. */
3837 true_label = false_label = end_label = NULL_TREE;
3839 /* If our arms just jump somewhere, hijack those labels so we don't
3840 generate jumps to jumps. */
3842 if (tree then_goto = find_goto_label (then_))
3844 true_label = GOTO_DESTINATION (then_goto);
3845 then_ = NULL;
3846 then_se = false;
3849 if (tree else_goto = find_goto_label (else_))
3851 false_label = GOTO_DESTINATION (else_goto);
3852 else_ = NULL;
3853 else_se = false;
3856 /* If we aren't hijacking a label for the 'then' branch, it falls through. */
3857 if (true_label)
3858 true_label_p = &true_label;
3859 else
3860 true_label_p = NULL;
3862 /* The 'else' branch also needs a label if it contains interesting code. */
3863 if (false_label || else_se)
3864 false_label_p = &false_label;
3865 else
3866 false_label_p = NULL;
3868 /* If there was nothing else in our arms, just forward the label(s). */
3869 if (!then_se && !else_se)
3870 return shortcut_cond_r (pred, true_label_p, false_label_p,
3871 EXPR_LOC_OR_LOC (expr, input_location));
3873 /* If our last subexpression already has a terminal label, reuse it. */
3874 if (else_se)
3875 t = expr_last (else_);
3876 else if (then_se)
3877 t = expr_last (then_);
3878 else
3879 t = NULL;
3880 if (t && TREE_CODE (t) == LABEL_EXPR)
3881 end_label = LABEL_EXPR_LABEL (t);
3883 /* If we don't care about jumping to the 'else' branch, jump to the end
3884 if the condition is false. */
3885 if (!false_label_p)
3886 false_label_p = &end_label;
3888 /* We only want to emit these labels if we aren't hijacking them. */
3889 emit_end = (end_label == NULL_TREE);
3890 emit_false = (false_label == NULL_TREE);
3892 /* We only emit the jump over the else clause if we have to--if the
3893 then clause may fall through. Otherwise we can wind up with a
3894 useless jump and a useless label at the end of gimplified code,
3895 which will cause us to think that this conditional as a whole
3896 falls through even if it doesn't. If we then inline a function
3897 which ends with such a condition, that can cause us to issue an
3898 inappropriate warning about control reaching the end of a
3899 non-void function. */
3900 jump_over_else = block_may_fallthru (then_);
3902 pred = shortcut_cond_r (pred, true_label_p, false_label_p,
3903 EXPR_LOC_OR_LOC (expr, input_location));
3905 expr = NULL;
3906 append_to_statement_list (pred, &expr);
3908 append_to_statement_list (then_, &expr);
3909 if (else_se)
3911 if (jump_over_else)
3913 tree last = expr_last (expr);
3914 t = build_and_jump (&end_label);
3915 if (rexpr_has_location (last))
3916 SET_EXPR_LOCATION (t, rexpr_location (last));
3917 append_to_statement_list (t, &expr);
3919 if (emit_false)
3921 t = build1 (LABEL_EXPR, void_type_node, false_label);
3922 append_to_statement_list (t, &expr);
3924 append_to_statement_list (else_, &expr);
3926 if (emit_end && end_label)
3928 t = build1 (LABEL_EXPR, void_type_node, end_label);
3929 append_to_statement_list (t, &expr);
3932 return expr;
3935 /* EXPR is used in a boolean context; make sure it has BOOLEAN_TYPE. */
3937 tree
3938 gimple_boolify (tree expr)
3940 tree type = TREE_TYPE (expr);
3941 location_t loc = EXPR_LOCATION (expr);
3943 if (TREE_CODE (expr) == NE_EXPR
3944 && TREE_CODE (TREE_OPERAND (expr, 0)) == CALL_EXPR
3945 && integer_zerop (TREE_OPERAND (expr, 1)))
3947 tree call = TREE_OPERAND (expr, 0);
3948 tree fn = get_callee_fndecl (call);
3950 /* For __builtin_expect ((long) (x), y) recurse into x as well
3951 if x is truth_value_p. */
3952 if (fn
3953 && fndecl_built_in_p (fn, BUILT_IN_EXPECT)
3954 && call_expr_nargs (call) == 2)
3956 tree arg = CALL_EXPR_ARG (call, 0);
3957 if (arg)
3959 if (TREE_CODE (arg) == NOP_EXPR
3960 && TREE_TYPE (arg) == TREE_TYPE (call))
3961 arg = TREE_OPERAND (arg, 0);
3962 if (truth_value_p (TREE_CODE (arg)))
3964 arg = gimple_boolify (arg);
3965 CALL_EXPR_ARG (call, 0)
3966 = fold_convert_loc (loc, TREE_TYPE (call), arg);
3972 switch (TREE_CODE (expr))
3974 case TRUTH_AND_EXPR:
3975 case TRUTH_OR_EXPR:
3976 case TRUTH_XOR_EXPR:
3977 case TRUTH_ANDIF_EXPR:
3978 case TRUTH_ORIF_EXPR:
3979 /* Also boolify the arguments of truth exprs. */
3980 TREE_OPERAND (expr, 1) = gimple_boolify (TREE_OPERAND (expr, 1));
3981 /* FALLTHRU */
3983 case TRUTH_NOT_EXPR:
3984 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
3986 /* These expressions always produce boolean results. */
3987 if (TREE_CODE (type) != BOOLEAN_TYPE)
3988 TREE_TYPE (expr) = boolean_type_node;
3989 return expr;
3991 case ANNOTATE_EXPR:
3992 switch ((enum annot_expr_kind) TREE_INT_CST_LOW (TREE_OPERAND (expr, 1)))
3994 case annot_expr_ivdep_kind:
3995 case annot_expr_unroll_kind:
3996 case annot_expr_no_vector_kind:
3997 case annot_expr_vector_kind:
3998 case annot_expr_parallel_kind:
3999 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
4000 if (TREE_CODE (type) != BOOLEAN_TYPE)
4001 TREE_TYPE (expr) = boolean_type_node;
4002 return expr;
4003 default:
4004 gcc_unreachable ();
4007 default:
4008 if (COMPARISON_CLASS_P (expr))
4010 /* There expressions always prduce boolean results. */
4011 if (TREE_CODE (type) != BOOLEAN_TYPE)
4012 TREE_TYPE (expr) = boolean_type_node;
4013 return expr;
4015 /* Other expressions that get here must have boolean values, but
4016 might need to be converted to the appropriate mode. */
4017 if (TREE_CODE (type) == BOOLEAN_TYPE)
4018 return expr;
4019 return fold_convert_loc (loc, boolean_type_node, expr);
4023 /* Given a conditional expression *EXPR_P without side effects, gimplify
4024 its operands. New statements are inserted to PRE_P. */
4026 static enum gimplify_status
4027 gimplify_pure_cond_expr (tree *expr_p, gimple_seq *pre_p)
4029 tree expr = *expr_p, cond;
4030 enum gimplify_status ret, tret;
4031 enum tree_code code;
4033 cond = gimple_boolify (COND_EXPR_COND (expr));
4035 /* We need to handle && and || specially, as their gimplification
4036 creates pure cond_expr, thus leading to an infinite cycle otherwise. */
4037 code = TREE_CODE (cond);
4038 if (code == TRUTH_ANDIF_EXPR)
4039 TREE_SET_CODE (cond, TRUTH_AND_EXPR);
4040 else if (code == TRUTH_ORIF_EXPR)
4041 TREE_SET_CODE (cond, TRUTH_OR_EXPR);
4042 ret = gimplify_expr (&cond, pre_p, NULL, is_gimple_condexpr, fb_rvalue);
4043 COND_EXPR_COND (*expr_p) = cond;
4045 tret = gimplify_expr (&COND_EXPR_THEN (expr), pre_p, NULL,
4046 is_gimple_val, fb_rvalue);
4047 ret = MIN (ret, tret);
4048 tret = gimplify_expr (&COND_EXPR_ELSE (expr), pre_p, NULL,
4049 is_gimple_val, fb_rvalue);
4051 return MIN (ret, tret);
4054 /* Return true if evaluating EXPR could trap.
4055 EXPR is GENERIC, while tree_could_trap_p can be called
4056 only on GIMPLE. */
4058 bool
4059 generic_expr_could_trap_p (tree expr)
4061 unsigned i, n;
4063 if (!expr || is_gimple_val (expr))
4064 return false;
4066 if (!EXPR_P (expr) || tree_could_trap_p (expr))
4067 return true;
4069 n = TREE_OPERAND_LENGTH (expr);
4070 for (i = 0; i < n; i++)
4071 if (generic_expr_could_trap_p (TREE_OPERAND (expr, i)))
4072 return true;
4074 return false;
4077 /* Convert the conditional expression pointed to by EXPR_P '(p) ? a : b;'
4078 into
4080 if (p) if (p)
4081 t1 = a; a;
4082 else or else
4083 t1 = b; b;
4086 The second form is used when *EXPR_P is of type void.
4088 PRE_P points to the list where side effects that must happen before
4089 *EXPR_P should be stored. */
4091 static enum gimplify_status
4092 gimplify_cond_expr (tree *expr_p, gimple_seq *pre_p, fallback_t fallback)
4094 tree expr = *expr_p;
4095 tree type = TREE_TYPE (expr);
4096 location_t loc = EXPR_LOCATION (expr);
4097 tree tmp, arm1, arm2;
4098 enum gimplify_status ret;
4099 tree label_true, label_false, label_cont;
4100 bool have_then_clause_p, have_else_clause_p;
4101 gcond *cond_stmt;
4102 enum tree_code pred_code;
4103 gimple_seq seq = NULL;
4105 /* If this COND_EXPR has a value, copy the values into a temporary within
4106 the arms. */
4107 if (!VOID_TYPE_P (type))
4109 tree then_ = TREE_OPERAND (expr, 1), else_ = TREE_OPERAND (expr, 2);
4110 tree result;
4112 /* If either an rvalue is ok or we do not require an lvalue, create the
4113 temporary. But we cannot do that if the type is addressable. */
4114 if (((fallback & fb_rvalue) || !(fallback & fb_lvalue))
4115 && !TREE_ADDRESSABLE (type))
4117 if (gimplify_ctxp->allow_rhs_cond_expr
4118 /* If either branch has side effects or could trap, it can't be
4119 evaluated unconditionally. */
4120 && !TREE_SIDE_EFFECTS (then_)
4121 && !generic_expr_could_trap_p (then_)
4122 && !TREE_SIDE_EFFECTS (else_)
4123 && !generic_expr_could_trap_p (else_))
4124 return gimplify_pure_cond_expr (expr_p, pre_p);
4126 tmp = create_tmp_var (type, "iftmp");
4127 result = tmp;
4130 /* Otherwise, only create and copy references to the values. */
4131 else
4133 type = build_pointer_type (type);
4135 if (!VOID_TYPE_P (TREE_TYPE (then_)))
4136 then_ = build_fold_addr_expr_loc (loc, then_);
4138 if (!VOID_TYPE_P (TREE_TYPE (else_)))
4139 else_ = build_fold_addr_expr_loc (loc, else_);
4141 expr
4142 = build3 (COND_EXPR, type, TREE_OPERAND (expr, 0), then_, else_);
4144 tmp = create_tmp_var (type, "iftmp");
4145 result = build_simple_mem_ref_loc (loc, tmp);
4148 /* Build the new then clause, `tmp = then_;'. But don't build the
4149 assignment if the value is void; in C++ it can be if it's a throw. */
4150 if (!VOID_TYPE_P (TREE_TYPE (then_)))
4151 TREE_OPERAND (expr, 1) = build2 (INIT_EXPR, type, tmp, then_);
4153 /* Similarly, build the new else clause, `tmp = else_;'. */
4154 if (!VOID_TYPE_P (TREE_TYPE (else_)))
4155 TREE_OPERAND (expr, 2) = build2 (INIT_EXPR, type, tmp, else_);
4157 TREE_TYPE (expr) = void_type_node;
4158 recalculate_side_effects (expr);
4160 /* Move the COND_EXPR to the prequeue. */
4161 gimplify_stmt (&expr, pre_p);
4163 *expr_p = result;
4164 return GS_ALL_DONE;
4167 /* Remove any COMPOUND_EXPR so the following cases will be caught. */
4168 STRIP_TYPE_NOPS (TREE_OPERAND (expr, 0));
4169 if (TREE_CODE (TREE_OPERAND (expr, 0)) == COMPOUND_EXPR)
4170 gimplify_compound_expr (&TREE_OPERAND (expr, 0), pre_p, true);
4172 /* Make sure the condition has BOOLEAN_TYPE. */
4173 TREE_OPERAND (expr, 0) = gimple_boolify (TREE_OPERAND (expr, 0));
4175 /* Break apart && and || conditions. */
4176 if (TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ANDIF_EXPR
4177 || TREE_CODE (TREE_OPERAND (expr, 0)) == TRUTH_ORIF_EXPR)
4179 expr = shortcut_cond_expr (expr);
4181 if (expr != *expr_p)
4183 *expr_p = expr;
4185 /* We can't rely on gimplify_expr to re-gimplify the expanded
4186 form properly, as cleanups might cause the target labels to be
4187 wrapped in a TRY_FINALLY_EXPR. To prevent that, we need to
4188 set up a conditional context. */
4189 gimple_push_condition ();
4190 gimplify_stmt (expr_p, &seq);
4191 gimple_pop_condition (pre_p);
4192 gimple_seq_add_seq (pre_p, seq);
4194 return GS_ALL_DONE;
4198 /* Now do the normal gimplification. */
4200 /* Gimplify condition. */
4201 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, NULL,
4202 is_gimple_condexpr_for_cond, fb_rvalue);
4203 if (ret == GS_ERROR)
4204 return GS_ERROR;
4205 gcc_assert (TREE_OPERAND (expr, 0) != NULL_TREE);
4207 gimple_push_condition ();
4209 have_then_clause_p = have_else_clause_p = false;
4210 label_true = find_goto_label (TREE_OPERAND (expr, 1));
4211 if (label_true
4212 && DECL_CONTEXT (GOTO_DESTINATION (label_true)) == current_function_decl
4213 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
4214 have different locations, otherwise we end up with incorrect
4215 location information on the branches. */
4216 && (optimize
4217 || !EXPR_HAS_LOCATION (expr)
4218 || !rexpr_has_location (label_true)
4219 || EXPR_LOCATION (expr) == rexpr_location (label_true)))
4221 have_then_clause_p = true;
4222 label_true = GOTO_DESTINATION (label_true);
4224 else
4225 label_true = create_artificial_label (UNKNOWN_LOCATION);
4226 label_false = find_goto_label (TREE_OPERAND (expr, 2));
4227 if (label_false
4228 && DECL_CONTEXT (GOTO_DESTINATION (label_false)) == current_function_decl
4229 /* For -O0 avoid this optimization if the COND_EXPR and GOTO_EXPR
4230 have different locations, otherwise we end up with incorrect
4231 location information on the branches. */
4232 && (optimize
4233 || !EXPR_HAS_LOCATION (expr)
4234 || !rexpr_has_location (label_false)
4235 || EXPR_LOCATION (expr) == rexpr_location (label_false)))
4237 have_else_clause_p = true;
4238 label_false = GOTO_DESTINATION (label_false);
4240 else
4241 label_false = create_artificial_label (UNKNOWN_LOCATION);
4243 gimple_cond_get_ops_from_tree (COND_EXPR_COND (expr), &pred_code, &arm1,
4244 &arm2);
4245 cond_stmt = gimple_build_cond (pred_code, arm1, arm2, label_true,
4246 label_false);
4247 gimple_set_no_warning (cond_stmt, TREE_NO_WARNING (COND_EXPR_COND (expr)));
4248 gimplify_seq_add_stmt (&seq, cond_stmt);
4249 gimple_stmt_iterator gsi = gsi_last (seq);
4250 maybe_fold_stmt (&gsi);
4252 label_cont = NULL_TREE;
4253 if (!have_then_clause_p)
4255 /* For if (...) {} else { code; } put label_true after
4256 the else block. */
4257 if (TREE_OPERAND (expr, 1) == NULL_TREE
4258 && !have_else_clause_p
4259 && TREE_OPERAND (expr, 2) != NULL_TREE)
4260 label_cont = label_true;
4261 else
4263 gimplify_seq_add_stmt (&seq, gimple_build_label (label_true));
4264 have_then_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 1), &seq);
4265 /* For if (...) { code; } else {} or
4266 if (...) { code; } else goto label; or
4267 if (...) { code; return; } else { ... }
4268 label_cont isn't needed. */
4269 if (!have_else_clause_p
4270 && TREE_OPERAND (expr, 2) != NULL_TREE
4271 && gimple_seq_may_fallthru (seq))
4273 gimple *g;
4274 label_cont = create_artificial_label (UNKNOWN_LOCATION);
4276 g = gimple_build_goto (label_cont);
4278 /* GIMPLE_COND's are very low level; they have embedded
4279 gotos. This particular embedded goto should not be marked
4280 with the location of the original COND_EXPR, as it would
4281 correspond to the COND_EXPR's condition, not the ELSE or the
4282 THEN arms. To avoid marking it with the wrong location, flag
4283 it as "no location". */
4284 gimple_set_do_not_emit_location (g);
4286 gimplify_seq_add_stmt (&seq, g);
4290 if (!have_else_clause_p)
4292 gimplify_seq_add_stmt (&seq, gimple_build_label (label_false));
4293 have_else_clause_p = gimplify_stmt (&TREE_OPERAND (expr, 2), &seq);
4295 if (label_cont)
4296 gimplify_seq_add_stmt (&seq, gimple_build_label (label_cont));
4298 gimple_pop_condition (pre_p);
4299 gimple_seq_add_seq (pre_p, seq);
4301 if (ret == GS_ERROR)
4302 ; /* Do nothing. */
4303 else if (have_then_clause_p || have_else_clause_p)
4304 ret = GS_ALL_DONE;
4305 else
4307 /* Both arms are empty; replace the COND_EXPR with its predicate. */
4308 expr = TREE_OPERAND (expr, 0);
4309 gimplify_stmt (&expr, pre_p);
4312 *expr_p = NULL;
4313 return ret;
4316 /* Prepare the node pointed to by EXPR_P, an is_gimple_addressable expression,
4317 to be marked addressable.
4319 We cannot rely on such an expression being directly markable if a temporary
4320 has been created by the gimplification. In this case, we create another
4321 temporary and initialize it with a copy, which will become a store after we
4322 mark it addressable. This can happen if the front-end passed us something
4323 that it could not mark addressable yet, like a Fortran pass-by-reference
4324 parameter (int) floatvar. */
4326 static void
4327 prepare_gimple_addressable (tree *expr_p, gimple_seq *seq_p)
4329 while (handled_component_p (*expr_p))
4330 expr_p = &TREE_OPERAND (*expr_p, 0);
4331 if (is_gimple_reg (*expr_p))
4333 /* Do not allow an SSA name as the temporary. */
4334 tree var = get_initialized_tmp_var (*expr_p, seq_p, NULL, false);
4335 DECL_NOT_GIMPLE_REG_P (var) = 1;
4336 *expr_p = var;
4340 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
4341 a call to __builtin_memcpy. */
4343 static enum gimplify_status
4344 gimplify_modify_expr_to_memcpy (tree *expr_p, tree size, bool want_value,
4345 gimple_seq *seq_p)
4347 tree t, to, to_ptr, from, from_ptr;
4348 gcall *gs;
4349 location_t loc = EXPR_LOCATION (*expr_p);
4351 to = TREE_OPERAND (*expr_p, 0);
4352 from = TREE_OPERAND (*expr_p, 1);
4354 /* Mark the RHS addressable. Beware that it may not be possible to do so
4355 directly if a temporary has been created by the gimplification. */
4356 prepare_gimple_addressable (&from, seq_p);
4358 mark_addressable (from);
4359 from_ptr = build_fold_addr_expr_loc (loc, from);
4360 gimplify_arg (&from_ptr, seq_p, loc);
4362 mark_addressable (to);
4363 to_ptr = build_fold_addr_expr_loc (loc, to);
4364 gimplify_arg (&to_ptr, seq_p, loc);
4366 t = builtin_decl_implicit (BUILT_IN_MEMCPY);
4368 gs = gimple_build_call (t, 3, to_ptr, from_ptr, size);
4369 gimple_call_set_alloca_for_var (gs, true);
4371 if (want_value)
4373 /* tmp = memcpy() */
4374 t = create_tmp_var (TREE_TYPE (to_ptr));
4375 gimple_call_set_lhs (gs, t);
4376 gimplify_seq_add_stmt (seq_p, gs);
4378 *expr_p = build_simple_mem_ref (t);
4379 return GS_ALL_DONE;
4382 gimplify_seq_add_stmt (seq_p, gs);
4383 *expr_p = NULL;
4384 return GS_ALL_DONE;
4387 /* A subroutine of gimplify_modify_expr. Replace a MODIFY_EXPR with
4388 a call to __builtin_memset. In this case we know that the RHS is
4389 a CONSTRUCTOR with an empty element list. */
4391 static enum gimplify_status
4392 gimplify_modify_expr_to_memset (tree *expr_p, tree size, bool want_value,
4393 gimple_seq *seq_p)
4395 tree t, from, to, to_ptr;
4396 gcall *gs;
4397 location_t loc = EXPR_LOCATION (*expr_p);
4399 /* Assert our assumptions, to abort instead of producing wrong code
4400 silently if they are not met. Beware that the RHS CONSTRUCTOR might
4401 not be immediately exposed. */
4402 from = TREE_OPERAND (*expr_p, 1);
4403 if (TREE_CODE (from) == WITH_SIZE_EXPR)
4404 from = TREE_OPERAND (from, 0);
4406 gcc_assert (TREE_CODE (from) == CONSTRUCTOR
4407 && vec_safe_is_empty (CONSTRUCTOR_ELTS (from)));
4409 /* Now proceed. */
4410 to = TREE_OPERAND (*expr_p, 0);
4412 to_ptr = build_fold_addr_expr_loc (loc, to);
4413 gimplify_arg (&to_ptr, seq_p, loc);
4414 t = builtin_decl_implicit (BUILT_IN_MEMSET);
4416 gs = gimple_build_call (t, 3, to_ptr, integer_zero_node, size);
4418 if (want_value)
4420 /* tmp = memset() */
4421 t = create_tmp_var (TREE_TYPE (to_ptr));
4422 gimple_call_set_lhs (gs, t);
4423 gimplify_seq_add_stmt (seq_p, gs);
4425 *expr_p = build1 (INDIRECT_REF, TREE_TYPE (to), t);
4426 return GS_ALL_DONE;
4429 gimplify_seq_add_stmt (seq_p, gs);
4430 *expr_p = NULL;
4431 return GS_ALL_DONE;
4434 /* A subroutine of gimplify_init_ctor_preeval. Called via walk_tree,
4435 determine, cautiously, if a CONSTRUCTOR overlaps the lhs of an
4436 assignment. Return non-null if we detect a potential overlap. */
4438 struct gimplify_init_ctor_preeval_data
4440 /* The base decl of the lhs object. May be NULL, in which case we
4441 have to assume the lhs is indirect. */
4442 tree lhs_base_decl;
4444 /* The alias set of the lhs object. */
4445 alias_set_type lhs_alias_set;
4448 static tree
4449 gimplify_init_ctor_preeval_1 (tree *tp, int *walk_subtrees, void *xdata)
4451 struct gimplify_init_ctor_preeval_data *data
4452 = (struct gimplify_init_ctor_preeval_data *) xdata;
4453 tree t = *tp;
4455 /* If we find the base object, obviously we have overlap. */
4456 if (data->lhs_base_decl == t)
4457 return t;
4459 /* If the constructor component is indirect, determine if we have a
4460 potential overlap with the lhs. The only bits of information we
4461 have to go on at this point are addressability and alias sets. */
4462 if ((INDIRECT_REF_P (t)
4463 || TREE_CODE (t) == MEM_REF)
4464 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
4465 && alias_sets_conflict_p (data->lhs_alias_set, get_alias_set (t)))
4466 return t;
4468 /* If the constructor component is a call, determine if it can hide a
4469 potential overlap with the lhs through an INDIRECT_REF like above.
4470 ??? Ugh - this is completely broken. In fact this whole analysis
4471 doesn't look conservative. */
4472 if (TREE_CODE (t) == CALL_EXPR)
4474 tree type, fntype = TREE_TYPE (TREE_TYPE (CALL_EXPR_FN (t)));
4476 for (type = TYPE_ARG_TYPES (fntype); type; type = TREE_CHAIN (type))
4477 if (POINTER_TYPE_P (TREE_VALUE (type))
4478 && (!data->lhs_base_decl || TREE_ADDRESSABLE (data->lhs_base_decl))
4479 && alias_sets_conflict_p (data->lhs_alias_set,
4480 get_alias_set
4481 (TREE_TYPE (TREE_VALUE (type)))))
4482 return t;
4485 if (IS_TYPE_OR_DECL_P (t))
4486 *walk_subtrees = 0;
4487 return NULL;
4490 /* A subroutine of gimplify_init_constructor. Pre-evaluate EXPR,
4491 force values that overlap with the lhs (as described by *DATA)
4492 into temporaries. */
4494 static void
4495 gimplify_init_ctor_preeval (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
4496 struct gimplify_init_ctor_preeval_data *data)
4498 enum gimplify_status one;
4500 /* If the value is constant, then there's nothing to pre-evaluate. */
4501 if (TREE_CONSTANT (*expr_p))
4503 /* Ensure it does not have side effects, it might contain a reference to
4504 the object we're initializing. */
4505 gcc_assert (!TREE_SIDE_EFFECTS (*expr_p));
4506 return;
4509 /* If the type has non-trivial constructors, we can't pre-evaluate. */
4510 if (TREE_ADDRESSABLE (TREE_TYPE (*expr_p)))
4511 return;
4513 /* Recurse for nested constructors. */
4514 if (TREE_CODE (*expr_p) == CONSTRUCTOR)
4516 unsigned HOST_WIDE_INT ix;
4517 constructor_elt *ce;
4518 vec<constructor_elt, va_gc> *v = CONSTRUCTOR_ELTS (*expr_p);
4520 FOR_EACH_VEC_SAFE_ELT (v, ix, ce)
4521 gimplify_init_ctor_preeval (&ce->value, pre_p, post_p, data);
4523 return;
4526 /* If this is a variable sized type, we must remember the size. */
4527 maybe_with_size_expr (expr_p);
4529 /* Gimplify the constructor element to something appropriate for the rhs
4530 of a MODIFY_EXPR. Given that we know the LHS is an aggregate, we know
4531 the gimplifier will consider this a store to memory. Doing this
4532 gimplification now means that we won't have to deal with complicated
4533 language-specific trees, nor trees like SAVE_EXPR that can induce
4534 exponential search behavior. */
4535 one = gimplify_expr (expr_p, pre_p, post_p, is_gimple_mem_rhs, fb_rvalue);
4536 if (one == GS_ERROR)
4538 *expr_p = NULL;
4539 return;
4542 /* If we gimplified to a bare decl, we can be sure that it doesn't overlap
4543 with the lhs, since "a = { .x=a }" doesn't make sense. This will
4544 always be true for all scalars, since is_gimple_mem_rhs insists on a
4545 temporary variable for them. */
4546 if (DECL_P (*expr_p))
4547 return;
4549 /* If this is of variable size, we have no choice but to assume it doesn't
4550 overlap since we can't make a temporary for it. */
4551 if (TREE_CODE (TYPE_SIZE (TREE_TYPE (*expr_p))) != INTEGER_CST)
4552 return;
4554 /* Otherwise, we must search for overlap ... */
4555 if (!walk_tree (expr_p, gimplify_init_ctor_preeval_1, data, NULL))
4556 return;
4558 /* ... and if found, force the value into a temporary. */
4559 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
4562 /* A subroutine of gimplify_init_ctor_eval. Create a loop for
4563 a RANGE_EXPR in a CONSTRUCTOR for an array.
4565 var = lower;
4566 loop_entry:
4567 object[var] = value;
4568 if (var == upper)
4569 goto loop_exit;
4570 var = var + 1;
4571 goto loop_entry;
4572 loop_exit:
4574 We increment var _after_ the loop exit check because we might otherwise
4575 fail if upper == TYPE_MAX_VALUE (type for upper).
4577 Note that we never have to deal with SAVE_EXPRs here, because this has
4578 already been taken care of for us, in gimplify_init_ctor_preeval(). */
4580 static void gimplify_init_ctor_eval (tree, vec<constructor_elt, va_gc> *,
4581 gimple_seq *, bool);
4583 static void
4584 gimplify_init_ctor_eval_range (tree object, tree lower, tree upper,
4585 tree value, tree array_elt_type,
4586 gimple_seq *pre_p, bool cleared)
4588 tree loop_entry_label, loop_exit_label, fall_thru_label;
4589 tree var, var_type, cref, tmp;
4591 loop_entry_label = create_artificial_label (UNKNOWN_LOCATION);
4592 loop_exit_label = create_artificial_label (UNKNOWN_LOCATION);
4593 fall_thru_label = create_artificial_label (UNKNOWN_LOCATION);
4595 /* Create and initialize the index variable. */
4596 var_type = TREE_TYPE (upper);
4597 var = create_tmp_var (var_type);
4598 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, lower));
4600 /* Add the loop entry label. */
4601 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_entry_label));
4603 /* Build the reference. */
4604 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
4605 var, NULL_TREE, NULL_TREE);
4607 /* If we are a constructor, just call gimplify_init_ctor_eval to do
4608 the store. Otherwise just assign value to the reference. */
4610 if (TREE_CODE (value) == CONSTRUCTOR)
4611 /* NB we might have to call ourself recursively through
4612 gimplify_init_ctor_eval if the value is a constructor. */
4613 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
4614 pre_p, cleared);
4615 else
4617 if (gimplify_expr (&value, pre_p, NULL, is_gimple_val, fb_rvalue)
4618 != GS_ERROR)
4619 gimplify_seq_add_stmt (pre_p, gimple_build_assign (cref, value));
4622 /* We exit the loop when the index var is equal to the upper bound. */
4623 gimplify_seq_add_stmt (pre_p,
4624 gimple_build_cond (EQ_EXPR, var, upper,
4625 loop_exit_label, fall_thru_label));
4627 gimplify_seq_add_stmt (pre_p, gimple_build_label (fall_thru_label));
4629 /* Otherwise, increment the index var... */
4630 tmp = build2 (PLUS_EXPR, var_type, var,
4631 fold_convert (var_type, integer_one_node));
4632 gimplify_seq_add_stmt (pre_p, gimple_build_assign (var, tmp));
4634 /* ...and jump back to the loop entry. */
4635 gimplify_seq_add_stmt (pre_p, gimple_build_goto (loop_entry_label));
4637 /* Add the loop exit label. */
4638 gimplify_seq_add_stmt (pre_p, gimple_build_label (loop_exit_label));
4641 /* Return true if FDECL is accessing a field that is zero sized. */
4643 static bool
4644 zero_sized_field_decl (const_tree fdecl)
4646 if (TREE_CODE (fdecl) == FIELD_DECL && DECL_SIZE (fdecl)
4647 && integer_zerop (DECL_SIZE (fdecl)))
4648 return true;
4649 return false;
4652 /* Return true if TYPE is zero sized. */
4654 static bool
4655 zero_sized_type (const_tree type)
4657 if (AGGREGATE_TYPE_P (type) && TYPE_SIZE (type)
4658 && integer_zerop (TYPE_SIZE (type)))
4659 return true;
4660 return false;
4663 /* A subroutine of gimplify_init_constructor. Generate individual
4664 MODIFY_EXPRs for a CONSTRUCTOR. OBJECT is the LHS against which the
4665 assignments should happen. ELTS is the CONSTRUCTOR_ELTS of the
4666 CONSTRUCTOR. CLEARED is true if the entire LHS object has been
4667 zeroed first. */
4669 static void
4670 gimplify_init_ctor_eval (tree object, vec<constructor_elt, va_gc> *elts,
4671 gimple_seq *pre_p, bool cleared)
4673 tree array_elt_type = NULL;
4674 unsigned HOST_WIDE_INT ix;
4675 tree purpose, value;
4677 if (TREE_CODE (TREE_TYPE (object)) == ARRAY_TYPE)
4678 array_elt_type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (object)));
4680 FOR_EACH_CONSTRUCTOR_ELT (elts, ix, purpose, value)
4682 tree cref;
4684 /* NULL values are created above for gimplification errors. */
4685 if (value == NULL)
4686 continue;
4688 if (cleared && initializer_zerop (value))
4689 continue;
4691 /* ??? Here's to hoping the front end fills in all of the indices,
4692 so we don't have to figure out what's missing ourselves. */
4693 gcc_assert (purpose);
4695 /* Skip zero-sized fields, unless value has side-effects. This can
4696 happen with calls to functions returning a zero-sized type, which
4697 we shouldn't discard. As a number of downstream passes don't
4698 expect sets of zero-sized fields, we rely on the gimplification of
4699 the MODIFY_EXPR we make below to drop the assignment statement. */
4700 if (! TREE_SIDE_EFFECTS (value) && zero_sized_field_decl (purpose))
4701 continue;
4703 /* If we have a RANGE_EXPR, we have to build a loop to assign the
4704 whole range. */
4705 if (TREE_CODE (purpose) == RANGE_EXPR)
4707 tree lower = TREE_OPERAND (purpose, 0);
4708 tree upper = TREE_OPERAND (purpose, 1);
4710 /* If the lower bound is equal to upper, just treat it as if
4711 upper was the index. */
4712 if (simple_cst_equal (lower, upper))
4713 purpose = upper;
4714 else
4716 gimplify_init_ctor_eval_range (object, lower, upper, value,
4717 array_elt_type, pre_p, cleared);
4718 continue;
4722 if (array_elt_type)
4724 /* Do not use bitsizetype for ARRAY_REF indices. */
4725 if (TYPE_DOMAIN (TREE_TYPE (object)))
4726 purpose
4727 = fold_convert (TREE_TYPE (TYPE_DOMAIN (TREE_TYPE (object))),
4728 purpose);
4729 cref = build4 (ARRAY_REF, array_elt_type, unshare_expr (object),
4730 purpose, NULL_TREE, NULL_TREE);
4732 else
4734 gcc_assert (TREE_CODE (purpose) == FIELD_DECL);
4735 cref = build3 (COMPONENT_REF, TREE_TYPE (purpose),
4736 unshare_expr (object), purpose, NULL_TREE);
4739 if (TREE_CODE (value) == CONSTRUCTOR
4740 && TREE_CODE (TREE_TYPE (value)) != VECTOR_TYPE)
4741 gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
4742 pre_p, cleared);
4743 else
4745 tree init = build2 (INIT_EXPR, TREE_TYPE (cref), cref, value);
4746 gimplify_and_add (init, pre_p);
4747 ggc_free (init);
4752 /* Return the appropriate RHS predicate for this LHS. */
4754 gimple_predicate
4755 rhs_predicate_for (tree lhs)
4757 if (is_gimple_reg (lhs))
4758 return is_gimple_reg_rhs_or_call;
4759 else
4760 return is_gimple_mem_rhs_or_call;
4763 /* Return the initial guess for an appropriate RHS predicate for this LHS,
4764 before the LHS has been gimplified. */
4766 static gimple_predicate
4767 initial_rhs_predicate_for (tree lhs)
4769 if (is_gimple_reg_type (TREE_TYPE (lhs)))
4770 return is_gimple_reg_rhs_or_call;
4771 else
4772 return is_gimple_mem_rhs_or_call;
4775 /* Gimplify a C99 compound literal expression. This just means adding
4776 the DECL_EXPR before the current statement and using its anonymous
4777 decl instead. */
4779 static enum gimplify_status
4780 gimplify_compound_literal_expr (tree *expr_p, gimple_seq *pre_p,
4781 bool (*gimple_test_f) (tree),
4782 fallback_t fallback)
4784 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (*expr_p);
4785 tree decl = DECL_EXPR_DECL (decl_s);
4786 tree init = DECL_INITIAL (decl);
4787 /* Mark the decl as addressable if the compound literal
4788 expression is addressable now, otherwise it is marked too late
4789 after we gimplify the initialization expression. */
4790 if (TREE_ADDRESSABLE (*expr_p))
4791 TREE_ADDRESSABLE (decl) = 1;
4792 /* Otherwise, if we don't need an lvalue and have a literal directly
4793 substitute it. Check if it matches the gimple predicate, as
4794 otherwise we'd generate a new temporary, and we can as well just
4795 use the decl we already have. */
4796 else if (!TREE_ADDRESSABLE (decl)
4797 && !TREE_THIS_VOLATILE (decl)
4798 && init
4799 && (fallback & fb_lvalue) == 0
4800 && gimple_test_f (init))
4802 *expr_p = init;
4803 return GS_OK;
4806 /* If the decl is not addressable, then it is being used in some
4807 expression or on the right hand side of a statement, and it can
4808 be put into a readonly data section. */
4809 if (!TREE_ADDRESSABLE (decl) && (fallback & fb_lvalue) == 0)
4810 TREE_READONLY (decl) = 1;
4812 /* This decl isn't mentioned in the enclosing block, so add it to the
4813 list of temps. FIXME it seems a bit of a kludge to say that
4814 anonymous artificial vars aren't pushed, but everything else is. */
4815 if (DECL_NAME (decl) == NULL_TREE && !DECL_SEEN_IN_BIND_EXPR_P (decl))
4816 gimple_add_tmp_var (decl);
4818 gimplify_and_add (decl_s, pre_p);
4819 *expr_p = decl;
4820 return GS_OK;
4823 /* Optimize embedded COMPOUND_LITERAL_EXPRs within a CONSTRUCTOR,
4824 return a new CONSTRUCTOR if something changed. */
4826 static tree
4827 optimize_compound_literals_in_ctor (tree orig_ctor)
4829 tree ctor = orig_ctor;
4830 vec<constructor_elt, va_gc> *elts = CONSTRUCTOR_ELTS (ctor);
4831 unsigned int idx, num = vec_safe_length (elts);
4833 for (idx = 0; idx < num; idx++)
4835 tree value = (*elts)[idx].value;
4836 tree newval = value;
4837 if (TREE_CODE (value) == CONSTRUCTOR)
4838 newval = optimize_compound_literals_in_ctor (value);
4839 else if (TREE_CODE (value) == COMPOUND_LITERAL_EXPR)
4841 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (value);
4842 tree decl = DECL_EXPR_DECL (decl_s);
4843 tree init = DECL_INITIAL (decl);
4845 if (!TREE_ADDRESSABLE (value)
4846 && !TREE_ADDRESSABLE (decl)
4847 && init
4848 && TREE_CODE (init) == CONSTRUCTOR)
4849 newval = optimize_compound_literals_in_ctor (init);
4851 if (newval == value)
4852 continue;
4854 if (ctor == orig_ctor)
4856 ctor = copy_node (orig_ctor);
4857 CONSTRUCTOR_ELTS (ctor) = vec_safe_copy (elts);
4858 elts = CONSTRUCTOR_ELTS (ctor);
4860 (*elts)[idx].value = newval;
4862 return ctor;
4865 /* A subroutine of gimplify_modify_expr. Break out elements of a
4866 CONSTRUCTOR used as an initializer into separate MODIFY_EXPRs.
4868 Note that we still need to clear any elements that don't have explicit
4869 initializers, so if not all elements are initialized we keep the
4870 original MODIFY_EXPR, we just remove all of the constructor elements.
4872 If NOTIFY_TEMP_CREATION is true, do not gimplify, just return
4873 GS_ERROR if we would have to create a temporary when gimplifying
4874 this constructor. Otherwise, return GS_OK.
4876 If NOTIFY_TEMP_CREATION is false, just do the gimplification. */
4878 static enum gimplify_status
4879 gimplify_init_constructor (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
4880 bool want_value, bool notify_temp_creation)
4882 tree object, ctor, type;
4883 enum gimplify_status ret;
4884 vec<constructor_elt, va_gc> *elts;
4886 gcc_assert (TREE_CODE (TREE_OPERAND (*expr_p, 1)) == CONSTRUCTOR);
4888 if (!notify_temp_creation)
4890 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
4891 is_gimple_lvalue, fb_lvalue);
4892 if (ret == GS_ERROR)
4893 return ret;
4896 object = TREE_OPERAND (*expr_p, 0);
4897 ctor = TREE_OPERAND (*expr_p, 1)
4898 = optimize_compound_literals_in_ctor (TREE_OPERAND (*expr_p, 1));
4899 type = TREE_TYPE (ctor);
4900 elts = CONSTRUCTOR_ELTS (ctor);
4901 ret = GS_ALL_DONE;
4903 switch (TREE_CODE (type))
4905 case RECORD_TYPE:
4906 case UNION_TYPE:
4907 case QUAL_UNION_TYPE:
4908 case ARRAY_TYPE:
4910 /* Use readonly data for initializers of this or smaller size
4911 regardless of the num_nonzero_elements / num_unique_nonzero_elements
4912 ratio. */
4913 const HOST_WIDE_INT min_unique_size = 64;
4914 /* If num_nonzero_elements / num_unique_nonzero_elements ratio
4915 is smaller than this, use readonly data. */
4916 const int unique_nonzero_ratio = 8;
4917 /* True if a single access of the object must be ensured. This is the
4918 case if the target is volatile, the type is non-addressable and more
4919 than one field need to be assigned. */
4920 const bool ensure_single_access
4921 = TREE_THIS_VOLATILE (object)
4922 && !TREE_ADDRESSABLE (type)
4923 && vec_safe_length (elts) > 1;
4924 struct gimplify_init_ctor_preeval_data preeval_data;
4925 HOST_WIDE_INT num_ctor_elements, num_nonzero_elements;
4926 HOST_WIDE_INT num_unique_nonzero_elements;
4927 bool cleared, complete_p, valid_const_initializer;
4929 /* Aggregate types must lower constructors to initialization of
4930 individual elements. The exception is that a CONSTRUCTOR node
4931 with no elements indicates zero-initialization of the whole. */
4932 if (vec_safe_is_empty (elts))
4934 if (notify_temp_creation)
4935 return GS_OK;
4936 break;
4939 /* Fetch information about the constructor to direct later processing.
4940 We might want to make static versions of it in various cases, and
4941 can only do so if it known to be a valid constant initializer. */
4942 valid_const_initializer
4943 = categorize_ctor_elements (ctor, &num_nonzero_elements,
4944 &num_unique_nonzero_elements,
4945 &num_ctor_elements, &complete_p);
4947 /* If a const aggregate variable is being initialized, then it
4948 should never be a lose to promote the variable to be static. */
4949 if (valid_const_initializer
4950 && num_nonzero_elements > 1
4951 && TREE_READONLY (object)
4952 && VAR_P (object)
4953 && !DECL_REGISTER (object)
4954 && (flag_merge_constants >= 2 || !TREE_ADDRESSABLE (object))
4955 /* For ctors that have many repeated nonzero elements
4956 represented through RANGE_EXPRs, prefer initializing
4957 those through runtime loops over copies of large amounts
4958 of data from readonly data section. */
4959 && (num_unique_nonzero_elements
4960 > num_nonzero_elements / unique_nonzero_ratio
4961 || ((unsigned HOST_WIDE_INT) int_size_in_bytes (type)
4962 <= (unsigned HOST_WIDE_INT) min_unique_size)))
4964 if (notify_temp_creation)
4965 return GS_ERROR;
4967 DECL_INITIAL (object) = ctor;
4968 TREE_STATIC (object) = 1;
4969 if (!DECL_NAME (object))
4970 DECL_NAME (object) = create_tmp_var_name ("C");
4971 walk_tree (&DECL_INITIAL (object), force_labels_r, NULL, NULL);
4973 /* ??? C++ doesn't automatically append a .<number> to the
4974 assembler name, and even when it does, it looks at FE private
4975 data structures to figure out what that number should be,
4976 which are not set for this variable. I suppose this is
4977 important for local statics for inline functions, which aren't
4978 "local" in the object file sense. So in order to get a unique
4979 TU-local symbol, we must invoke the lhd version now. */
4980 lhd_set_decl_assembler_name (object);
4982 *expr_p = NULL_TREE;
4983 break;
4986 /* If there are "lots" of initialized elements, even discounting
4987 those that are not address constants (and thus *must* be
4988 computed at runtime), then partition the constructor into
4989 constant and non-constant parts. Block copy the constant
4990 parts in, then generate code for the non-constant parts. */
4991 /* TODO. There's code in cp/typeck.c to do this. */
4993 if (int_size_in_bytes (TREE_TYPE (ctor)) < 0)
4994 /* store_constructor will ignore the clearing of variable-sized
4995 objects. Initializers for such objects must explicitly set
4996 every field that needs to be set. */
4997 cleared = false;
4998 else if (!complete_p)
4999 /* If the constructor isn't complete, clear the whole object
5000 beforehand, unless CONSTRUCTOR_NO_CLEARING is set on it.
5002 ??? This ought not to be needed. For any element not present
5003 in the initializer, we should simply set them to zero. Except
5004 we'd need to *find* the elements that are not present, and that
5005 requires trickery to avoid quadratic compile-time behavior in
5006 large cases or excessive memory use in small cases. */
5007 cleared = !CONSTRUCTOR_NO_CLEARING (ctor);
5008 else if (num_ctor_elements - num_nonzero_elements
5009 > CLEAR_RATIO (optimize_function_for_speed_p (cfun))
5010 && num_nonzero_elements < num_ctor_elements / 4)
5011 /* If there are "lots" of zeros, it's more efficient to clear
5012 the memory and then set the nonzero elements. */
5013 cleared = true;
5014 else if (ensure_single_access && num_nonzero_elements == 0)
5015 /* If a single access to the target must be ensured and all elements
5016 are zero, then it's optimal to clear whatever their number. */
5017 cleared = true;
5018 else
5019 cleared = false;
5021 /* If there are "lots" of initialized elements, and all of them
5022 are valid address constants, then the entire initializer can
5023 be dropped to memory, and then memcpy'd out. Don't do this
5024 for sparse arrays, though, as it's more efficient to follow
5025 the standard CONSTRUCTOR behavior of memset followed by
5026 individual element initialization. Also don't do this for small
5027 all-zero initializers (which aren't big enough to merit
5028 clearing), and don't try to make bitwise copies of
5029 TREE_ADDRESSABLE types. */
5030 if (valid_const_initializer
5031 && complete_p
5032 && !(cleared || num_nonzero_elements == 0)
5033 && !TREE_ADDRESSABLE (type))
5035 HOST_WIDE_INT size = int_size_in_bytes (type);
5036 unsigned int align;
5038 /* ??? We can still get unbounded array types, at least
5039 from the C++ front end. This seems wrong, but attempt
5040 to work around it for now. */
5041 if (size < 0)
5043 size = int_size_in_bytes (TREE_TYPE (object));
5044 if (size >= 0)
5045 TREE_TYPE (ctor) = type = TREE_TYPE (object);
5048 /* Find the maximum alignment we can assume for the object. */
5049 /* ??? Make use of DECL_OFFSET_ALIGN. */
5050 if (DECL_P (object))
5051 align = DECL_ALIGN (object);
5052 else
5053 align = TYPE_ALIGN (type);
5055 /* Do a block move either if the size is so small as to make
5056 each individual move a sub-unit move on average, or if it
5057 is so large as to make individual moves inefficient. */
5058 if (size > 0
5059 && num_nonzero_elements > 1
5060 /* For ctors that have many repeated nonzero elements
5061 represented through RANGE_EXPRs, prefer initializing
5062 those through runtime loops over copies of large amounts
5063 of data from readonly data section. */
5064 && (num_unique_nonzero_elements
5065 > num_nonzero_elements / unique_nonzero_ratio
5066 || size <= min_unique_size)
5067 && (size < num_nonzero_elements
5068 || !can_move_by_pieces (size, align)))
5070 if (notify_temp_creation)
5071 return GS_ERROR;
5073 walk_tree (&ctor, force_labels_r, NULL, NULL);
5074 ctor = tree_output_constant_def (ctor);
5075 if (!useless_type_conversion_p (type, TREE_TYPE (ctor)))
5076 ctor = build1 (VIEW_CONVERT_EXPR, type, ctor);
5077 TREE_OPERAND (*expr_p, 1) = ctor;
5079 /* This is no longer an assignment of a CONSTRUCTOR, but
5080 we still may have processing to do on the LHS. So
5081 pretend we didn't do anything here to let that happen. */
5082 return GS_UNHANDLED;
5086 /* If a single access to the target must be ensured and there are
5087 nonzero elements or the zero elements are not assigned en masse,
5088 initialize the target from a temporary. */
5089 if (ensure_single_access && (num_nonzero_elements > 0 || !cleared))
5091 if (notify_temp_creation)
5092 return GS_ERROR;
5094 tree temp = create_tmp_var (TYPE_MAIN_VARIANT (type));
5095 TREE_OPERAND (*expr_p, 0) = temp;
5096 *expr_p = build2 (COMPOUND_EXPR, TREE_TYPE (*expr_p),
5097 *expr_p,
5098 build2 (MODIFY_EXPR, void_type_node,
5099 object, temp));
5100 return GS_OK;
5103 if (notify_temp_creation)
5104 return GS_OK;
5106 /* If there are nonzero elements and if needed, pre-evaluate to capture
5107 elements overlapping with the lhs into temporaries. We must do this
5108 before clearing to fetch the values before they are zeroed-out. */
5109 if (num_nonzero_elements > 0 && TREE_CODE (*expr_p) != INIT_EXPR)
5111 preeval_data.lhs_base_decl = get_base_address (object);
5112 if (!DECL_P (preeval_data.lhs_base_decl))
5113 preeval_data.lhs_base_decl = NULL;
5114 preeval_data.lhs_alias_set = get_alias_set (object);
5116 gimplify_init_ctor_preeval (&TREE_OPERAND (*expr_p, 1),
5117 pre_p, post_p, &preeval_data);
5120 bool ctor_has_side_effects_p
5121 = TREE_SIDE_EFFECTS (TREE_OPERAND (*expr_p, 1));
5123 if (cleared)
5125 /* Zap the CONSTRUCTOR element list, which simplifies this case.
5126 Note that we still have to gimplify, in order to handle the
5127 case of variable sized types. Avoid shared tree structures. */
5128 CONSTRUCTOR_ELTS (ctor) = NULL;
5129 TREE_SIDE_EFFECTS (ctor) = 0;
5130 object = unshare_expr (object);
5131 gimplify_stmt (expr_p, pre_p);
5134 /* If we have not block cleared the object, or if there are nonzero
5135 elements in the constructor, or if the constructor has side effects,
5136 add assignments to the individual scalar fields of the object. */
5137 if (!cleared
5138 || num_nonzero_elements > 0
5139 || ctor_has_side_effects_p)
5140 gimplify_init_ctor_eval (object, elts, pre_p, cleared);
5142 *expr_p = NULL_TREE;
5144 break;
5146 case COMPLEX_TYPE:
5148 tree r, i;
5150 if (notify_temp_creation)
5151 return GS_OK;
5153 /* Extract the real and imaginary parts out of the ctor. */
5154 gcc_assert (elts->length () == 2);
5155 r = (*elts)[0].value;
5156 i = (*elts)[1].value;
5157 if (r == NULL || i == NULL)
5159 tree zero = build_zero_cst (TREE_TYPE (type));
5160 if (r == NULL)
5161 r = zero;
5162 if (i == NULL)
5163 i = zero;
5166 /* Complex types have either COMPLEX_CST or COMPLEX_EXPR to
5167 represent creation of a complex value. */
5168 if (TREE_CONSTANT (r) && TREE_CONSTANT (i))
5170 ctor = build_complex (type, r, i);
5171 TREE_OPERAND (*expr_p, 1) = ctor;
5173 else
5175 ctor = build2 (COMPLEX_EXPR, type, r, i);
5176 TREE_OPERAND (*expr_p, 1) = ctor;
5177 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 1),
5178 pre_p,
5179 post_p,
5180 rhs_predicate_for (TREE_OPERAND (*expr_p, 0)),
5181 fb_rvalue);
5184 break;
5186 case VECTOR_TYPE:
5188 unsigned HOST_WIDE_INT ix;
5189 constructor_elt *ce;
5191 if (notify_temp_creation)
5192 return GS_OK;
5194 /* Go ahead and simplify constant constructors to VECTOR_CST. */
5195 if (TREE_CONSTANT (ctor))
5197 bool constant_p = true;
5198 tree value;
5200 /* Even when ctor is constant, it might contain non-*_CST
5201 elements, such as addresses or trapping values like
5202 1.0/0.0 - 1.0/0.0. Such expressions don't belong
5203 in VECTOR_CST nodes. */
5204 FOR_EACH_CONSTRUCTOR_VALUE (elts, ix, value)
5205 if (!CONSTANT_CLASS_P (value))
5207 constant_p = false;
5208 break;
5211 if (constant_p)
5213 TREE_OPERAND (*expr_p, 1) = build_vector_from_ctor (type, elts);
5214 break;
5217 TREE_CONSTANT (ctor) = 0;
5220 /* Vector types use CONSTRUCTOR all the way through gimple
5221 compilation as a general initializer. */
5222 FOR_EACH_VEC_SAFE_ELT (elts, ix, ce)
5224 enum gimplify_status tret;
5225 tret = gimplify_expr (&ce->value, pre_p, post_p, is_gimple_val,
5226 fb_rvalue);
5227 if (tret == GS_ERROR)
5228 ret = GS_ERROR;
5229 else if (TREE_STATIC (ctor)
5230 && !initializer_constant_valid_p (ce->value,
5231 TREE_TYPE (ce->value)))
5232 TREE_STATIC (ctor) = 0;
5234 if (!is_gimple_reg (TREE_OPERAND (*expr_p, 0)))
5235 TREE_OPERAND (*expr_p, 1) = get_formal_tmp_var (ctor, pre_p);
5237 break;
5239 default:
5240 /* So how did we get a CONSTRUCTOR for a scalar type? */
5241 gcc_unreachable ();
5244 if (ret == GS_ERROR)
5245 return GS_ERROR;
5246 /* If we have gimplified both sides of the initializer but have
5247 not emitted an assignment, do so now. */
5248 if (*expr_p)
5250 tree lhs = TREE_OPERAND (*expr_p, 0);
5251 tree rhs = TREE_OPERAND (*expr_p, 1);
5252 if (want_value && object == lhs)
5253 lhs = unshare_expr (lhs);
5254 gassign *init = gimple_build_assign (lhs, rhs);
5255 gimplify_seq_add_stmt (pre_p, init);
5257 if (want_value)
5259 *expr_p = object;
5260 return GS_OK;
5262 else
5264 *expr_p = NULL;
5265 return GS_ALL_DONE;
5269 /* Given a pointer value OP0, return a simplified version of an
5270 indirection through OP0, or NULL_TREE if no simplification is
5271 possible. This may only be applied to a rhs of an expression.
5272 Note that the resulting type may be different from the type pointed
5273 to in the sense that it is still compatible from the langhooks
5274 point of view. */
5276 static tree
5277 gimple_fold_indirect_ref_rhs (tree t)
5279 return gimple_fold_indirect_ref (t);
5282 /* Subroutine of gimplify_modify_expr to do simplifications of
5283 MODIFY_EXPRs based on the code of the RHS. We loop for as long as
5284 something changes. */
5286 static enum gimplify_status
5287 gimplify_modify_expr_rhs (tree *expr_p, tree *from_p, tree *to_p,
5288 gimple_seq *pre_p, gimple_seq *post_p,
5289 bool want_value)
5291 enum gimplify_status ret = GS_UNHANDLED;
5292 bool changed;
5296 changed = false;
5297 switch (TREE_CODE (*from_p))
5299 case VAR_DECL:
5300 /* If we're assigning from a read-only variable initialized with
5301 a constructor and not volatile, do the direct assignment from
5302 the constructor, but only if the target is not volatile either
5303 since this latter assignment might end up being done on a per
5304 field basis. However, if the target is volatile and the type
5305 is aggregate and non-addressable, gimplify_init_constructor
5306 knows that it needs to ensure a single access to the target
5307 and it will return GS_OK only in this case. */
5308 if (TREE_READONLY (*from_p)
5309 && DECL_INITIAL (*from_p)
5310 && TREE_CODE (DECL_INITIAL (*from_p)) == CONSTRUCTOR
5311 && !TREE_THIS_VOLATILE (*from_p)
5312 && (!TREE_THIS_VOLATILE (*to_p)
5313 || (AGGREGATE_TYPE_P (TREE_TYPE (*to_p))
5314 && !TREE_ADDRESSABLE (TREE_TYPE (*to_p)))))
5316 tree old_from = *from_p;
5317 enum gimplify_status subret;
5319 /* Move the constructor into the RHS. */
5320 *from_p = unshare_expr (DECL_INITIAL (*from_p));
5322 /* Let's see if gimplify_init_constructor will need to put
5323 it in memory. */
5324 subret = gimplify_init_constructor (expr_p, NULL, NULL,
5325 false, true);
5326 if (subret == GS_ERROR)
5328 /* If so, revert the change. */
5329 *from_p = old_from;
5331 else
5333 ret = GS_OK;
5334 changed = true;
5337 break;
5338 case INDIRECT_REF:
5340 /* If we have code like
5342 *(const A*)(A*)&x
5344 where the type of "x" is a (possibly cv-qualified variant
5345 of "A"), treat the entire expression as identical to "x".
5346 This kind of code arises in C++ when an object is bound
5347 to a const reference, and if "x" is a TARGET_EXPR we want
5348 to take advantage of the optimization below. */
5349 bool volatile_p = TREE_THIS_VOLATILE (*from_p);
5350 tree t = gimple_fold_indirect_ref_rhs (TREE_OPERAND (*from_p, 0));
5351 if (t)
5353 if (TREE_THIS_VOLATILE (t) != volatile_p)
5355 if (DECL_P (t))
5356 t = build_simple_mem_ref_loc (EXPR_LOCATION (*from_p),
5357 build_fold_addr_expr (t));
5358 if (REFERENCE_CLASS_P (t))
5359 TREE_THIS_VOLATILE (t) = volatile_p;
5361 *from_p = t;
5362 ret = GS_OK;
5363 changed = true;
5365 break;
5368 case TARGET_EXPR:
5370 /* If we are initializing something from a TARGET_EXPR, strip the
5371 TARGET_EXPR and initialize it directly, if possible. This can't
5372 be done if the initializer is void, since that implies that the
5373 temporary is set in some non-trivial way.
5375 ??? What about code that pulls out the temp and uses it
5376 elsewhere? I think that such code never uses the TARGET_EXPR as
5377 an initializer. If I'm wrong, we'll die because the temp won't
5378 have any RTL. In that case, I guess we'll need to replace
5379 references somehow. */
5380 tree init = TARGET_EXPR_INITIAL (*from_p);
5382 if (init
5383 && (TREE_CODE (*expr_p) != MODIFY_EXPR
5384 || !TARGET_EXPR_NO_ELIDE (*from_p))
5385 && !VOID_TYPE_P (TREE_TYPE (init)))
5387 *from_p = init;
5388 ret = GS_OK;
5389 changed = true;
5392 break;
5394 case COMPOUND_EXPR:
5395 /* Remove any COMPOUND_EXPR in the RHS so the following cases will be
5396 caught. */
5397 gimplify_compound_expr (from_p, pre_p, true);
5398 ret = GS_OK;
5399 changed = true;
5400 break;
5402 case CONSTRUCTOR:
5403 /* If we already made some changes, let the front end have a
5404 crack at this before we break it down. */
5405 if (ret != GS_UNHANDLED)
5406 break;
5407 /* If we're initializing from a CONSTRUCTOR, break this into
5408 individual MODIFY_EXPRs. */
5409 return gimplify_init_constructor (expr_p, pre_p, post_p, want_value,
5410 false);
5412 case COND_EXPR:
5413 /* If we're assigning to a non-register type, push the assignment
5414 down into the branches. This is mandatory for ADDRESSABLE types,
5415 since we cannot generate temporaries for such, but it saves a
5416 copy in other cases as well. */
5417 if (!is_gimple_reg_type (TREE_TYPE (*from_p)))
5419 /* This code should mirror the code in gimplify_cond_expr. */
5420 enum tree_code code = TREE_CODE (*expr_p);
5421 tree cond = *from_p;
5422 tree result = *to_p;
5424 ret = gimplify_expr (&result, pre_p, post_p,
5425 is_gimple_lvalue, fb_lvalue);
5426 if (ret != GS_ERROR)
5427 ret = GS_OK;
5429 /* If we are going to write RESULT more than once, clear
5430 TREE_READONLY flag, otherwise we might incorrectly promote
5431 the variable to static const and initialize it at compile
5432 time in one of the branches. */
5433 if (VAR_P (result)
5434 && TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node
5435 && TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
5436 TREE_READONLY (result) = 0;
5437 if (TREE_TYPE (TREE_OPERAND (cond, 1)) != void_type_node)
5438 TREE_OPERAND (cond, 1)
5439 = build2 (code, void_type_node, result,
5440 TREE_OPERAND (cond, 1));
5441 if (TREE_TYPE (TREE_OPERAND (cond, 2)) != void_type_node)
5442 TREE_OPERAND (cond, 2)
5443 = build2 (code, void_type_node, unshare_expr (result),
5444 TREE_OPERAND (cond, 2));
5446 TREE_TYPE (cond) = void_type_node;
5447 recalculate_side_effects (cond);
5449 if (want_value)
5451 gimplify_and_add (cond, pre_p);
5452 *expr_p = unshare_expr (result);
5454 else
5455 *expr_p = cond;
5456 return ret;
5458 break;
5460 case CALL_EXPR:
5461 /* For calls that return in memory, give *to_p as the CALL_EXPR's
5462 return slot so that we don't generate a temporary. */
5463 if (!CALL_EXPR_RETURN_SLOT_OPT (*from_p)
5464 && aggregate_value_p (*from_p, *from_p))
5466 bool use_target;
5468 if (!(rhs_predicate_for (*to_p))(*from_p))
5469 /* If we need a temporary, *to_p isn't accurate. */
5470 use_target = false;
5471 /* It's OK to use the return slot directly unless it's an NRV. */
5472 else if (TREE_CODE (*to_p) == RESULT_DECL
5473 && DECL_NAME (*to_p) == NULL_TREE
5474 && needs_to_live_in_memory (*to_p))
5475 use_target = true;
5476 else if (is_gimple_reg_type (TREE_TYPE (*to_p))
5477 || (DECL_P (*to_p) && DECL_REGISTER (*to_p)))
5478 /* Don't force regs into memory. */
5479 use_target = false;
5480 else if (TREE_CODE (*expr_p) == INIT_EXPR)
5481 /* It's OK to use the target directly if it's being
5482 initialized. */
5483 use_target = true;
5484 else if (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (*to_p)))
5485 != INTEGER_CST)
5486 /* Always use the target and thus RSO for variable-sized types.
5487 GIMPLE cannot deal with a variable-sized assignment
5488 embedded in a call statement. */
5489 use_target = true;
5490 else if (TREE_CODE (*to_p) != SSA_NAME
5491 && (!is_gimple_variable (*to_p)
5492 || needs_to_live_in_memory (*to_p)))
5493 /* Don't use the original target if it's already addressable;
5494 if its address escapes, and the called function uses the
5495 NRV optimization, a conforming program could see *to_p
5496 change before the called function returns; see c++/19317.
5497 When optimizing, the return_slot pass marks more functions
5498 as safe after we have escape info. */
5499 use_target = false;
5500 else
5501 use_target = true;
5503 if (use_target)
5505 CALL_EXPR_RETURN_SLOT_OPT (*from_p) = 1;
5506 mark_addressable (*to_p);
5509 break;
5511 case WITH_SIZE_EXPR:
5512 /* Likewise for calls that return an aggregate of non-constant size,
5513 since we would not be able to generate a temporary at all. */
5514 if (TREE_CODE (TREE_OPERAND (*from_p, 0)) == CALL_EXPR)
5516 *from_p = TREE_OPERAND (*from_p, 0);
5517 /* We don't change ret in this case because the
5518 WITH_SIZE_EXPR might have been added in
5519 gimplify_modify_expr, so returning GS_OK would lead to an
5520 infinite loop. */
5521 changed = true;
5523 break;
5525 /* If we're initializing from a container, push the initialization
5526 inside it. */
5527 case CLEANUP_POINT_EXPR:
5528 case BIND_EXPR:
5529 case STATEMENT_LIST:
5531 tree wrap = *from_p;
5532 tree t;
5534 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_min_lval,
5535 fb_lvalue);
5536 if (ret != GS_ERROR)
5537 ret = GS_OK;
5539 t = voidify_wrapper_expr (wrap, *expr_p);
5540 gcc_assert (t == *expr_p);
5542 if (want_value)
5544 gimplify_and_add (wrap, pre_p);
5545 *expr_p = unshare_expr (*to_p);
5547 else
5548 *expr_p = wrap;
5549 return GS_OK;
5552 case NOP_EXPR:
5553 /* Pull out compound literal expressions from a NOP_EXPR.
5554 Those are created in the C FE to drop qualifiers during
5555 lvalue conversion. */
5556 if ((TREE_CODE (TREE_OPERAND (*from_p, 0)) == COMPOUND_LITERAL_EXPR)
5557 && tree_ssa_useless_type_conversion (*from_p))
5559 *from_p = TREE_OPERAND (*from_p, 0);
5560 ret = GS_OK;
5561 changed = true;
5563 break;
5565 case COMPOUND_LITERAL_EXPR:
5567 tree complit = TREE_OPERAND (*expr_p, 1);
5568 tree decl_s = COMPOUND_LITERAL_EXPR_DECL_EXPR (complit);
5569 tree decl = DECL_EXPR_DECL (decl_s);
5570 tree init = DECL_INITIAL (decl);
5572 /* struct T x = (struct T) { 0, 1, 2 } can be optimized
5573 into struct T x = { 0, 1, 2 } if the address of the
5574 compound literal has never been taken. */
5575 if (!TREE_ADDRESSABLE (complit)
5576 && !TREE_ADDRESSABLE (decl)
5577 && init)
5579 *expr_p = copy_node (*expr_p);
5580 TREE_OPERAND (*expr_p, 1) = init;
5581 return GS_OK;
5585 default:
5586 break;
5589 while (changed);
5591 return ret;
5595 /* Return true if T looks like a valid GIMPLE statement. */
5597 static bool
5598 is_gimple_stmt (tree t)
5600 const enum tree_code code = TREE_CODE (t);
5602 switch (code)
5604 case NOP_EXPR:
5605 /* The only valid NOP_EXPR is the empty statement. */
5606 return IS_EMPTY_STMT (t);
5608 case BIND_EXPR:
5609 case COND_EXPR:
5610 /* These are only valid if they're void. */
5611 return TREE_TYPE (t) == NULL || VOID_TYPE_P (TREE_TYPE (t));
5613 case SWITCH_EXPR:
5614 case GOTO_EXPR:
5615 case RETURN_EXPR:
5616 case LABEL_EXPR:
5617 case CASE_LABEL_EXPR:
5618 case TRY_CATCH_EXPR:
5619 case TRY_FINALLY_EXPR:
5620 case EH_FILTER_EXPR:
5621 case CATCH_EXPR:
5622 case ASM_EXPR:
5623 case STATEMENT_LIST:
5624 case OACC_PARALLEL:
5625 case OACC_KERNELS:
5626 case OACC_SERIAL:
5627 case OACC_DATA:
5628 case OACC_HOST_DATA:
5629 case OACC_DECLARE:
5630 case OACC_UPDATE:
5631 case OACC_ENTER_DATA:
5632 case OACC_EXIT_DATA:
5633 case OACC_CACHE:
5634 case OMP_PARALLEL:
5635 case OMP_FOR:
5636 case OMP_SIMD:
5637 case OMP_DISTRIBUTE:
5638 case OMP_LOOP:
5639 case OACC_LOOP:
5640 case OMP_SCAN:
5641 case OMP_SECTIONS:
5642 case OMP_SECTION:
5643 case OMP_SINGLE:
5644 case OMP_MASTER:
5645 case OMP_TASKGROUP:
5646 case OMP_ORDERED:
5647 case OMP_CRITICAL:
5648 case OMP_TASK:
5649 case OMP_TARGET:
5650 case OMP_TARGET_DATA:
5651 case OMP_TARGET_UPDATE:
5652 case OMP_TARGET_ENTER_DATA:
5653 case OMP_TARGET_EXIT_DATA:
5654 case OMP_TASKLOOP:
5655 case OMP_TEAMS:
5656 /* These are always void. */
5657 return true;
5659 case CALL_EXPR:
5660 case MODIFY_EXPR:
5661 case PREDICT_EXPR:
5662 /* These are valid regardless of their type. */
5663 return true;
5665 default:
5666 return false;
5671 /* Promote partial stores to COMPLEX variables to total stores. *EXPR_P is
5672 a MODIFY_EXPR with a lhs of a REAL/IMAGPART_EXPR of a gimple register.
5674 IMPORTANT NOTE: This promotion is performed by introducing a load of the
5675 other, unmodified part of the complex object just before the total store.
5676 As a consequence, if the object is still uninitialized, an undefined value
5677 will be loaded into a register, which may result in a spurious exception
5678 if the register is floating-point and the value happens to be a signaling
5679 NaN for example. Then the fully-fledged complex operations lowering pass
5680 followed by a DCE pass are necessary in order to fix things up. */
5682 static enum gimplify_status
5683 gimplify_modify_expr_complex_part (tree *expr_p, gimple_seq *pre_p,
5684 bool want_value)
5686 enum tree_code code, ocode;
5687 tree lhs, rhs, new_rhs, other, realpart, imagpart;
5689 lhs = TREE_OPERAND (*expr_p, 0);
5690 rhs = TREE_OPERAND (*expr_p, 1);
5691 code = TREE_CODE (lhs);
5692 lhs = TREE_OPERAND (lhs, 0);
5694 ocode = code == REALPART_EXPR ? IMAGPART_EXPR : REALPART_EXPR;
5695 other = build1 (ocode, TREE_TYPE (rhs), lhs);
5696 TREE_NO_WARNING (other) = 1;
5697 other = get_formal_tmp_var (other, pre_p);
5699 realpart = code == REALPART_EXPR ? rhs : other;
5700 imagpart = code == REALPART_EXPR ? other : rhs;
5702 if (TREE_CONSTANT (realpart) && TREE_CONSTANT (imagpart))
5703 new_rhs = build_complex (TREE_TYPE (lhs), realpart, imagpart);
5704 else
5705 new_rhs = build2 (COMPLEX_EXPR, TREE_TYPE (lhs), realpart, imagpart);
5707 gimplify_seq_add_stmt (pre_p, gimple_build_assign (lhs, new_rhs));
5708 *expr_p = (want_value) ? rhs : NULL_TREE;
5710 return GS_ALL_DONE;
5713 /* Gimplify the MODIFY_EXPR node pointed to by EXPR_P.
5715 modify_expr
5716 : varname '=' rhs
5717 | '*' ID '=' rhs
5719 PRE_P points to the list where side effects that must happen before
5720 *EXPR_P should be stored.
5722 POST_P points to the list where side effects that must happen after
5723 *EXPR_P should be stored.
5725 WANT_VALUE is nonzero iff we want to use the value of this expression
5726 in another expression. */
5728 static enum gimplify_status
5729 gimplify_modify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
5730 bool want_value)
5732 tree *from_p = &TREE_OPERAND (*expr_p, 1);
5733 tree *to_p = &TREE_OPERAND (*expr_p, 0);
5734 enum gimplify_status ret = GS_UNHANDLED;
5735 gimple *assign;
5736 location_t loc = EXPR_LOCATION (*expr_p);
5737 gimple_stmt_iterator gsi;
5739 gcc_assert (TREE_CODE (*expr_p) == MODIFY_EXPR
5740 || TREE_CODE (*expr_p) == INIT_EXPR);
5742 /* Trying to simplify a clobber using normal logic doesn't work,
5743 so handle it here. */
5744 if (TREE_CLOBBER_P (*from_p))
5746 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
5747 if (ret == GS_ERROR)
5748 return ret;
5749 gcc_assert (!want_value);
5750 if (!VAR_P (*to_p) && TREE_CODE (*to_p) != MEM_REF)
5752 tree addr = get_initialized_tmp_var (build_fold_addr_expr (*to_p),
5753 pre_p, post_p);
5754 *to_p = build_simple_mem_ref_loc (EXPR_LOCATION (*to_p), addr);
5756 gimplify_seq_add_stmt (pre_p, gimple_build_assign (*to_p, *from_p));
5757 *expr_p = NULL;
5758 return GS_ALL_DONE;
5761 /* Insert pointer conversions required by the middle-end that are not
5762 required by the frontend. This fixes middle-end type checking for
5763 for example gcc.dg/redecl-6.c. */
5764 if (POINTER_TYPE_P (TREE_TYPE (*to_p)))
5766 STRIP_USELESS_TYPE_CONVERSION (*from_p);
5767 if (!useless_type_conversion_p (TREE_TYPE (*to_p), TREE_TYPE (*from_p)))
5768 *from_p = fold_convert_loc (loc, TREE_TYPE (*to_p), *from_p);
5771 /* See if any simplifications can be done based on what the RHS is. */
5772 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
5773 want_value);
5774 if (ret != GS_UNHANDLED)
5775 return ret;
5777 /* For zero sized types only gimplify the left hand side and right hand
5778 side as statements and throw away the assignment. Do this after
5779 gimplify_modify_expr_rhs so we handle TARGET_EXPRs of addressable
5780 types properly. */
5781 if (zero_sized_type (TREE_TYPE (*from_p))
5782 && !want_value
5783 /* Don't do this for calls that return addressable types, expand_call
5784 relies on those having a lhs. */
5785 && !(TREE_ADDRESSABLE (TREE_TYPE (*from_p))
5786 && TREE_CODE (*from_p) == CALL_EXPR))
5788 gimplify_stmt (from_p, pre_p);
5789 gimplify_stmt (to_p, pre_p);
5790 *expr_p = NULL_TREE;
5791 return GS_ALL_DONE;
5794 /* If the value being copied is of variable width, compute the length
5795 of the copy into a WITH_SIZE_EXPR. Note that we need to do this
5796 before gimplifying any of the operands so that we can resolve any
5797 PLACEHOLDER_EXPRs in the size. Also note that the RTL expander uses
5798 the size of the expression to be copied, not of the destination, so
5799 that is what we must do here. */
5800 maybe_with_size_expr (from_p);
5802 /* As a special case, we have to temporarily allow for assignments
5803 with a CALL_EXPR on the RHS. Since in GIMPLE a function call is
5804 a toplevel statement, when gimplifying the GENERIC expression
5805 MODIFY_EXPR <a, CALL_EXPR <foo>>, we cannot create the tuple
5806 GIMPLE_ASSIGN <a, GIMPLE_CALL <foo>>.
5808 Instead, we need to create the tuple GIMPLE_CALL <a, foo>. To
5809 prevent gimplify_expr from trying to create a new temporary for
5810 foo's LHS, we tell it that it should only gimplify until it
5811 reaches the CALL_EXPR. On return from gimplify_expr, the newly
5812 created GIMPLE_CALL <foo> will be the last statement in *PRE_P
5813 and all we need to do here is set 'a' to be its LHS. */
5815 /* Gimplify the RHS first for C++17 and bug 71104. */
5816 gimple_predicate initial_pred = initial_rhs_predicate_for (*to_p);
5817 ret = gimplify_expr (from_p, pre_p, post_p, initial_pred, fb_rvalue);
5818 if (ret == GS_ERROR)
5819 return ret;
5821 /* Then gimplify the LHS. */
5822 /* If we gimplified the RHS to a CALL_EXPR and that call may return
5823 twice we have to make sure to gimplify into non-SSA as otherwise
5824 the abnormal edge added later will make those defs not dominate
5825 their uses.
5826 ??? Technically this applies only to the registers used in the
5827 resulting non-register *TO_P. */
5828 bool saved_into_ssa = gimplify_ctxp->into_ssa;
5829 if (saved_into_ssa
5830 && TREE_CODE (*from_p) == CALL_EXPR
5831 && call_expr_flags (*from_p) & ECF_RETURNS_TWICE)
5832 gimplify_ctxp->into_ssa = false;
5833 ret = gimplify_expr (to_p, pre_p, post_p, is_gimple_lvalue, fb_lvalue);
5834 gimplify_ctxp->into_ssa = saved_into_ssa;
5835 if (ret == GS_ERROR)
5836 return ret;
5838 /* Now that the LHS is gimplified, re-gimplify the RHS if our initial
5839 guess for the predicate was wrong. */
5840 gimple_predicate final_pred = rhs_predicate_for (*to_p);
5841 if (final_pred != initial_pred)
5843 ret = gimplify_expr (from_p, pre_p, post_p, final_pred, fb_rvalue);
5844 if (ret == GS_ERROR)
5845 return ret;
5848 /* In case of va_arg internal fn wrappped in a WITH_SIZE_EXPR, add the type
5849 size as argument to the call. */
5850 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
5852 tree call = TREE_OPERAND (*from_p, 0);
5853 tree vlasize = TREE_OPERAND (*from_p, 1);
5855 if (TREE_CODE (call) == CALL_EXPR
5856 && CALL_EXPR_IFN (call) == IFN_VA_ARG)
5858 int nargs = call_expr_nargs (call);
5859 tree type = TREE_TYPE (call);
5860 tree ap = CALL_EXPR_ARG (call, 0);
5861 tree tag = CALL_EXPR_ARG (call, 1);
5862 tree aptag = CALL_EXPR_ARG (call, 2);
5863 tree newcall = build_call_expr_internal_loc (EXPR_LOCATION (call),
5864 IFN_VA_ARG, type,
5865 nargs + 1, ap, tag,
5866 aptag, vlasize);
5867 TREE_OPERAND (*from_p, 0) = newcall;
5871 /* Now see if the above changed *from_p to something we handle specially. */
5872 ret = gimplify_modify_expr_rhs (expr_p, from_p, to_p, pre_p, post_p,
5873 want_value);
5874 if (ret != GS_UNHANDLED)
5875 return ret;
5877 /* If we've got a variable sized assignment between two lvalues (i.e. does
5878 not involve a call), then we can make things a bit more straightforward
5879 by converting the assignment to memcpy or memset. */
5880 if (TREE_CODE (*from_p) == WITH_SIZE_EXPR)
5882 tree from = TREE_OPERAND (*from_p, 0);
5883 tree size = TREE_OPERAND (*from_p, 1);
5885 if (TREE_CODE (from) == CONSTRUCTOR)
5886 return gimplify_modify_expr_to_memset (expr_p, size, want_value, pre_p);
5888 if (is_gimple_addressable (from))
5890 *from_p = from;
5891 return gimplify_modify_expr_to_memcpy (expr_p, size, want_value,
5892 pre_p);
5896 /* Transform partial stores to non-addressable complex variables into
5897 total stores. This allows us to use real instead of virtual operands
5898 for these variables, which improves optimization. */
5899 if ((TREE_CODE (*to_p) == REALPART_EXPR
5900 || TREE_CODE (*to_p) == IMAGPART_EXPR)
5901 && is_gimple_reg (TREE_OPERAND (*to_p, 0)))
5902 return gimplify_modify_expr_complex_part (expr_p, pre_p, want_value);
5904 /* Try to alleviate the effects of the gimplification creating artificial
5905 temporaries (see for example is_gimple_reg_rhs) on the debug info, but
5906 make sure not to create DECL_DEBUG_EXPR links across functions. */
5907 if (!gimplify_ctxp->into_ssa
5908 && VAR_P (*from_p)
5909 && DECL_IGNORED_P (*from_p)
5910 && DECL_P (*to_p)
5911 && !DECL_IGNORED_P (*to_p)
5912 && decl_function_context (*to_p) == current_function_decl
5913 && decl_function_context (*from_p) == current_function_decl)
5915 if (!DECL_NAME (*from_p) && DECL_NAME (*to_p))
5916 DECL_NAME (*from_p)
5917 = create_tmp_var_name (IDENTIFIER_POINTER (DECL_NAME (*to_p)));
5918 DECL_HAS_DEBUG_EXPR_P (*from_p) = 1;
5919 SET_DECL_DEBUG_EXPR (*from_p, *to_p);
5922 if (want_value && TREE_THIS_VOLATILE (*to_p))
5923 *from_p = get_initialized_tmp_var (*from_p, pre_p, post_p);
5925 if (TREE_CODE (*from_p) == CALL_EXPR)
5927 /* Since the RHS is a CALL_EXPR, we need to create a GIMPLE_CALL
5928 instead of a GIMPLE_ASSIGN. */
5929 gcall *call_stmt;
5930 if (CALL_EXPR_FN (*from_p) == NULL_TREE)
5932 /* Gimplify internal functions created in the FEs. */
5933 int nargs = call_expr_nargs (*from_p), i;
5934 enum internal_fn ifn = CALL_EXPR_IFN (*from_p);
5935 auto_vec<tree> vargs (nargs);
5937 for (i = 0; i < nargs; i++)
5939 gimplify_arg (&CALL_EXPR_ARG (*from_p, i), pre_p,
5940 EXPR_LOCATION (*from_p));
5941 vargs.quick_push (CALL_EXPR_ARG (*from_p, i));
5943 call_stmt = gimple_build_call_internal_vec (ifn, vargs);
5944 gimple_call_set_nothrow (call_stmt, TREE_NOTHROW (*from_p));
5945 gimple_set_location (call_stmt, EXPR_LOCATION (*expr_p));
5947 else
5949 tree fnptrtype = TREE_TYPE (CALL_EXPR_FN (*from_p));
5950 CALL_EXPR_FN (*from_p) = TREE_OPERAND (CALL_EXPR_FN (*from_p), 0);
5951 STRIP_USELESS_TYPE_CONVERSION (CALL_EXPR_FN (*from_p));
5952 tree fndecl = get_callee_fndecl (*from_p);
5953 if (fndecl
5954 && fndecl_built_in_p (fndecl, BUILT_IN_EXPECT)
5955 && call_expr_nargs (*from_p) == 3)
5956 call_stmt = gimple_build_call_internal (IFN_BUILTIN_EXPECT, 3,
5957 CALL_EXPR_ARG (*from_p, 0),
5958 CALL_EXPR_ARG (*from_p, 1),
5959 CALL_EXPR_ARG (*from_p, 2));
5960 else
5962 call_stmt = gimple_build_call_from_tree (*from_p, fnptrtype);
5965 notice_special_calls (call_stmt);
5966 if (!gimple_call_noreturn_p (call_stmt) || !should_remove_lhs_p (*to_p))
5967 gimple_call_set_lhs (call_stmt, *to_p);
5968 else if (TREE_CODE (*to_p) == SSA_NAME)
5969 /* The above is somewhat premature, avoid ICEing later for a
5970 SSA name w/o a definition. We may have uses in the GIMPLE IL.
5971 ??? This doesn't make it a default-def. */
5972 SSA_NAME_DEF_STMT (*to_p) = gimple_build_nop ();
5974 assign = call_stmt;
5976 else
5978 assign = gimple_build_assign (*to_p, *from_p);
5979 gimple_set_location (assign, EXPR_LOCATION (*expr_p));
5980 if (COMPARISON_CLASS_P (*from_p))
5981 gimple_set_no_warning (assign, TREE_NO_WARNING (*from_p));
5984 if (gimplify_ctxp->into_ssa && is_gimple_reg (*to_p))
5986 /* We should have got an SSA name from the start. */
5987 gcc_assert (TREE_CODE (*to_p) == SSA_NAME
5988 || ! gimple_in_ssa_p (cfun));
5991 gimplify_seq_add_stmt (pre_p, assign);
5992 gsi = gsi_last (*pre_p);
5993 maybe_fold_stmt (&gsi);
5995 if (want_value)
5997 *expr_p = TREE_THIS_VOLATILE (*to_p) ? *from_p : unshare_expr (*to_p);
5998 return GS_OK;
6000 else
6001 *expr_p = NULL;
6003 return GS_ALL_DONE;
6006 /* Gimplify a comparison between two variable-sized objects. Do this
6007 with a call to BUILT_IN_MEMCMP. */
6009 static enum gimplify_status
6010 gimplify_variable_sized_compare (tree *expr_p)
6012 location_t loc = EXPR_LOCATION (*expr_p);
6013 tree op0 = TREE_OPERAND (*expr_p, 0);
6014 tree op1 = TREE_OPERAND (*expr_p, 1);
6015 tree t, arg, dest, src, expr;
6017 arg = TYPE_SIZE_UNIT (TREE_TYPE (op0));
6018 arg = unshare_expr (arg);
6019 arg = SUBSTITUTE_PLACEHOLDER_IN_EXPR (arg, op0);
6020 src = build_fold_addr_expr_loc (loc, op1);
6021 dest = build_fold_addr_expr_loc (loc, op0);
6022 t = builtin_decl_implicit (BUILT_IN_MEMCMP);
6023 t = build_call_expr_loc (loc, t, 3, dest, src, arg);
6025 expr
6026 = build2 (TREE_CODE (*expr_p), TREE_TYPE (*expr_p), t, integer_zero_node);
6027 SET_EXPR_LOCATION (expr, loc);
6028 *expr_p = expr;
6030 return GS_OK;
6033 /* Gimplify a comparison between two aggregate objects of integral scalar
6034 mode as a comparison between the bitwise equivalent scalar values. */
6036 static enum gimplify_status
6037 gimplify_scalar_mode_aggregate_compare (tree *expr_p)
6039 location_t loc = EXPR_LOCATION (*expr_p);
6040 tree op0 = TREE_OPERAND (*expr_p, 0);
6041 tree op1 = TREE_OPERAND (*expr_p, 1);
6043 tree type = TREE_TYPE (op0);
6044 tree scalar_type = lang_hooks.types.type_for_mode (TYPE_MODE (type), 1);
6046 op0 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op0);
6047 op1 = fold_build1_loc (loc, VIEW_CONVERT_EXPR, scalar_type, op1);
6049 *expr_p
6050 = fold_build2_loc (loc, TREE_CODE (*expr_p), TREE_TYPE (*expr_p), op0, op1);
6052 return GS_OK;
6055 /* Gimplify an expression sequence. This function gimplifies each
6056 expression and rewrites the original expression with the last
6057 expression of the sequence in GIMPLE form.
6059 PRE_P points to the list where the side effects for all the
6060 expressions in the sequence will be emitted.
6062 WANT_VALUE is true when the result of the last COMPOUND_EXPR is used. */
6064 static enum gimplify_status
6065 gimplify_compound_expr (tree *expr_p, gimple_seq *pre_p, bool want_value)
6067 tree t = *expr_p;
6071 tree *sub_p = &TREE_OPERAND (t, 0);
6073 if (TREE_CODE (*sub_p) == COMPOUND_EXPR)
6074 gimplify_compound_expr (sub_p, pre_p, false);
6075 else
6076 gimplify_stmt (sub_p, pre_p);
6078 t = TREE_OPERAND (t, 1);
6080 while (TREE_CODE (t) == COMPOUND_EXPR);
6082 *expr_p = t;
6083 if (want_value)
6084 return GS_OK;
6085 else
6087 gimplify_stmt (expr_p, pre_p);
6088 return GS_ALL_DONE;
6092 /* Gimplify a SAVE_EXPR node. EXPR_P points to the expression to
6093 gimplify. After gimplification, EXPR_P will point to a new temporary
6094 that holds the original value of the SAVE_EXPR node.
6096 PRE_P points to the list where side effects that must happen before
6097 *EXPR_P should be stored. */
6099 static enum gimplify_status
6100 gimplify_save_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6102 enum gimplify_status ret = GS_ALL_DONE;
6103 tree val;
6105 gcc_assert (TREE_CODE (*expr_p) == SAVE_EXPR);
6106 val = TREE_OPERAND (*expr_p, 0);
6108 /* If the SAVE_EXPR has not been resolved, then evaluate it once. */
6109 if (!SAVE_EXPR_RESOLVED_P (*expr_p))
6111 /* The operand may be a void-valued expression. It is
6112 being executed only for its side-effects. */
6113 if (TREE_TYPE (val) == void_type_node)
6115 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
6116 is_gimple_stmt, fb_none);
6117 val = NULL;
6119 else
6120 /* The temporary may not be an SSA name as later abnormal and EH
6121 control flow may invalidate use/def domination. When in SSA
6122 form then assume there are no such issues and SAVE_EXPRs only
6123 appear via GENERIC foldings. */
6124 val = get_initialized_tmp_var (val, pre_p, post_p,
6125 gimple_in_ssa_p (cfun));
6127 TREE_OPERAND (*expr_p, 0) = val;
6128 SAVE_EXPR_RESOLVED_P (*expr_p) = 1;
6131 *expr_p = val;
6133 return ret;
6136 /* Rewrite the ADDR_EXPR node pointed to by EXPR_P
6138 unary_expr
6139 : ...
6140 | '&' varname
6143 PRE_P points to the list where side effects that must happen before
6144 *EXPR_P should be stored.
6146 POST_P points to the list where side effects that must happen after
6147 *EXPR_P should be stored. */
6149 static enum gimplify_status
6150 gimplify_addr_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6152 tree expr = *expr_p;
6153 tree op0 = TREE_OPERAND (expr, 0);
6154 enum gimplify_status ret;
6155 location_t loc = EXPR_LOCATION (*expr_p);
6157 switch (TREE_CODE (op0))
6159 case INDIRECT_REF:
6160 do_indirect_ref:
6161 /* Check if we are dealing with an expression of the form '&*ptr'.
6162 While the front end folds away '&*ptr' into 'ptr', these
6163 expressions may be generated internally by the compiler (e.g.,
6164 builtins like __builtin_va_end). */
6165 /* Caution: the silent array decomposition semantics we allow for
6166 ADDR_EXPR means we can't always discard the pair. */
6167 /* Gimplification of the ADDR_EXPR operand may drop
6168 cv-qualification conversions, so make sure we add them if
6169 needed. */
6171 tree op00 = TREE_OPERAND (op0, 0);
6172 tree t_expr = TREE_TYPE (expr);
6173 tree t_op00 = TREE_TYPE (op00);
6175 if (!useless_type_conversion_p (t_expr, t_op00))
6176 op00 = fold_convert_loc (loc, TREE_TYPE (expr), op00);
6177 *expr_p = op00;
6178 ret = GS_OK;
6180 break;
6182 case VIEW_CONVERT_EXPR:
6183 /* Take the address of our operand and then convert it to the type of
6184 this ADDR_EXPR.
6186 ??? The interactions of VIEW_CONVERT_EXPR and aliasing is not at
6187 all clear. The impact of this transformation is even less clear. */
6189 /* If the operand is a useless conversion, look through it. Doing so
6190 guarantees that the ADDR_EXPR and its operand will remain of the
6191 same type. */
6192 if (tree_ssa_useless_type_conversion (TREE_OPERAND (op0, 0)))
6193 op0 = TREE_OPERAND (op0, 0);
6195 *expr_p = fold_convert_loc (loc, TREE_TYPE (expr),
6196 build_fold_addr_expr_loc (loc,
6197 TREE_OPERAND (op0, 0)));
6198 ret = GS_OK;
6199 break;
6201 case MEM_REF:
6202 if (integer_zerop (TREE_OPERAND (op0, 1)))
6203 goto do_indirect_ref;
6205 /* fall through */
6207 default:
6208 /* If we see a call to a declared builtin or see its address
6209 being taken (we can unify those cases here) then we can mark
6210 the builtin for implicit generation by GCC. */
6211 if (TREE_CODE (op0) == FUNCTION_DECL
6212 && fndecl_built_in_p (op0, BUILT_IN_NORMAL)
6213 && builtin_decl_declared_p (DECL_FUNCTION_CODE (op0)))
6214 set_builtin_decl_implicit_p (DECL_FUNCTION_CODE (op0), true);
6216 /* We use fb_either here because the C frontend sometimes takes
6217 the address of a call that returns a struct; see
6218 gcc.dg/c99-array-lval-1.c. The gimplifier will correctly make
6219 the implied temporary explicit. */
6221 /* Make the operand addressable. */
6222 ret = gimplify_expr (&TREE_OPERAND (expr, 0), pre_p, post_p,
6223 is_gimple_addressable, fb_either);
6224 if (ret == GS_ERROR)
6225 break;
6227 /* Then mark it. Beware that it may not be possible to do so directly
6228 if a temporary has been created by the gimplification. */
6229 prepare_gimple_addressable (&TREE_OPERAND (expr, 0), pre_p);
6231 op0 = TREE_OPERAND (expr, 0);
6233 /* For various reasons, the gimplification of the expression
6234 may have made a new INDIRECT_REF. */
6235 if (TREE_CODE (op0) == INDIRECT_REF
6236 || (TREE_CODE (op0) == MEM_REF
6237 && integer_zerop (TREE_OPERAND (op0, 1))))
6238 goto do_indirect_ref;
6240 mark_addressable (TREE_OPERAND (expr, 0));
6242 /* The FEs may end up building ADDR_EXPRs early on a decl with
6243 an incomplete type. Re-build ADDR_EXPRs in canonical form
6244 here. */
6245 if (!types_compatible_p (TREE_TYPE (op0), TREE_TYPE (TREE_TYPE (expr))))
6246 *expr_p = build_fold_addr_expr (op0);
6248 /* Make sure TREE_CONSTANT and TREE_SIDE_EFFECTS are set properly. */
6249 recompute_tree_invariant_for_addr_expr (*expr_p);
6251 /* If we re-built the ADDR_EXPR add a conversion to the original type
6252 if required. */
6253 if (!useless_type_conversion_p (TREE_TYPE (expr), TREE_TYPE (*expr_p)))
6254 *expr_p = fold_convert (TREE_TYPE (expr), *expr_p);
6256 break;
6259 return ret;
6262 /* Gimplify the operands of an ASM_EXPR. Input operands should be a gimple
6263 value; output operands should be a gimple lvalue. */
6265 static enum gimplify_status
6266 gimplify_asm_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6268 tree expr;
6269 int noutputs;
6270 const char **oconstraints;
6271 int i;
6272 tree link;
6273 const char *constraint;
6274 bool allows_mem, allows_reg, is_inout;
6275 enum gimplify_status ret, tret;
6276 gasm *stmt;
6277 vec<tree, va_gc> *inputs;
6278 vec<tree, va_gc> *outputs;
6279 vec<tree, va_gc> *clobbers;
6280 vec<tree, va_gc> *labels;
6281 tree link_next;
6283 expr = *expr_p;
6284 noutputs = list_length (ASM_OUTPUTS (expr));
6285 oconstraints = (const char **) alloca ((noutputs) * sizeof (const char *));
6287 inputs = NULL;
6288 outputs = NULL;
6289 clobbers = NULL;
6290 labels = NULL;
6292 ret = GS_ALL_DONE;
6293 link_next = NULL_TREE;
6294 for (i = 0, link = ASM_OUTPUTS (expr); link; ++i, link = link_next)
6296 bool ok;
6297 size_t constraint_len;
6299 link_next = TREE_CHAIN (link);
6301 oconstraints[i]
6302 = constraint
6303 = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
6304 constraint_len = strlen (constraint);
6305 if (constraint_len == 0)
6306 continue;
6308 ok = parse_output_constraint (&constraint, i, 0, 0,
6309 &allows_mem, &allows_reg, &is_inout);
6310 if (!ok)
6312 ret = GS_ERROR;
6313 is_inout = false;
6316 /* If we can't make copies, we can only accept memory.
6317 Similarly for VLAs. */
6318 tree outtype = TREE_TYPE (TREE_VALUE (link));
6319 if (outtype != error_mark_node
6320 && (TREE_ADDRESSABLE (outtype)
6321 || !COMPLETE_TYPE_P (outtype)
6322 || !tree_fits_poly_uint64_p (TYPE_SIZE_UNIT (outtype))))
6324 if (allows_mem)
6325 allows_reg = 0;
6326 else
6328 error ("impossible constraint in %<asm%>");
6329 error ("non-memory output %d must stay in memory", i);
6330 return GS_ERROR;
6334 if (!allows_reg && allows_mem)
6335 mark_addressable (TREE_VALUE (link));
6337 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6338 is_inout ? is_gimple_min_lval : is_gimple_lvalue,
6339 fb_lvalue | fb_mayfail);
6340 if (tret == GS_ERROR)
6342 error ("invalid lvalue in %<asm%> output %d", i);
6343 ret = tret;
6346 /* If the constraint does not allow memory make sure we gimplify
6347 it to a register if it is not already but its base is. This
6348 happens for complex and vector components. */
6349 if (!allows_mem)
6351 tree op = TREE_VALUE (link);
6352 if (! is_gimple_val (op)
6353 && is_gimple_reg_type (TREE_TYPE (op))
6354 && is_gimple_reg (get_base_address (op)))
6356 tree tem = create_tmp_reg (TREE_TYPE (op));
6357 tree ass;
6358 if (is_inout)
6360 ass = build2 (MODIFY_EXPR, TREE_TYPE (tem),
6361 tem, unshare_expr (op));
6362 gimplify_and_add (ass, pre_p);
6364 ass = build2 (MODIFY_EXPR, TREE_TYPE (tem), op, tem);
6365 gimplify_and_add (ass, post_p);
6367 TREE_VALUE (link) = tem;
6368 tret = GS_OK;
6372 vec_safe_push (outputs, link);
6373 TREE_CHAIN (link) = NULL_TREE;
6375 if (is_inout)
6377 /* An input/output operand. To give the optimizers more
6378 flexibility, split it into separate input and output
6379 operands. */
6380 tree input;
6381 /* Buffer big enough to format a 32-bit UINT_MAX into. */
6382 char buf[11];
6384 /* Turn the in/out constraint into an output constraint. */
6385 char *p = xstrdup (constraint);
6386 p[0] = '=';
6387 TREE_VALUE (TREE_PURPOSE (link)) = build_string (constraint_len, p);
6389 /* And add a matching input constraint. */
6390 if (allows_reg)
6392 sprintf (buf, "%u", i);
6394 /* If there are multiple alternatives in the constraint,
6395 handle each of them individually. Those that allow register
6396 will be replaced with operand number, the others will stay
6397 unchanged. */
6398 if (strchr (p, ',') != NULL)
6400 size_t len = 0, buflen = strlen (buf);
6401 char *beg, *end, *str, *dst;
6403 for (beg = p + 1;;)
6405 end = strchr (beg, ',');
6406 if (end == NULL)
6407 end = strchr (beg, '\0');
6408 if ((size_t) (end - beg) < buflen)
6409 len += buflen + 1;
6410 else
6411 len += end - beg + 1;
6412 if (*end)
6413 beg = end + 1;
6414 else
6415 break;
6418 str = (char *) alloca (len);
6419 for (beg = p + 1, dst = str;;)
6421 const char *tem;
6422 bool mem_p, reg_p, inout_p;
6424 end = strchr (beg, ',');
6425 if (end)
6426 *end = '\0';
6427 beg[-1] = '=';
6428 tem = beg - 1;
6429 parse_output_constraint (&tem, i, 0, 0,
6430 &mem_p, &reg_p, &inout_p);
6431 if (dst != str)
6432 *dst++ = ',';
6433 if (reg_p)
6435 memcpy (dst, buf, buflen);
6436 dst += buflen;
6438 else
6440 if (end)
6441 len = end - beg;
6442 else
6443 len = strlen (beg);
6444 memcpy (dst, beg, len);
6445 dst += len;
6447 if (end)
6448 beg = end + 1;
6449 else
6450 break;
6452 *dst = '\0';
6453 input = build_string (dst - str, str);
6455 else
6456 input = build_string (strlen (buf), buf);
6458 else
6459 input = build_string (constraint_len - 1, constraint + 1);
6461 free (p);
6463 input = build_tree_list (build_tree_list (NULL_TREE, input),
6464 unshare_expr (TREE_VALUE (link)));
6465 ASM_INPUTS (expr) = chainon (ASM_INPUTS (expr), input);
6469 link_next = NULL_TREE;
6470 for (link = ASM_INPUTS (expr); link; ++i, link = link_next)
6472 link_next = TREE_CHAIN (link);
6473 constraint = TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
6474 parse_input_constraint (&constraint, 0, 0, noutputs, 0,
6475 oconstraints, &allows_mem, &allows_reg);
6477 /* If we can't make copies, we can only accept memory. */
6478 tree intype = TREE_TYPE (TREE_VALUE (link));
6479 if (intype != error_mark_node
6480 && (TREE_ADDRESSABLE (intype)
6481 || !COMPLETE_TYPE_P (intype)
6482 || !tree_fits_poly_uint64_p (TYPE_SIZE_UNIT (intype))))
6484 if (allows_mem)
6485 allows_reg = 0;
6486 else
6488 error ("impossible constraint in %<asm%>");
6489 error ("non-memory input %d must stay in memory", i);
6490 return GS_ERROR;
6494 /* If the operand is a memory input, it should be an lvalue. */
6495 if (!allows_reg && allows_mem)
6497 tree inputv = TREE_VALUE (link);
6498 STRIP_NOPS (inputv);
6499 if (TREE_CODE (inputv) == PREDECREMENT_EXPR
6500 || TREE_CODE (inputv) == PREINCREMENT_EXPR
6501 || TREE_CODE (inputv) == POSTDECREMENT_EXPR
6502 || TREE_CODE (inputv) == POSTINCREMENT_EXPR
6503 || TREE_CODE (inputv) == MODIFY_EXPR)
6504 TREE_VALUE (link) = error_mark_node;
6505 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6506 is_gimple_lvalue, fb_lvalue | fb_mayfail);
6507 if (tret != GS_ERROR)
6509 /* Unlike output operands, memory inputs are not guaranteed
6510 to be lvalues by the FE, and while the expressions are
6511 marked addressable there, if it is e.g. a statement
6512 expression, temporaries in it might not end up being
6513 addressable. They might be already used in the IL and thus
6514 it is too late to make them addressable now though. */
6515 tree x = TREE_VALUE (link);
6516 while (handled_component_p (x))
6517 x = TREE_OPERAND (x, 0);
6518 if (TREE_CODE (x) == MEM_REF
6519 && TREE_CODE (TREE_OPERAND (x, 0)) == ADDR_EXPR)
6520 x = TREE_OPERAND (TREE_OPERAND (x, 0), 0);
6521 if ((VAR_P (x)
6522 || TREE_CODE (x) == PARM_DECL
6523 || TREE_CODE (x) == RESULT_DECL)
6524 && !TREE_ADDRESSABLE (x)
6525 && is_gimple_reg (x))
6527 warning_at (EXPR_LOC_OR_LOC (TREE_VALUE (link),
6528 input_location), 0,
6529 "memory input %d is not directly addressable",
6531 prepare_gimple_addressable (&TREE_VALUE (link), pre_p);
6534 mark_addressable (TREE_VALUE (link));
6535 if (tret == GS_ERROR)
6537 error_at (EXPR_LOC_OR_LOC (TREE_VALUE (link), input_location),
6538 "memory input %d is not directly addressable", i);
6539 ret = tret;
6542 else
6544 tret = gimplify_expr (&TREE_VALUE (link), pre_p, post_p,
6545 is_gimple_asm_val, fb_rvalue);
6546 if (tret == GS_ERROR)
6547 ret = tret;
6550 TREE_CHAIN (link) = NULL_TREE;
6551 vec_safe_push (inputs, link);
6554 link_next = NULL_TREE;
6555 for (link = ASM_CLOBBERS (expr); link; ++i, link = link_next)
6557 link_next = TREE_CHAIN (link);
6558 TREE_CHAIN (link) = NULL_TREE;
6559 vec_safe_push (clobbers, link);
6562 link_next = NULL_TREE;
6563 for (link = ASM_LABELS (expr); link; ++i, link = link_next)
6565 link_next = TREE_CHAIN (link);
6566 TREE_CHAIN (link) = NULL_TREE;
6567 vec_safe_push (labels, link);
6570 /* Do not add ASMs with errors to the gimple IL stream. */
6571 if (ret != GS_ERROR)
6573 stmt = gimple_build_asm_vec (TREE_STRING_POINTER (ASM_STRING (expr)),
6574 inputs, outputs, clobbers, labels);
6576 gimple_asm_set_volatile (stmt, ASM_VOLATILE_P (expr) || noutputs == 0);
6577 gimple_asm_set_input (stmt, ASM_INPUT_P (expr));
6578 gimple_asm_set_inline (stmt, ASM_INLINE_P (expr));
6580 gimplify_seq_add_stmt (pre_p, stmt);
6583 return ret;
6586 /* Gimplify a CLEANUP_POINT_EXPR. Currently this works by adding
6587 GIMPLE_WITH_CLEANUP_EXPRs to the prequeue as we encounter cleanups while
6588 gimplifying the body, and converting them to TRY_FINALLY_EXPRs when we
6589 return to this function.
6591 FIXME should we complexify the prequeue handling instead? Or use flags
6592 for all the cleanups and let the optimizer tighten them up? The current
6593 code seems pretty fragile; it will break on a cleanup within any
6594 non-conditional nesting. But any such nesting would be broken, anyway;
6595 we can't write a TRY_FINALLY_EXPR that starts inside a nesting construct
6596 and continues out of it. We can do that at the RTL level, though, so
6597 having an optimizer to tighten up try/finally regions would be a Good
6598 Thing. */
6600 static enum gimplify_status
6601 gimplify_cleanup_point_expr (tree *expr_p, gimple_seq *pre_p)
6603 gimple_stmt_iterator iter;
6604 gimple_seq body_sequence = NULL;
6606 tree temp = voidify_wrapper_expr (*expr_p, NULL);
6608 /* We only care about the number of conditions between the innermost
6609 CLEANUP_POINT_EXPR and the cleanup. So save and reset the count and
6610 any cleanups collected outside the CLEANUP_POINT_EXPR. */
6611 int old_conds = gimplify_ctxp->conditions;
6612 gimple_seq old_cleanups = gimplify_ctxp->conditional_cleanups;
6613 bool old_in_cleanup_point_expr = gimplify_ctxp->in_cleanup_point_expr;
6614 gimplify_ctxp->conditions = 0;
6615 gimplify_ctxp->conditional_cleanups = NULL;
6616 gimplify_ctxp->in_cleanup_point_expr = true;
6618 gimplify_stmt (&TREE_OPERAND (*expr_p, 0), &body_sequence);
6620 gimplify_ctxp->conditions = old_conds;
6621 gimplify_ctxp->conditional_cleanups = old_cleanups;
6622 gimplify_ctxp->in_cleanup_point_expr = old_in_cleanup_point_expr;
6624 for (iter = gsi_start (body_sequence); !gsi_end_p (iter); )
6626 gimple *wce = gsi_stmt (iter);
6628 if (gimple_code (wce) == GIMPLE_WITH_CLEANUP_EXPR)
6630 if (gsi_one_before_end_p (iter))
6632 /* Note that gsi_insert_seq_before and gsi_remove do not
6633 scan operands, unlike some other sequence mutators. */
6634 if (!gimple_wce_cleanup_eh_only (wce))
6635 gsi_insert_seq_before_without_update (&iter,
6636 gimple_wce_cleanup (wce),
6637 GSI_SAME_STMT);
6638 gsi_remove (&iter, true);
6639 break;
6641 else
6643 gtry *gtry;
6644 gimple_seq seq;
6645 enum gimple_try_flags kind;
6647 if (gimple_wce_cleanup_eh_only (wce))
6648 kind = GIMPLE_TRY_CATCH;
6649 else
6650 kind = GIMPLE_TRY_FINALLY;
6651 seq = gsi_split_seq_after (iter);
6653 gtry = gimple_build_try (seq, gimple_wce_cleanup (wce), kind);
6654 /* Do not use gsi_replace here, as it may scan operands.
6655 We want to do a simple structural modification only. */
6656 gsi_set_stmt (&iter, gtry);
6657 iter = gsi_start (gtry->eval);
6660 else
6661 gsi_next (&iter);
6664 gimplify_seq_add_seq (pre_p, body_sequence);
6665 if (temp)
6667 *expr_p = temp;
6668 return GS_OK;
6670 else
6672 *expr_p = NULL;
6673 return GS_ALL_DONE;
6677 /* Insert a cleanup marker for gimplify_cleanup_point_expr. CLEANUP
6678 is the cleanup action required. EH_ONLY is true if the cleanup should
6679 only be executed if an exception is thrown, not on normal exit.
6680 If FORCE_UNCOND is true perform the cleanup unconditionally; this is
6681 only valid for clobbers. */
6683 static void
6684 gimple_push_cleanup (tree var, tree cleanup, bool eh_only, gimple_seq *pre_p,
6685 bool force_uncond = false)
6687 gimple *wce;
6688 gimple_seq cleanup_stmts = NULL;
6690 /* Errors can result in improperly nested cleanups. Which results in
6691 confusion when trying to resolve the GIMPLE_WITH_CLEANUP_EXPR. */
6692 if (seen_error ())
6693 return;
6695 if (gimple_conditional_context ())
6697 /* If we're in a conditional context, this is more complex. We only
6698 want to run the cleanup if we actually ran the initialization that
6699 necessitates it, but we want to run it after the end of the
6700 conditional context. So we wrap the try/finally around the
6701 condition and use a flag to determine whether or not to actually
6702 run the destructor. Thus
6704 test ? f(A()) : 0
6706 becomes (approximately)
6708 flag = 0;
6709 try {
6710 if (test) { A::A(temp); flag = 1; val = f(temp); }
6711 else { val = 0; }
6712 } finally {
6713 if (flag) A::~A(temp);
6717 if (force_uncond)
6719 gimplify_stmt (&cleanup, &cleanup_stmts);
6720 wce = gimple_build_wce (cleanup_stmts);
6721 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, wce);
6723 else
6725 tree flag = create_tmp_var (boolean_type_node, "cleanup");
6726 gassign *ffalse = gimple_build_assign (flag, boolean_false_node);
6727 gassign *ftrue = gimple_build_assign (flag, boolean_true_node);
6729 cleanup = build3 (COND_EXPR, void_type_node, flag, cleanup, NULL);
6730 gimplify_stmt (&cleanup, &cleanup_stmts);
6731 wce = gimple_build_wce (cleanup_stmts);
6733 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, ffalse);
6734 gimplify_seq_add_stmt (&gimplify_ctxp->conditional_cleanups, wce);
6735 gimplify_seq_add_stmt (pre_p, ftrue);
6737 /* Because of this manipulation, and the EH edges that jump
6738 threading cannot redirect, the temporary (VAR) will appear
6739 to be used uninitialized. Don't warn. */
6740 TREE_NO_WARNING (var) = 1;
6743 else
6745 gimplify_stmt (&cleanup, &cleanup_stmts);
6746 wce = gimple_build_wce (cleanup_stmts);
6747 gimple_wce_set_cleanup_eh_only (wce, eh_only);
6748 gimplify_seq_add_stmt (pre_p, wce);
6752 /* Gimplify a TARGET_EXPR which doesn't appear on the rhs of an INIT_EXPR. */
6754 static enum gimplify_status
6755 gimplify_target_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
6757 tree targ = *expr_p;
6758 tree temp = TARGET_EXPR_SLOT (targ);
6759 tree init = TARGET_EXPR_INITIAL (targ);
6760 enum gimplify_status ret;
6762 bool unpoison_empty_seq = false;
6763 gimple_stmt_iterator unpoison_it;
6765 if (init)
6767 tree cleanup = NULL_TREE;
6769 /* TARGET_EXPR temps aren't part of the enclosing block, so add it
6770 to the temps list. Handle also variable length TARGET_EXPRs. */
6771 if (!poly_int_tree_p (DECL_SIZE (temp)))
6773 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (temp)))
6774 gimplify_type_sizes (TREE_TYPE (temp), pre_p);
6775 gimplify_vla_decl (temp, pre_p);
6777 else
6779 /* Save location where we need to place unpoisoning. It's possible
6780 that a variable will be converted to needs_to_live_in_memory. */
6781 unpoison_it = gsi_last (*pre_p);
6782 unpoison_empty_seq = gsi_end_p (unpoison_it);
6784 gimple_add_tmp_var (temp);
6787 /* If TARGET_EXPR_INITIAL is void, then the mere evaluation of the
6788 expression is supposed to initialize the slot. */
6789 if (VOID_TYPE_P (TREE_TYPE (init)))
6790 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
6791 else
6793 tree init_expr = build2 (INIT_EXPR, void_type_node, temp, init);
6794 init = init_expr;
6795 ret = gimplify_expr (&init, pre_p, post_p, is_gimple_stmt, fb_none);
6796 init = NULL;
6797 ggc_free (init_expr);
6799 if (ret == GS_ERROR)
6801 /* PR c++/28266 Make sure this is expanded only once. */
6802 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
6803 return GS_ERROR;
6805 if (init)
6806 gimplify_and_add (init, pre_p);
6808 /* If needed, push the cleanup for the temp. */
6809 if (TARGET_EXPR_CLEANUP (targ))
6811 if (CLEANUP_EH_ONLY (targ))
6812 gimple_push_cleanup (temp, TARGET_EXPR_CLEANUP (targ),
6813 CLEANUP_EH_ONLY (targ), pre_p);
6814 else
6815 cleanup = TARGET_EXPR_CLEANUP (targ);
6818 /* Add a clobber for the temporary going out of scope, like
6819 gimplify_bind_expr. */
6820 if (gimplify_ctxp->in_cleanup_point_expr
6821 && needs_to_live_in_memory (temp))
6823 if (flag_stack_reuse == SR_ALL)
6825 tree clobber = build_clobber (TREE_TYPE (temp));
6826 clobber = build2 (MODIFY_EXPR, TREE_TYPE (temp), temp, clobber);
6827 gimple_push_cleanup (temp, clobber, false, pre_p, true);
6829 if (asan_poisoned_variables
6830 && DECL_ALIGN (temp) <= MAX_SUPPORTED_STACK_ALIGNMENT
6831 && !TREE_STATIC (temp)
6832 && dbg_cnt (asan_use_after_scope)
6833 && !gimplify_omp_ctxp)
6835 tree asan_cleanup = build_asan_poison_call_expr (temp);
6836 if (asan_cleanup)
6838 if (unpoison_empty_seq)
6839 unpoison_it = gsi_start (*pre_p);
6841 asan_poison_variable (temp, false, &unpoison_it,
6842 unpoison_empty_seq);
6843 gimple_push_cleanup (temp, asan_cleanup, false, pre_p);
6847 if (cleanup)
6848 gimple_push_cleanup (temp, cleanup, false, pre_p);
6850 /* Only expand this once. */
6851 TREE_OPERAND (targ, 3) = init;
6852 TARGET_EXPR_INITIAL (targ) = NULL_TREE;
6854 else
6855 /* We should have expanded this before. */
6856 gcc_assert (DECL_SEEN_IN_BIND_EXPR_P (temp));
6858 *expr_p = temp;
6859 return GS_OK;
6862 /* Gimplification of expression trees. */
6864 /* Gimplify an expression which appears at statement context. The
6865 corresponding GIMPLE statements are added to *SEQ_P. If *SEQ_P is
6866 NULL, a new sequence is allocated.
6868 Return true if we actually added a statement to the queue. */
6870 bool
6871 gimplify_stmt (tree *stmt_p, gimple_seq *seq_p)
6873 gimple_seq_node last;
6875 last = gimple_seq_last (*seq_p);
6876 gimplify_expr (stmt_p, seq_p, NULL, is_gimple_stmt, fb_none);
6877 return last != gimple_seq_last (*seq_p);
6880 /* Add FIRSTPRIVATE entries for DECL in the OpenMP the surrounding parallels
6881 to CTX. If entries already exist, force them to be some flavor of private.
6882 If there is no enclosing parallel, do nothing. */
6884 void
6885 omp_firstprivatize_variable (struct gimplify_omp_ctx *ctx, tree decl)
6887 splay_tree_node n;
6889 if (decl == NULL || !DECL_P (decl) || ctx->region_type == ORT_NONE)
6890 return;
6894 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
6895 if (n != NULL)
6897 if (n->value & GOVD_SHARED)
6898 n->value = GOVD_FIRSTPRIVATE | (n->value & GOVD_SEEN);
6899 else if (n->value & GOVD_MAP)
6900 n->value |= GOVD_MAP_TO_ONLY;
6901 else
6902 return;
6904 else if ((ctx->region_type & ORT_TARGET) != 0)
6906 if (ctx->defaultmap[GDMK_SCALAR] & GOVD_FIRSTPRIVATE)
6907 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
6908 else
6909 omp_add_variable (ctx, decl, GOVD_MAP | GOVD_MAP_TO_ONLY);
6911 else if (ctx->region_type != ORT_WORKSHARE
6912 && ctx->region_type != ORT_TASKGROUP
6913 && ctx->region_type != ORT_SIMD
6914 && ctx->region_type != ORT_ACC
6915 && !(ctx->region_type & ORT_TARGET_DATA))
6916 omp_add_variable (ctx, decl, GOVD_FIRSTPRIVATE);
6918 ctx = ctx->outer_context;
6920 while (ctx);
6923 /* Similarly for each of the type sizes of TYPE. */
6925 static void
6926 omp_firstprivatize_type_sizes (struct gimplify_omp_ctx *ctx, tree type)
6928 if (type == NULL || type == error_mark_node)
6929 return;
6930 type = TYPE_MAIN_VARIANT (type);
6932 if (ctx->privatized_types->add (type))
6933 return;
6935 switch (TREE_CODE (type))
6937 case INTEGER_TYPE:
6938 case ENUMERAL_TYPE:
6939 case BOOLEAN_TYPE:
6940 case REAL_TYPE:
6941 case FIXED_POINT_TYPE:
6942 omp_firstprivatize_variable (ctx, TYPE_MIN_VALUE (type));
6943 omp_firstprivatize_variable (ctx, TYPE_MAX_VALUE (type));
6944 break;
6946 case ARRAY_TYPE:
6947 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
6948 omp_firstprivatize_type_sizes (ctx, TYPE_DOMAIN (type));
6949 break;
6951 case RECORD_TYPE:
6952 case UNION_TYPE:
6953 case QUAL_UNION_TYPE:
6955 tree field;
6956 for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
6957 if (TREE_CODE (field) == FIELD_DECL)
6959 omp_firstprivatize_variable (ctx, DECL_FIELD_OFFSET (field));
6960 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (field));
6963 break;
6965 case POINTER_TYPE:
6966 case REFERENCE_TYPE:
6967 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (type));
6968 break;
6970 default:
6971 break;
6974 omp_firstprivatize_variable (ctx, TYPE_SIZE (type));
6975 omp_firstprivatize_variable (ctx, TYPE_SIZE_UNIT (type));
6976 lang_hooks.types.omp_firstprivatize_type_sizes (ctx, type);
6979 /* Add an entry for DECL in the OMP context CTX with FLAGS. */
6981 static void
6982 omp_add_variable (struct gimplify_omp_ctx *ctx, tree decl, unsigned int flags)
6984 splay_tree_node n;
6985 unsigned int nflags;
6986 tree t;
6988 if (error_operand_p (decl) || ctx->region_type == ORT_NONE)
6989 return;
6991 /* Never elide decls whose type has TREE_ADDRESSABLE set. This means
6992 there are constructors involved somewhere. Exception is a shared clause,
6993 there is nothing privatized in that case. */
6994 if ((flags & GOVD_SHARED) == 0
6995 && (TREE_ADDRESSABLE (TREE_TYPE (decl))
6996 || TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (decl))))
6997 flags |= GOVD_SEEN;
6999 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7000 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
7002 /* We shouldn't be re-adding the decl with the same data
7003 sharing class. */
7004 gcc_assert ((n->value & GOVD_DATA_SHARE_CLASS & flags) == 0);
7005 nflags = n->value | flags;
7006 /* The only combination of data sharing classes we should see is
7007 FIRSTPRIVATE and LASTPRIVATE. However, OpenACC permits
7008 reduction variables to be used in data sharing clauses. */
7009 gcc_assert ((ctx->region_type & ORT_ACC) != 0
7010 || ((nflags & GOVD_DATA_SHARE_CLASS)
7011 == (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE))
7012 || (flags & GOVD_DATA_SHARE_CLASS) == 0);
7013 n->value = nflags;
7014 return;
7017 /* When adding a variable-sized variable, we have to handle all sorts
7018 of additional bits of data: the pointer replacement variable, and
7019 the parameters of the type. */
7020 if (DECL_SIZE (decl) && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
7022 /* Add the pointer replacement variable as PRIVATE if the variable
7023 replacement is private, else FIRSTPRIVATE since we'll need the
7024 address of the original variable either for SHARED, or for the
7025 copy into or out of the context. */
7026 if (!(flags & GOVD_LOCAL) && ctx->region_type != ORT_TASKGROUP)
7028 if (flags & GOVD_MAP)
7029 nflags = GOVD_MAP | GOVD_MAP_TO_ONLY | GOVD_EXPLICIT;
7030 else if (flags & GOVD_PRIVATE)
7031 nflags = GOVD_PRIVATE;
7032 else if (((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0
7033 && (flags & GOVD_FIRSTPRIVATE))
7034 || (ctx->region_type == ORT_TARGET_DATA
7035 && (flags & GOVD_DATA_SHARE_CLASS) == 0))
7036 nflags = GOVD_PRIVATE | GOVD_EXPLICIT;
7037 else
7038 nflags = GOVD_FIRSTPRIVATE;
7039 nflags |= flags & GOVD_SEEN;
7040 t = DECL_VALUE_EXPR (decl);
7041 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
7042 t = TREE_OPERAND (t, 0);
7043 gcc_assert (DECL_P (t));
7044 omp_add_variable (ctx, t, nflags);
7047 /* Add all of the variable and type parameters (which should have
7048 been gimplified to a formal temporary) as FIRSTPRIVATE. */
7049 omp_firstprivatize_variable (ctx, DECL_SIZE_UNIT (decl));
7050 omp_firstprivatize_variable (ctx, DECL_SIZE (decl));
7051 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
7053 /* The variable-sized variable itself is never SHARED, only some form
7054 of PRIVATE. The sharing would take place via the pointer variable
7055 which we remapped above. */
7056 if (flags & GOVD_SHARED)
7057 flags = GOVD_SHARED | GOVD_DEBUG_PRIVATE
7058 | (flags & (GOVD_SEEN | GOVD_EXPLICIT));
7060 /* We're going to make use of the TYPE_SIZE_UNIT at least in the
7061 alloca statement we generate for the variable, so make sure it
7062 is available. This isn't automatically needed for the SHARED
7063 case, since we won't be allocating local storage then.
7064 For local variables TYPE_SIZE_UNIT might not be gimplified yet,
7065 in this case omp_notice_variable will be called later
7066 on when it is gimplified. */
7067 else if (! (flags & (GOVD_LOCAL | GOVD_MAP))
7068 && DECL_P (TYPE_SIZE_UNIT (TREE_TYPE (decl))))
7069 omp_notice_variable (ctx, TYPE_SIZE_UNIT (TREE_TYPE (decl)), true);
7071 else if ((flags & (GOVD_MAP | GOVD_LOCAL)) == 0
7072 && lang_hooks.decls.omp_privatize_by_reference (decl))
7074 omp_firstprivatize_type_sizes (ctx, TREE_TYPE (decl));
7076 /* Similar to the direct variable sized case above, we'll need the
7077 size of references being privatized. */
7078 if ((flags & GOVD_SHARED) == 0)
7080 t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
7081 if (t && DECL_P (t))
7082 omp_notice_variable (ctx, t, true);
7086 if (n != NULL)
7087 n->value |= flags;
7088 else
7089 splay_tree_insert (ctx->variables, (splay_tree_key)decl, flags);
7091 /* For reductions clauses in OpenACC loop directives, by default create a
7092 copy clause on the enclosing parallel construct for carrying back the
7093 results. */
7094 if (ctx->region_type == ORT_ACC && (flags & GOVD_REDUCTION))
7096 struct gimplify_omp_ctx *outer_ctx = ctx->outer_context;
7097 while (outer_ctx)
7099 n = splay_tree_lookup (outer_ctx->variables, (splay_tree_key)decl);
7100 if (n != NULL)
7102 /* Ignore local variables and explicitly declared clauses. */
7103 if (n->value & (GOVD_LOCAL | GOVD_EXPLICIT))
7104 break;
7105 else if (outer_ctx->region_type == ORT_ACC_KERNELS)
7107 /* According to the OpenACC spec, such a reduction variable
7108 should already have a copy map on a kernels construct,
7109 verify that here. */
7110 gcc_assert (!(n->value & GOVD_FIRSTPRIVATE)
7111 && (n->value & GOVD_MAP));
7113 else if (outer_ctx->region_type == ORT_ACC_PARALLEL)
7115 /* Remove firstprivate and make it a copy map. */
7116 n->value &= ~GOVD_FIRSTPRIVATE;
7117 n->value |= GOVD_MAP;
7120 else if (outer_ctx->region_type == ORT_ACC_PARALLEL)
7122 splay_tree_insert (outer_ctx->variables, (splay_tree_key)decl,
7123 GOVD_MAP | GOVD_SEEN);
7124 break;
7126 outer_ctx = outer_ctx->outer_context;
7131 /* Notice a threadprivate variable DECL used in OMP context CTX.
7132 This just prints out diagnostics about threadprivate variable uses
7133 in untied tasks. If DECL2 is non-NULL, prevent this warning
7134 on that variable. */
7136 static bool
7137 omp_notice_threadprivate_variable (struct gimplify_omp_ctx *ctx, tree decl,
7138 tree decl2)
7140 splay_tree_node n;
7141 struct gimplify_omp_ctx *octx;
7143 for (octx = ctx; octx; octx = octx->outer_context)
7144 if ((octx->region_type & ORT_TARGET) != 0
7145 || octx->order_concurrent)
7147 n = splay_tree_lookup (octx->variables, (splay_tree_key)decl);
7148 if (n == NULL)
7150 if (octx->order_concurrent)
7152 error ("threadprivate variable %qE used in a region with"
7153 " %<order(concurrent)%> clause", DECL_NAME (decl));
7154 inform (octx->location, "enclosing region");
7156 else
7158 error ("threadprivate variable %qE used in target region",
7159 DECL_NAME (decl));
7160 inform (octx->location, "enclosing target region");
7162 splay_tree_insert (octx->variables, (splay_tree_key)decl, 0);
7164 if (decl2)
7165 splay_tree_insert (octx->variables, (splay_tree_key)decl2, 0);
7168 if (ctx->region_type != ORT_UNTIED_TASK)
7169 return false;
7170 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7171 if (n == NULL)
7173 error ("threadprivate variable %qE used in untied task",
7174 DECL_NAME (decl));
7175 inform (ctx->location, "enclosing task");
7176 splay_tree_insert (ctx->variables, (splay_tree_key)decl, 0);
7178 if (decl2)
7179 splay_tree_insert (ctx->variables, (splay_tree_key)decl2, 0);
7180 return false;
7183 /* Return true if global var DECL is device resident. */
7185 static bool
7186 device_resident_p (tree decl)
7188 tree attr = lookup_attribute ("oacc declare target", DECL_ATTRIBUTES (decl));
7190 if (!attr)
7191 return false;
7193 for (tree t = TREE_VALUE (attr); t; t = TREE_PURPOSE (t))
7195 tree c = TREE_VALUE (t);
7196 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_DEVICE_RESIDENT)
7197 return true;
7200 return false;
7203 /* Return true if DECL has an ACC DECLARE attribute. */
7205 static bool
7206 is_oacc_declared (tree decl)
7208 tree t = TREE_CODE (decl) == MEM_REF ? TREE_OPERAND (decl, 0) : decl;
7209 tree declared = lookup_attribute ("oacc declare target", DECL_ATTRIBUTES (t));
7210 return declared != NULL_TREE;
7213 /* Determine outer default flags for DECL mentioned in an OMP region
7214 but not declared in an enclosing clause.
7216 ??? Some compiler-generated variables (like SAVE_EXPRs) could be
7217 remapped firstprivate instead of shared. To some extent this is
7218 addressed in omp_firstprivatize_type_sizes, but not
7219 effectively. */
7221 static unsigned
7222 omp_default_clause (struct gimplify_omp_ctx *ctx, tree decl,
7223 bool in_code, unsigned flags)
7225 enum omp_clause_default_kind default_kind = ctx->default_kind;
7226 enum omp_clause_default_kind kind;
7228 kind = lang_hooks.decls.omp_predetermined_sharing (decl);
7229 if (ctx->region_type & ORT_TASK)
7231 tree detach_clause = omp_find_clause (ctx->clauses, OMP_CLAUSE_DETACH);
7233 /* The event-handle specified by a detach clause should always be firstprivate,
7234 regardless of the current default. */
7235 if (detach_clause && OMP_CLAUSE_DECL (detach_clause) == decl)
7236 kind = OMP_CLAUSE_DEFAULT_FIRSTPRIVATE;
7238 if (kind != OMP_CLAUSE_DEFAULT_UNSPECIFIED)
7239 default_kind = kind;
7240 else if (VAR_P (decl) && TREE_STATIC (decl) && DECL_IN_CONSTANT_POOL (decl))
7241 default_kind = OMP_CLAUSE_DEFAULT_SHARED;
7243 switch (default_kind)
7245 case OMP_CLAUSE_DEFAULT_NONE:
7247 const char *rtype;
7249 if (ctx->region_type & ORT_PARALLEL)
7250 rtype = "parallel";
7251 else if ((ctx->region_type & ORT_TASKLOOP) == ORT_TASKLOOP)
7252 rtype = "taskloop";
7253 else if (ctx->region_type & ORT_TASK)
7254 rtype = "task";
7255 else if (ctx->region_type & ORT_TEAMS)
7256 rtype = "teams";
7257 else
7258 gcc_unreachable ();
7260 error ("%qE not specified in enclosing %qs",
7261 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)), rtype);
7262 inform (ctx->location, "enclosing %qs", rtype);
7264 /* FALLTHRU */
7265 case OMP_CLAUSE_DEFAULT_SHARED:
7266 flags |= GOVD_SHARED;
7267 break;
7268 case OMP_CLAUSE_DEFAULT_PRIVATE:
7269 flags |= GOVD_PRIVATE;
7270 break;
7271 case OMP_CLAUSE_DEFAULT_FIRSTPRIVATE:
7272 flags |= GOVD_FIRSTPRIVATE;
7273 break;
7274 case OMP_CLAUSE_DEFAULT_UNSPECIFIED:
7275 /* decl will be either GOVD_FIRSTPRIVATE or GOVD_SHARED. */
7276 gcc_assert ((ctx->region_type & ORT_TASK) != 0);
7277 if (struct gimplify_omp_ctx *octx = ctx->outer_context)
7279 omp_notice_variable (octx, decl, in_code);
7280 for (; octx; octx = octx->outer_context)
7282 splay_tree_node n2;
7284 n2 = splay_tree_lookup (octx->variables, (splay_tree_key) decl);
7285 if ((octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)) != 0
7286 && (n2 == NULL || (n2->value & GOVD_DATA_SHARE_CLASS) == 0))
7287 continue;
7288 if (n2 && (n2->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED)
7290 flags |= GOVD_FIRSTPRIVATE;
7291 goto found_outer;
7293 if ((octx->region_type & (ORT_PARALLEL | ORT_TEAMS)) != 0)
7295 flags |= GOVD_SHARED;
7296 goto found_outer;
7301 if (TREE_CODE (decl) == PARM_DECL
7302 || (!is_global_var (decl)
7303 && DECL_CONTEXT (decl) == current_function_decl))
7304 flags |= GOVD_FIRSTPRIVATE;
7305 else
7306 flags |= GOVD_SHARED;
7307 found_outer:
7308 break;
7310 default:
7311 gcc_unreachable ();
7314 return flags;
7318 /* Determine outer default flags for DECL mentioned in an OACC region
7319 but not declared in an enclosing clause. */
7321 static unsigned
7322 oacc_default_clause (struct gimplify_omp_ctx *ctx, tree decl, unsigned flags)
7324 const char *rkind;
7325 bool on_device = false;
7326 bool is_private = false;
7327 bool declared = is_oacc_declared (decl);
7328 tree type = TREE_TYPE (decl);
7330 if (lang_hooks.decls.omp_privatize_by_reference (decl))
7331 type = TREE_TYPE (type);
7333 /* For Fortran COMMON blocks, only used variables in those blocks are
7334 transfered and remapped. The block itself will have a private clause to
7335 avoid transfering the data twice.
7336 The hook evaluates to false by default. For a variable in Fortran's COMMON
7337 or EQUIVALENCE block, returns 'true' (as we have shared=false) - as only
7338 the variables in such a COMMON/EQUIVALENCE block shall be privatized not
7339 the whole block. For C++ and Fortran, it can also be true under certain
7340 other conditions, if DECL_HAS_VALUE_EXPR. */
7341 if (RECORD_OR_UNION_TYPE_P (type))
7342 is_private = lang_hooks.decls.omp_disregard_value_expr (decl, false);
7344 if ((ctx->region_type & (ORT_ACC_PARALLEL | ORT_ACC_KERNELS)) != 0
7345 && is_global_var (decl)
7346 && device_resident_p (decl)
7347 && !is_private)
7349 on_device = true;
7350 flags |= GOVD_MAP_TO_ONLY;
7353 switch (ctx->region_type)
7355 case ORT_ACC_KERNELS:
7356 rkind = "kernels";
7358 if (is_private)
7359 flags |= GOVD_FIRSTPRIVATE;
7360 else if (AGGREGATE_TYPE_P (type))
7362 /* Aggregates default to 'present_or_copy', or 'present'. */
7363 if (ctx->default_kind != OMP_CLAUSE_DEFAULT_PRESENT)
7364 flags |= GOVD_MAP;
7365 else
7366 flags |= GOVD_MAP | GOVD_MAP_FORCE_PRESENT;
7368 else
7369 /* Scalars default to 'copy'. */
7370 flags |= GOVD_MAP | GOVD_MAP_FORCE;
7372 break;
7374 case ORT_ACC_PARALLEL:
7375 case ORT_ACC_SERIAL:
7376 rkind = ctx->region_type == ORT_ACC_PARALLEL ? "parallel" : "serial";
7378 if (is_private)
7379 flags |= GOVD_FIRSTPRIVATE;
7380 else if (on_device || declared)
7381 flags |= GOVD_MAP;
7382 else if (AGGREGATE_TYPE_P (type))
7384 /* Aggregates default to 'present_or_copy', or 'present'. */
7385 if (ctx->default_kind != OMP_CLAUSE_DEFAULT_PRESENT)
7386 flags |= GOVD_MAP;
7387 else
7388 flags |= GOVD_MAP | GOVD_MAP_FORCE_PRESENT;
7390 else
7391 /* Scalars default to 'firstprivate'. */
7392 flags |= GOVD_FIRSTPRIVATE;
7394 break;
7396 default:
7397 gcc_unreachable ();
7400 if (DECL_ARTIFICIAL (decl))
7401 ; /* We can get compiler-generated decls, and should not complain
7402 about them. */
7403 else if (ctx->default_kind == OMP_CLAUSE_DEFAULT_NONE)
7405 error ("%qE not specified in enclosing OpenACC %qs construct",
7406 DECL_NAME (lang_hooks.decls.omp_report_decl (decl)), rkind);
7407 inform (ctx->location, "enclosing OpenACC %qs construct", rkind);
7409 else if (ctx->default_kind == OMP_CLAUSE_DEFAULT_PRESENT)
7410 ; /* Handled above. */
7411 else
7412 gcc_checking_assert (ctx->default_kind == OMP_CLAUSE_DEFAULT_SHARED);
7414 return flags;
7417 /* Record the fact that DECL was used within the OMP context CTX.
7418 IN_CODE is true when real code uses DECL, and false when we should
7419 merely emit default(none) errors. Return true if DECL is going to
7420 be remapped and thus DECL shouldn't be gimplified into its
7421 DECL_VALUE_EXPR (if any). */
7423 static bool
7424 omp_notice_variable (struct gimplify_omp_ctx *ctx, tree decl, bool in_code)
7426 splay_tree_node n;
7427 unsigned flags = in_code ? GOVD_SEEN : 0;
7428 bool ret = false, shared;
7430 if (error_operand_p (decl))
7431 return false;
7433 if (ctx->region_type == ORT_NONE)
7434 return lang_hooks.decls.omp_disregard_value_expr (decl, false);
7436 if (is_global_var (decl))
7438 /* Threadprivate variables are predetermined. */
7439 if (DECL_THREAD_LOCAL_P (decl))
7440 return omp_notice_threadprivate_variable (ctx, decl, NULL_TREE);
7442 if (DECL_HAS_VALUE_EXPR_P (decl))
7444 if (ctx->region_type & ORT_ACC)
7445 /* For OpenACC, defer expansion of value to avoid transfering
7446 privatized common block data instead of im-/explicitly transfered
7447 variables which are in common blocks. */
7449 else
7451 tree value = get_base_address (DECL_VALUE_EXPR (decl));
7453 if (value && DECL_P (value) && DECL_THREAD_LOCAL_P (value))
7454 return omp_notice_threadprivate_variable (ctx, decl, value);
7458 if (gimplify_omp_ctxp->outer_context == NULL
7459 && VAR_P (decl)
7460 && oacc_get_fn_attrib (current_function_decl))
7462 location_t loc = DECL_SOURCE_LOCATION (decl);
7464 if (lookup_attribute ("omp declare target link",
7465 DECL_ATTRIBUTES (decl)))
7467 error_at (loc,
7468 "%qE with %<link%> clause used in %<routine%> function",
7469 DECL_NAME (decl));
7470 return false;
7472 else if (!lookup_attribute ("omp declare target",
7473 DECL_ATTRIBUTES (decl)))
7475 error_at (loc,
7476 "%qE requires a %<declare%> directive for use "
7477 "in a %<routine%> function", DECL_NAME (decl));
7478 return false;
7483 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7484 if ((ctx->region_type & ORT_TARGET) != 0)
7486 if (ctx->region_type & ORT_ACC)
7487 /* For OpenACC, as remarked above, defer expansion. */
7488 shared = false;
7489 else
7490 shared = true;
7492 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
7493 if (n == NULL)
7495 unsigned nflags = flags;
7496 if ((ctx->region_type & ORT_ACC) == 0)
7498 bool is_declare_target = false;
7499 if (is_global_var (decl)
7500 && varpool_node::get_create (decl)->offloadable)
7502 struct gimplify_omp_ctx *octx;
7503 for (octx = ctx->outer_context;
7504 octx; octx = octx->outer_context)
7506 n = splay_tree_lookup (octx->variables,
7507 (splay_tree_key)decl);
7508 if (n
7509 && (n->value & GOVD_DATA_SHARE_CLASS) != GOVD_SHARED
7510 && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
7511 break;
7513 is_declare_target = octx == NULL;
7515 if (!is_declare_target)
7517 int gdmk;
7518 enum omp_clause_defaultmap_kind kind;
7519 if (TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE
7520 || (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
7521 && (TREE_CODE (TREE_TYPE (TREE_TYPE (decl)))
7522 == POINTER_TYPE)))
7523 gdmk = GDMK_POINTER;
7524 else if (lang_hooks.decls.omp_scalar_p (decl))
7525 gdmk = GDMK_SCALAR;
7526 else
7527 gdmk = GDMK_AGGREGATE;
7528 kind = lang_hooks.decls.omp_predetermined_mapping (decl);
7529 if (kind != OMP_CLAUSE_DEFAULTMAP_CATEGORY_UNSPECIFIED)
7531 if (kind == OMP_CLAUSE_DEFAULTMAP_FIRSTPRIVATE)
7532 nflags |= GOVD_FIRSTPRIVATE;
7533 else if (kind == OMP_CLAUSE_DEFAULTMAP_TO)
7534 nflags |= GOVD_MAP | GOVD_MAP_TO_ONLY;
7535 else
7536 gcc_unreachable ();
7538 else if (ctx->defaultmap[gdmk] == 0)
7540 tree d = lang_hooks.decls.omp_report_decl (decl);
7541 error ("%qE not specified in enclosing %<target%>",
7542 DECL_NAME (d));
7543 inform (ctx->location, "enclosing %<target%>");
7545 else if (ctx->defaultmap[gdmk]
7546 & (GOVD_MAP_0LEN_ARRAY | GOVD_FIRSTPRIVATE))
7547 nflags |= ctx->defaultmap[gdmk];
7548 else
7550 gcc_assert (ctx->defaultmap[gdmk] & GOVD_MAP);
7551 nflags |= ctx->defaultmap[gdmk] & ~GOVD_MAP;
7556 struct gimplify_omp_ctx *octx = ctx->outer_context;
7557 if ((ctx->region_type & ORT_ACC) && octx)
7559 /* Look in outer OpenACC contexts, to see if there's a
7560 data attribute for this variable. */
7561 omp_notice_variable (octx, decl, in_code);
7563 for (; octx; octx = octx->outer_context)
7565 if (!(octx->region_type & (ORT_TARGET_DATA | ORT_TARGET)))
7566 break;
7567 splay_tree_node n2
7568 = splay_tree_lookup (octx->variables,
7569 (splay_tree_key) decl);
7570 if (n2)
7572 if (octx->region_type == ORT_ACC_HOST_DATA)
7573 error ("variable %qE declared in enclosing "
7574 "%<host_data%> region", DECL_NAME (decl));
7575 nflags |= GOVD_MAP;
7576 if (octx->region_type == ORT_ACC_DATA
7577 && (n2->value & GOVD_MAP_0LEN_ARRAY))
7578 nflags |= GOVD_MAP_0LEN_ARRAY;
7579 goto found_outer;
7584 if ((nflags & ~(GOVD_MAP_TO_ONLY | GOVD_MAP_FROM_ONLY
7585 | GOVD_MAP_ALLOC_ONLY)) == flags)
7587 tree type = TREE_TYPE (decl);
7589 if (gimplify_omp_ctxp->target_firstprivatize_array_bases
7590 && lang_hooks.decls.omp_privatize_by_reference (decl))
7591 type = TREE_TYPE (type);
7592 if (!lang_hooks.types.omp_mappable_type (type))
7594 error ("%qD referenced in target region does not have "
7595 "a mappable type", decl);
7596 nflags |= GOVD_MAP | GOVD_EXPLICIT;
7598 else
7600 if ((ctx->region_type & ORT_ACC) != 0)
7601 nflags = oacc_default_clause (ctx, decl, flags);
7602 else
7603 nflags |= GOVD_MAP;
7606 found_outer:
7607 omp_add_variable (ctx, decl, nflags);
7609 else
7611 /* If nothing changed, there's nothing left to do. */
7612 if ((n->value & flags) == flags)
7613 return ret;
7614 flags |= n->value;
7615 n->value = flags;
7617 goto do_outer;
7620 if (n == NULL)
7622 if (ctx->region_type == ORT_WORKSHARE
7623 || ctx->region_type == ORT_TASKGROUP
7624 || ctx->region_type == ORT_SIMD
7625 || ctx->region_type == ORT_ACC
7626 || (ctx->region_type & ORT_TARGET_DATA) != 0)
7627 goto do_outer;
7629 flags = omp_default_clause (ctx, decl, in_code, flags);
7631 if ((flags & GOVD_PRIVATE)
7632 && lang_hooks.decls.omp_private_outer_ref (decl))
7633 flags |= GOVD_PRIVATE_OUTER_REF;
7635 omp_add_variable (ctx, decl, flags);
7637 shared = (flags & GOVD_SHARED) != 0;
7638 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
7639 goto do_outer;
7642 /* Don't mark as GOVD_SEEN addressable temporaries seen only in simd
7643 lb, b or incr expressions, those shouldn't be turned into simd arrays. */
7644 if (ctx->region_type == ORT_SIMD
7645 && ctx->in_for_exprs
7646 && ((n->value & (GOVD_PRIVATE | GOVD_SEEN | GOVD_EXPLICIT))
7647 == GOVD_PRIVATE))
7648 flags &= ~GOVD_SEEN;
7650 if ((n->value & (GOVD_SEEN | GOVD_LOCAL)) == 0
7651 && (flags & (GOVD_SEEN | GOVD_LOCAL)) == GOVD_SEEN
7652 && DECL_SIZE (decl))
7654 if (TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
7656 splay_tree_node n2;
7657 tree t = DECL_VALUE_EXPR (decl);
7658 gcc_assert (TREE_CODE (t) == INDIRECT_REF);
7659 t = TREE_OPERAND (t, 0);
7660 gcc_assert (DECL_P (t));
7661 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
7662 n2->value |= GOVD_SEEN;
7664 else if (lang_hooks.decls.omp_privatize_by_reference (decl)
7665 && TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)))
7666 && (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl))))
7667 != INTEGER_CST))
7669 splay_tree_node n2;
7670 tree t = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl)));
7671 gcc_assert (DECL_P (t));
7672 n2 = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
7673 if (n2)
7674 omp_notice_variable (ctx, t, true);
7678 if (ctx->region_type & ORT_ACC)
7679 /* For OpenACC, as remarked above, defer expansion. */
7680 shared = false;
7681 else
7682 shared = ((flags | n->value) & GOVD_SHARED) != 0;
7683 ret = lang_hooks.decls.omp_disregard_value_expr (decl, shared);
7685 /* If nothing changed, there's nothing left to do. */
7686 if ((n->value & flags) == flags)
7687 return ret;
7688 flags |= n->value;
7689 n->value = flags;
7691 do_outer:
7692 /* If the variable is private in the current context, then we don't
7693 need to propagate anything to an outer context. */
7694 if ((flags & GOVD_PRIVATE) && !(flags & GOVD_PRIVATE_OUTER_REF))
7695 return ret;
7696 if ((flags & (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7697 == (GOVD_LINEAR | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7698 return ret;
7699 if ((flags & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
7700 | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7701 == (GOVD_LASTPRIVATE | GOVD_LINEAR_LASTPRIVATE_NO_OUTER))
7702 return ret;
7703 if (ctx->outer_context
7704 && omp_notice_variable (ctx->outer_context, decl, in_code))
7705 return true;
7706 return ret;
7709 /* Verify that DECL is private within CTX. If there's specific information
7710 to the contrary in the innermost scope, generate an error. */
7712 static bool
7713 omp_is_private (struct gimplify_omp_ctx *ctx, tree decl, int simd)
7715 splay_tree_node n;
7717 n = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
7718 if (n != NULL)
7720 if (n->value & GOVD_SHARED)
7722 if (ctx == gimplify_omp_ctxp)
7724 if (simd)
7725 error ("iteration variable %qE is predetermined linear",
7726 DECL_NAME (decl));
7727 else
7728 error ("iteration variable %qE should be private",
7729 DECL_NAME (decl));
7730 n->value = GOVD_PRIVATE;
7731 return true;
7733 else
7734 return false;
7736 else if ((n->value & GOVD_EXPLICIT) != 0
7737 && (ctx == gimplify_omp_ctxp
7738 || (ctx->region_type == ORT_COMBINED_PARALLEL
7739 && gimplify_omp_ctxp->outer_context == ctx)))
7741 if ((n->value & GOVD_FIRSTPRIVATE) != 0)
7742 error ("iteration variable %qE should not be firstprivate",
7743 DECL_NAME (decl));
7744 else if ((n->value & GOVD_REDUCTION) != 0)
7745 error ("iteration variable %qE should not be reduction",
7746 DECL_NAME (decl));
7747 else if (simd != 1 && (n->value & GOVD_LINEAR) != 0)
7748 error ("iteration variable %qE should not be linear",
7749 DECL_NAME (decl));
7751 return (ctx == gimplify_omp_ctxp
7752 || (ctx->region_type == ORT_COMBINED_PARALLEL
7753 && gimplify_omp_ctxp->outer_context == ctx));
7756 if (ctx->region_type != ORT_WORKSHARE
7757 && ctx->region_type != ORT_TASKGROUP
7758 && ctx->region_type != ORT_SIMD
7759 && ctx->region_type != ORT_ACC)
7760 return false;
7761 else if (ctx->outer_context)
7762 return omp_is_private (ctx->outer_context, decl, simd);
7763 return false;
7766 /* Return true if DECL is private within a parallel region
7767 that binds to the current construct's context or in parallel
7768 region's REDUCTION clause. */
7770 static bool
7771 omp_check_private (struct gimplify_omp_ctx *ctx, tree decl, bool copyprivate)
7773 splay_tree_node n;
7777 ctx = ctx->outer_context;
7778 if (ctx == NULL)
7780 if (is_global_var (decl))
7781 return false;
7783 /* References might be private, but might be shared too,
7784 when checking for copyprivate, assume they might be
7785 private, otherwise assume they might be shared. */
7786 if (copyprivate)
7787 return true;
7789 if (lang_hooks.decls.omp_privatize_by_reference (decl))
7790 return false;
7792 /* Treat C++ privatized non-static data members outside
7793 of the privatization the same. */
7794 if (omp_member_access_dummy_var (decl))
7795 return false;
7797 return true;
7800 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
7802 if ((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0
7803 && (n == NULL || (n->value & GOVD_DATA_SHARE_CLASS) == 0))
7804 continue;
7806 if (n != NULL)
7808 if ((n->value & GOVD_LOCAL) != 0
7809 && omp_member_access_dummy_var (decl))
7810 return false;
7811 return (n->value & GOVD_SHARED) == 0;
7814 while (ctx->region_type == ORT_WORKSHARE
7815 || ctx->region_type == ORT_TASKGROUP
7816 || ctx->region_type == ORT_SIMD
7817 || ctx->region_type == ORT_ACC);
7818 return false;
7821 /* Callback for walk_tree to find a DECL_EXPR for the given DECL. */
7823 static tree
7824 find_decl_expr (tree *tp, int *walk_subtrees, void *data)
7826 tree t = *tp;
7828 /* If this node has been visited, unmark it and keep looking. */
7829 if (TREE_CODE (t) == DECL_EXPR && DECL_EXPR_DECL (t) == (tree) data)
7830 return t;
7832 if (IS_TYPE_OR_DECL_P (t))
7833 *walk_subtrees = 0;
7834 return NULL_TREE;
7837 /* If *LIST_P contains any OpenMP depend clauses with iterators,
7838 lower all the depend clauses by populating corresponding depend
7839 array. Returns 0 if there are no such depend clauses, or
7840 2 if all depend clauses should be removed, 1 otherwise. */
7842 static int
7843 gimplify_omp_depend (tree *list_p, gimple_seq *pre_p)
7845 tree c;
7846 gimple *g;
7847 size_t n[4] = { 0, 0, 0, 0 };
7848 bool unused[4];
7849 tree counts[4] = { NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE };
7850 tree last_iter = NULL_TREE, last_count = NULL_TREE;
7851 size_t i, j;
7852 location_t first_loc = UNKNOWN_LOCATION;
7854 for (c = *list_p; c; c = OMP_CLAUSE_CHAIN (c))
7855 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND)
7857 switch (OMP_CLAUSE_DEPEND_KIND (c))
7859 case OMP_CLAUSE_DEPEND_IN:
7860 i = 2;
7861 break;
7862 case OMP_CLAUSE_DEPEND_OUT:
7863 case OMP_CLAUSE_DEPEND_INOUT:
7864 i = 0;
7865 break;
7866 case OMP_CLAUSE_DEPEND_MUTEXINOUTSET:
7867 i = 1;
7868 break;
7869 case OMP_CLAUSE_DEPEND_DEPOBJ:
7870 i = 3;
7871 break;
7872 case OMP_CLAUSE_DEPEND_SOURCE:
7873 case OMP_CLAUSE_DEPEND_SINK:
7874 continue;
7875 default:
7876 gcc_unreachable ();
7878 tree t = OMP_CLAUSE_DECL (c);
7879 if (first_loc == UNKNOWN_LOCATION)
7880 first_loc = OMP_CLAUSE_LOCATION (c);
7881 if (TREE_CODE (t) == TREE_LIST
7882 && TREE_PURPOSE (t)
7883 && TREE_CODE (TREE_PURPOSE (t)) == TREE_VEC)
7885 if (TREE_PURPOSE (t) != last_iter)
7887 tree tcnt = size_one_node;
7888 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
7890 if (gimplify_expr (&TREE_VEC_ELT (it, 1), pre_p, NULL,
7891 is_gimple_val, fb_rvalue) == GS_ERROR
7892 || gimplify_expr (&TREE_VEC_ELT (it, 2), pre_p, NULL,
7893 is_gimple_val, fb_rvalue) == GS_ERROR
7894 || gimplify_expr (&TREE_VEC_ELT (it, 3), pre_p, NULL,
7895 is_gimple_val, fb_rvalue) == GS_ERROR
7896 || (gimplify_expr (&TREE_VEC_ELT (it, 4), pre_p, NULL,
7897 is_gimple_val, fb_rvalue)
7898 == GS_ERROR))
7899 return 2;
7900 tree var = TREE_VEC_ELT (it, 0);
7901 tree begin = TREE_VEC_ELT (it, 1);
7902 tree end = TREE_VEC_ELT (it, 2);
7903 tree step = TREE_VEC_ELT (it, 3);
7904 tree orig_step = TREE_VEC_ELT (it, 4);
7905 tree type = TREE_TYPE (var);
7906 tree stype = TREE_TYPE (step);
7907 location_t loc = DECL_SOURCE_LOCATION (var);
7908 tree endmbegin;
7909 /* Compute count for this iterator as
7910 orig_step > 0
7911 ? (begin < end ? (end - begin + (step - 1)) / step : 0)
7912 : (begin > end ? (end - begin + (step + 1)) / step : 0)
7913 and compute product of those for the entire depend
7914 clause. */
7915 if (POINTER_TYPE_P (type))
7916 endmbegin = fold_build2_loc (loc, POINTER_DIFF_EXPR,
7917 stype, end, begin);
7918 else
7919 endmbegin = fold_build2_loc (loc, MINUS_EXPR, type,
7920 end, begin);
7921 tree stepm1 = fold_build2_loc (loc, MINUS_EXPR, stype,
7922 step,
7923 build_int_cst (stype, 1));
7924 tree stepp1 = fold_build2_loc (loc, PLUS_EXPR, stype, step,
7925 build_int_cst (stype, 1));
7926 tree pos = fold_build2_loc (loc, PLUS_EXPR, stype,
7927 unshare_expr (endmbegin),
7928 stepm1);
7929 pos = fold_build2_loc (loc, TRUNC_DIV_EXPR, stype,
7930 pos, step);
7931 tree neg = fold_build2_loc (loc, PLUS_EXPR, stype,
7932 endmbegin, stepp1);
7933 if (TYPE_UNSIGNED (stype))
7935 neg = fold_build1_loc (loc, NEGATE_EXPR, stype, neg);
7936 step = fold_build1_loc (loc, NEGATE_EXPR, stype, step);
7938 neg = fold_build2_loc (loc, TRUNC_DIV_EXPR, stype,
7939 neg, step);
7940 step = NULL_TREE;
7941 tree cond = fold_build2_loc (loc, LT_EXPR,
7942 boolean_type_node,
7943 begin, end);
7944 pos = fold_build3_loc (loc, COND_EXPR, stype, cond, pos,
7945 build_int_cst (stype, 0));
7946 cond = fold_build2_loc (loc, LT_EXPR, boolean_type_node,
7947 end, begin);
7948 neg = fold_build3_loc (loc, COND_EXPR, stype, cond, neg,
7949 build_int_cst (stype, 0));
7950 tree osteptype = TREE_TYPE (orig_step);
7951 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
7952 orig_step,
7953 build_int_cst (osteptype, 0));
7954 tree cnt = fold_build3_loc (loc, COND_EXPR, stype,
7955 cond, pos, neg);
7956 cnt = fold_convert_loc (loc, sizetype, cnt);
7957 if (gimplify_expr (&cnt, pre_p, NULL, is_gimple_val,
7958 fb_rvalue) == GS_ERROR)
7959 return 2;
7960 tcnt = size_binop_loc (loc, MULT_EXPR, tcnt, cnt);
7962 if (gimplify_expr (&tcnt, pre_p, NULL, is_gimple_val,
7963 fb_rvalue) == GS_ERROR)
7964 return 2;
7965 last_iter = TREE_PURPOSE (t);
7966 last_count = tcnt;
7968 if (counts[i] == NULL_TREE)
7969 counts[i] = last_count;
7970 else
7971 counts[i] = size_binop_loc (OMP_CLAUSE_LOCATION (c),
7972 PLUS_EXPR, counts[i], last_count);
7974 else
7975 n[i]++;
7977 for (i = 0; i < 4; i++)
7978 if (counts[i])
7979 break;
7980 if (i == 4)
7981 return 0;
7983 tree total = size_zero_node;
7984 for (i = 0; i < 4; i++)
7986 unused[i] = counts[i] == NULL_TREE && n[i] == 0;
7987 if (counts[i] == NULL_TREE)
7988 counts[i] = size_zero_node;
7989 if (n[i])
7990 counts[i] = size_binop (PLUS_EXPR, counts[i], size_int (n[i]));
7991 if (gimplify_expr (&counts[i], pre_p, NULL, is_gimple_val,
7992 fb_rvalue) == GS_ERROR)
7993 return 2;
7994 total = size_binop (PLUS_EXPR, total, counts[i]);
7997 if (gimplify_expr (&total, pre_p, NULL, is_gimple_val, fb_rvalue)
7998 == GS_ERROR)
7999 return 2;
8000 bool is_old = unused[1] && unused[3];
8001 tree totalpx = size_binop (PLUS_EXPR, unshare_expr (total),
8002 size_int (is_old ? 1 : 4));
8003 tree type = build_array_type (ptr_type_node, build_index_type (totalpx));
8004 tree array = create_tmp_var_raw (type);
8005 TREE_ADDRESSABLE (array) = 1;
8006 if (!poly_int_tree_p (totalpx))
8008 if (!TYPE_SIZES_GIMPLIFIED (TREE_TYPE (array)))
8009 gimplify_type_sizes (TREE_TYPE (array), pre_p);
8010 if (gimplify_omp_ctxp)
8012 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
8013 while (ctx
8014 && (ctx->region_type == ORT_WORKSHARE
8015 || ctx->region_type == ORT_TASKGROUP
8016 || ctx->region_type == ORT_SIMD
8017 || ctx->region_type == ORT_ACC))
8018 ctx = ctx->outer_context;
8019 if (ctx)
8020 omp_add_variable (ctx, array, GOVD_LOCAL | GOVD_SEEN);
8022 gimplify_vla_decl (array, pre_p);
8024 else
8025 gimple_add_tmp_var (array);
8026 tree r = build4 (ARRAY_REF, ptr_type_node, array, size_int (0), NULL_TREE,
8027 NULL_TREE);
8028 tree tem;
8029 if (!is_old)
8031 tem = build2 (MODIFY_EXPR, void_type_node, r,
8032 build_int_cst (ptr_type_node, 0));
8033 gimplify_and_add (tem, pre_p);
8034 r = build4 (ARRAY_REF, ptr_type_node, array, size_int (1), NULL_TREE,
8035 NULL_TREE);
8037 tem = build2 (MODIFY_EXPR, void_type_node, r,
8038 fold_convert (ptr_type_node, total));
8039 gimplify_and_add (tem, pre_p);
8040 for (i = 1; i < (is_old ? 2 : 4); i++)
8042 r = build4 (ARRAY_REF, ptr_type_node, array, size_int (i + !is_old),
8043 NULL_TREE, NULL_TREE);
8044 tem = build2 (MODIFY_EXPR, void_type_node, r, counts[i - 1]);
8045 gimplify_and_add (tem, pre_p);
8048 tree cnts[4];
8049 for (j = 4; j; j--)
8050 if (!unused[j - 1])
8051 break;
8052 for (i = 0; i < 4; i++)
8054 if (i && (i >= j || unused[i - 1]))
8056 cnts[i] = cnts[i - 1];
8057 continue;
8059 cnts[i] = create_tmp_var (sizetype);
8060 if (i == 0)
8061 g = gimple_build_assign (cnts[i], size_int (is_old ? 2 : 5));
8062 else
8064 tree t;
8065 if (is_old)
8066 t = size_binop (PLUS_EXPR, counts[0], size_int (2));
8067 else
8068 t = size_binop (PLUS_EXPR, cnts[i - 1], counts[i - 1]);
8069 if (gimplify_expr (&t, pre_p, NULL, is_gimple_val, fb_rvalue)
8070 == GS_ERROR)
8071 return 2;
8072 g = gimple_build_assign (cnts[i], t);
8074 gimple_seq_add_stmt (pre_p, g);
8077 last_iter = NULL_TREE;
8078 tree last_bind = NULL_TREE;
8079 tree *last_body = NULL;
8080 for (c = *list_p; c; c = OMP_CLAUSE_CHAIN (c))
8081 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND)
8083 switch (OMP_CLAUSE_DEPEND_KIND (c))
8085 case OMP_CLAUSE_DEPEND_IN:
8086 i = 2;
8087 break;
8088 case OMP_CLAUSE_DEPEND_OUT:
8089 case OMP_CLAUSE_DEPEND_INOUT:
8090 i = 0;
8091 break;
8092 case OMP_CLAUSE_DEPEND_MUTEXINOUTSET:
8093 i = 1;
8094 break;
8095 case OMP_CLAUSE_DEPEND_DEPOBJ:
8096 i = 3;
8097 break;
8098 case OMP_CLAUSE_DEPEND_SOURCE:
8099 case OMP_CLAUSE_DEPEND_SINK:
8100 continue;
8101 default:
8102 gcc_unreachable ();
8104 tree t = OMP_CLAUSE_DECL (c);
8105 if (TREE_CODE (t) == TREE_LIST
8106 && TREE_PURPOSE (t)
8107 && TREE_CODE (TREE_PURPOSE (t)) == TREE_VEC)
8109 if (TREE_PURPOSE (t) != last_iter)
8111 if (last_bind)
8112 gimplify_and_add (last_bind, pre_p);
8113 tree block = TREE_VEC_ELT (TREE_PURPOSE (t), 5);
8114 last_bind = build3 (BIND_EXPR, void_type_node,
8115 BLOCK_VARS (block), NULL, block);
8116 TREE_SIDE_EFFECTS (last_bind) = 1;
8117 SET_EXPR_LOCATION (last_bind, OMP_CLAUSE_LOCATION (c));
8118 tree *p = &BIND_EXPR_BODY (last_bind);
8119 for (tree it = TREE_PURPOSE (t); it; it = TREE_CHAIN (it))
8121 tree var = TREE_VEC_ELT (it, 0);
8122 tree begin = TREE_VEC_ELT (it, 1);
8123 tree end = TREE_VEC_ELT (it, 2);
8124 tree step = TREE_VEC_ELT (it, 3);
8125 tree orig_step = TREE_VEC_ELT (it, 4);
8126 tree type = TREE_TYPE (var);
8127 location_t loc = DECL_SOURCE_LOCATION (var);
8128 /* Emit:
8129 var = begin;
8130 goto cond_label;
8131 beg_label:
8133 var = var + step;
8134 cond_label:
8135 if (orig_step > 0) {
8136 if (var < end) goto beg_label;
8137 } else {
8138 if (var > end) goto beg_label;
8140 for each iterator, with inner iterators added to
8141 the ... above. */
8142 tree beg_label = create_artificial_label (loc);
8143 tree cond_label = NULL_TREE;
8144 tem = build2_loc (loc, MODIFY_EXPR, void_type_node,
8145 var, begin);
8146 append_to_statement_list_force (tem, p);
8147 tem = build_and_jump (&cond_label);
8148 append_to_statement_list_force (tem, p);
8149 tem = build1 (LABEL_EXPR, void_type_node, beg_label);
8150 append_to_statement_list (tem, p);
8151 tree bind = build3 (BIND_EXPR, void_type_node, NULL_TREE,
8152 NULL_TREE, NULL_TREE);
8153 TREE_SIDE_EFFECTS (bind) = 1;
8154 SET_EXPR_LOCATION (bind, loc);
8155 append_to_statement_list_force (bind, p);
8156 if (POINTER_TYPE_P (type))
8157 tem = build2_loc (loc, POINTER_PLUS_EXPR, type,
8158 var, fold_convert_loc (loc, sizetype,
8159 step));
8160 else
8161 tem = build2_loc (loc, PLUS_EXPR, type, var, step);
8162 tem = build2_loc (loc, MODIFY_EXPR, void_type_node,
8163 var, tem);
8164 append_to_statement_list_force (tem, p);
8165 tem = build1 (LABEL_EXPR, void_type_node, cond_label);
8166 append_to_statement_list (tem, p);
8167 tree cond = fold_build2_loc (loc, LT_EXPR,
8168 boolean_type_node,
8169 var, end);
8170 tree pos
8171 = fold_build3_loc (loc, COND_EXPR, void_type_node,
8172 cond, build_and_jump (&beg_label),
8173 void_node);
8174 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8175 var, end);
8176 tree neg
8177 = fold_build3_loc (loc, COND_EXPR, void_type_node,
8178 cond, build_and_jump (&beg_label),
8179 void_node);
8180 tree osteptype = TREE_TYPE (orig_step);
8181 cond = fold_build2_loc (loc, GT_EXPR, boolean_type_node,
8182 orig_step,
8183 build_int_cst (osteptype, 0));
8184 tem = fold_build3_loc (loc, COND_EXPR, void_type_node,
8185 cond, pos, neg);
8186 append_to_statement_list_force (tem, p);
8187 p = &BIND_EXPR_BODY (bind);
8189 last_body = p;
8191 last_iter = TREE_PURPOSE (t);
8192 if (TREE_CODE (TREE_VALUE (t)) == COMPOUND_EXPR)
8194 append_to_statement_list (TREE_OPERAND (TREE_VALUE (t),
8195 0), last_body);
8196 TREE_VALUE (t) = TREE_OPERAND (TREE_VALUE (t), 1);
8198 if (error_operand_p (TREE_VALUE (t)))
8199 return 2;
8200 TREE_VALUE (t) = build_fold_addr_expr (TREE_VALUE (t));
8201 r = build4 (ARRAY_REF, ptr_type_node, array, cnts[i],
8202 NULL_TREE, NULL_TREE);
8203 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
8204 void_type_node, r, TREE_VALUE (t));
8205 append_to_statement_list_force (tem, last_body);
8206 tem = build2_loc (OMP_CLAUSE_LOCATION (c), MODIFY_EXPR,
8207 void_type_node, cnts[i],
8208 size_binop (PLUS_EXPR, cnts[i], size_int (1)));
8209 append_to_statement_list_force (tem, last_body);
8210 TREE_VALUE (t) = null_pointer_node;
8212 else
8214 if (last_bind)
8216 gimplify_and_add (last_bind, pre_p);
8217 last_bind = NULL_TREE;
8219 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
8221 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
8222 NULL, is_gimple_val, fb_rvalue);
8223 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
8225 if (error_operand_p (OMP_CLAUSE_DECL (c)))
8226 return 2;
8227 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (OMP_CLAUSE_DECL (c));
8228 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
8229 is_gimple_val, fb_rvalue) == GS_ERROR)
8230 return 2;
8231 r = build4 (ARRAY_REF, ptr_type_node, array, cnts[i],
8232 NULL_TREE, NULL_TREE);
8233 tem = build2 (MODIFY_EXPR, void_type_node, r, OMP_CLAUSE_DECL (c));
8234 gimplify_and_add (tem, pre_p);
8235 g = gimple_build_assign (cnts[i], size_binop (PLUS_EXPR, cnts[i],
8236 size_int (1)));
8237 gimple_seq_add_stmt (pre_p, g);
8240 if (last_bind)
8241 gimplify_and_add (last_bind, pre_p);
8242 tree cond = boolean_false_node;
8243 if (is_old)
8245 if (!unused[0])
8246 cond = build2_loc (first_loc, NE_EXPR, boolean_type_node, cnts[0],
8247 size_binop_loc (first_loc, PLUS_EXPR, counts[0],
8248 size_int (2)));
8249 if (!unused[2])
8250 cond = build2_loc (first_loc, TRUTH_OR_EXPR, boolean_type_node, cond,
8251 build2_loc (first_loc, NE_EXPR, boolean_type_node,
8252 cnts[2],
8253 size_binop_loc (first_loc, PLUS_EXPR,
8254 totalpx,
8255 size_int (1))));
8257 else
8259 tree prev = size_int (5);
8260 for (i = 0; i < 4; i++)
8262 if (unused[i])
8263 continue;
8264 prev = size_binop_loc (first_loc, PLUS_EXPR, counts[i], prev);
8265 cond = build2_loc (first_loc, TRUTH_OR_EXPR, boolean_type_node, cond,
8266 build2_loc (first_loc, NE_EXPR, boolean_type_node,
8267 cnts[i], unshare_expr (prev)));
8270 tem = build3_loc (first_loc, COND_EXPR, void_type_node, cond,
8271 build_call_expr_loc (first_loc,
8272 builtin_decl_explicit (BUILT_IN_TRAP),
8273 0), void_node);
8274 gimplify_and_add (tem, pre_p);
8275 c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_DEPEND);
8276 OMP_CLAUSE_DEPEND_KIND (c) = OMP_CLAUSE_DEPEND_LAST;
8277 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (array);
8278 OMP_CLAUSE_CHAIN (c) = *list_p;
8279 *list_p = c;
8280 return 1;
8283 /* Insert a GOMP_MAP_ALLOC or GOMP_MAP_RELEASE node following a
8284 GOMP_MAP_STRUCT mapping. C is an always_pointer mapping. STRUCT_NODE is
8285 the struct node to insert the new mapping after (when the struct node is
8286 initially created). PREV_NODE is the first of two or three mappings for a
8287 pointer, and is either:
8288 - the node before C, when a pair of mappings is used, e.g. for a C/C++
8289 array section.
8290 - not the node before C. This is true when we have a reference-to-pointer
8291 type (with a mapping for the reference and for the pointer), or for
8292 Fortran derived-type mappings with a GOMP_MAP_TO_PSET.
8293 If SCP is non-null, the new node is inserted before *SCP.
8294 if SCP is null, the new node is inserted before PREV_NODE.
8295 The return type is:
8296 - PREV_NODE, if SCP is non-null.
8297 - The newly-created ALLOC or RELEASE node, if SCP is null.
8298 - The second newly-created ALLOC or RELEASE node, if we are mapping a
8299 reference to a pointer. */
8301 static tree
8302 insert_struct_comp_map (enum tree_code code, tree c, tree struct_node,
8303 tree prev_node, tree *scp)
8305 enum gomp_map_kind mkind
8306 = (code == OMP_TARGET_EXIT_DATA || code == OACC_EXIT_DATA)
8307 ? GOMP_MAP_RELEASE : GOMP_MAP_ALLOC;
8309 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c), OMP_CLAUSE_MAP);
8310 tree cl = scp ? prev_node : c2;
8311 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
8312 OMP_CLAUSE_DECL (c2) = unshare_expr (OMP_CLAUSE_DECL (c));
8313 OMP_CLAUSE_CHAIN (c2) = scp ? *scp : prev_node;
8314 if (OMP_CLAUSE_CHAIN (prev_node) != c
8315 && OMP_CLAUSE_CODE (OMP_CLAUSE_CHAIN (prev_node)) == OMP_CLAUSE_MAP
8316 && (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (prev_node))
8317 == GOMP_MAP_TO_PSET))
8318 OMP_CLAUSE_SIZE (c2) = OMP_CLAUSE_SIZE (OMP_CLAUSE_CHAIN (prev_node));
8319 else
8320 OMP_CLAUSE_SIZE (c2) = TYPE_SIZE_UNIT (ptr_type_node);
8321 if (struct_node)
8322 OMP_CLAUSE_CHAIN (struct_node) = c2;
8324 /* We might need to create an additional mapping if we have a reference to a
8325 pointer (in C++). Don't do this if we have something other than a
8326 GOMP_MAP_ALWAYS_POINTER though, i.e. a GOMP_MAP_TO_PSET. */
8327 if (OMP_CLAUSE_CHAIN (prev_node) != c
8328 && OMP_CLAUSE_CODE (OMP_CLAUSE_CHAIN (prev_node)) == OMP_CLAUSE_MAP
8329 && ((OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (prev_node))
8330 == GOMP_MAP_ALWAYS_POINTER)
8331 || (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (prev_node))
8332 == GOMP_MAP_ATTACH_DETACH)))
8334 tree c4 = OMP_CLAUSE_CHAIN (prev_node);
8335 tree c3 = build_omp_clause (OMP_CLAUSE_LOCATION (c), OMP_CLAUSE_MAP);
8336 OMP_CLAUSE_SET_MAP_KIND (c3, mkind);
8337 OMP_CLAUSE_DECL (c3) = unshare_expr (OMP_CLAUSE_DECL (c4));
8338 OMP_CLAUSE_SIZE (c3) = TYPE_SIZE_UNIT (ptr_type_node);
8339 OMP_CLAUSE_CHAIN (c3) = prev_node;
8340 if (!scp)
8341 OMP_CLAUSE_CHAIN (c2) = c3;
8342 else
8343 cl = c3;
8346 if (scp)
8347 *scp = c2;
8349 return cl;
8352 /* Strip ARRAY_REFS or an indirect ref off BASE, find the containing object,
8353 and set *BITPOSP and *POFFSETP to the bit offset of the access.
8354 If BASE_REF is non-NULL and the containing object is a reference, set
8355 *BASE_REF to that reference before dereferencing the object.
8356 If BASE_REF is NULL, check that the containing object is a COMPONENT_REF or
8357 has array type, else return NULL. */
8359 static tree
8360 extract_base_bit_offset (tree base, tree *base_ref, poly_int64 *bitposp,
8361 poly_offset_int *poffsetp)
8363 tree offset;
8364 poly_int64 bitsize, bitpos;
8365 machine_mode mode;
8366 int unsignedp, reversep, volatilep = 0;
8367 poly_offset_int poffset;
8369 if (base_ref)
8371 *base_ref = NULL_TREE;
8373 while (TREE_CODE (base) == ARRAY_REF)
8374 base = TREE_OPERAND (base, 0);
8376 if (TREE_CODE (base) == INDIRECT_REF)
8377 base = TREE_OPERAND (base, 0);
8379 else
8381 if (TREE_CODE (base) == ARRAY_REF)
8383 while (TREE_CODE (base) == ARRAY_REF)
8384 base = TREE_OPERAND (base, 0);
8385 if (TREE_CODE (base) != COMPONENT_REF
8386 || TREE_CODE (TREE_TYPE (base)) != ARRAY_TYPE)
8387 return NULL_TREE;
8389 else if (TREE_CODE (base) == INDIRECT_REF
8390 && TREE_CODE (TREE_OPERAND (base, 0)) == COMPONENT_REF
8391 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (base, 0)))
8392 == REFERENCE_TYPE))
8393 base = TREE_OPERAND (base, 0);
8396 base = get_inner_reference (base, &bitsize, &bitpos, &offset, &mode,
8397 &unsignedp, &reversep, &volatilep);
8399 tree orig_base = base;
8401 if ((TREE_CODE (base) == INDIRECT_REF
8402 || (TREE_CODE (base) == MEM_REF
8403 && integer_zerop (TREE_OPERAND (base, 1))))
8404 && DECL_P (TREE_OPERAND (base, 0))
8405 && TREE_CODE (TREE_TYPE (TREE_OPERAND (base, 0))) == REFERENCE_TYPE)
8406 base = TREE_OPERAND (base, 0);
8408 gcc_assert (offset == NULL_TREE || poly_int_tree_p (offset));
8410 if (offset)
8411 poffset = wi::to_poly_offset (offset);
8412 else
8413 poffset = 0;
8415 if (maybe_ne (bitpos, 0))
8416 poffset += bits_to_bytes_round_down (bitpos);
8418 *bitposp = bitpos;
8419 *poffsetp = poffset;
8421 /* Set *BASE_REF if BASE was a dereferenced reference variable. */
8422 if (base_ref && orig_base != base)
8423 *base_ref = orig_base;
8425 return base;
8428 /* Returns true if EXPR is or contains (as a sub-component) BASE_PTR. */
8430 static bool
8431 is_or_contains_p (tree expr, tree base_ptr)
8433 while (expr != base_ptr)
8434 if (TREE_CODE (base_ptr) == COMPONENT_REF)
8435 base_ptr = TREE_OPERAND (base_ptr, 0);
8436 else
8437 break;
8438 return expr == base_ptr;
8441 /* Implement OpenMP 5.x map ordering rules for target directives. There are
8442 several rules, and with some level of ambiguity, hopefully we can at least
8443 collect the complexity here in one place. */
8445 static void
8446 omp_target_reorder_clauses (tree *list_p)
8448 /* Collect refs to alloc/release/delete maps. */
8449 auto_vec<tree, 32> ard;
8450 tree *cp = list_p;
8451 while (*cp != NULL_TREE)
8452 if (OMP_CLAUSE_CODE (*cp) == OMP_CLAUSE_MAP
8453 && (OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_ALLOC
8454 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_RELEASE
8455 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_DELETE))
8457 /* Unlink cp and push to ard. */
8458 tree c = *cp;
8459 tree nc = OMP_CLAUSE_CHAIN (c);
8460 *cp = nc;
8461 ard.safe_push (c);
8463 /* Any associated pointer type maps should also move along. */
8464 while (*cp != NULL_TREE
8465 && OMP_CLAUSE_CODE (*cp) == OMP_CLAUSE_MAP
8466 && (OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_FIRSTPRIVATE_REFERENCE
8467 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_FIRSTPRIVATE_POINTER
8468 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_ATTACH_DETACH
8469 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_POINTER
8470 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_ALWAYS_POINTER
8471 || OMP_CLAUSE_MAP_KIND (*cp) == GOMP_MAP_TO_PSET))
8473 c = *cp;
8474 nc = OMP_CLAUSE_CHAIN (c);
8475 *cp = nc;
8476 ard.safe_push (c);
8479 else
8480 cp = &OMP_CLAUSE_CHAIN (*cp);
8482 /* Link alloc/release/delete maps to the end of list. */
8483 for (unsigned int i = 0; i < ard.length (); i++)
8485 *cp = ard[i];
8486 cp = &OMP_CLAUSE_CHAIN (ard[i]);
8488 *cp = NULL_TREE;
8490 /* OpenMP 5.0 requires that pointer variables are mapped before
8491 its use as a base-pointer. */
8492 auto_vec<tree *, 32> atf;
8493 for (tree *cp = list_p; *cp; cp = &OMP_CLAUSE_CHAIN (*cp))
8494 if (OMP_CLAUSE_CODE (*cp) == OMP_CLAUSE_MAP)
8496 /* Collect alloc, to, from, to/from clause tree pointers. */
8497 gomp_map_kind k = OMP_CLAUSE_MAP_KIND (*cp);
8498 if (k == GOMP_MAP_ALLOC
8499 || k == GOMP_MAP_TO
8500 || k == GOMP_MAP_FROM
8501 || k == GOMP_MAP_TOFROM
8502 || k == GOMP_MAP_ALWAYS_TO
8503 || k == GOMP_MAP_ALWAYS_FROM
8504 || k == GOMP_MAP_ALWAYS_TOFROM)
8505 atf.safe_push (cp);
8508 for (unsigned int i = 0; i < atf.length (); i++)
8509 if (atf[i])
8511 tree *cp = atf[i];
8512 tree decl = OMP_CLAUSE_DECL (*cp);
8513 if (TREE_CODE (decl) == INDIRECT_REF || TREE_CODE (decl) == MEM_REF)
8515 tree base_ptr = TREE_OPERAND (decl, 0);
8516 STRIP_TYPE_NOPS (base_ptr);
8517 for (unsigned int j = i + 1; j < atf.length (); j++)
8519 tree *cp2 = atf[j];
8520 tree decl2 = OMP_CLAUSE_DECL (*cp2);
8521 if (is_or_contains_p (decl2, base_ptr))
8523 /* Move *cp2 to before *cp. */
8524 tree c = *cp2;
8525 *cp2 = OMP_CLAUSE_CHAIN (c);
8526 OMP_CLAUSE_CHAIN (c) = *cp;
8527 *cp = c;
8528 atf[j] = NULL;
8535 /* Scan the OMP clauses in *LIST_P, installing mappings into a new
8536 and previous omp contexts. */
8538 static void
8539 gimplify_scan_omp_clauses (tree *list_p, gimple_seq *pre_p,
8540 enum omp_region_type region_type,
8541 enum tree_code code)
8543 struct gimplify_omp_ctx *ctx, *outer_ctx;
8544 tree c;
8545 hash_map<tree, tree> *struct_map_to_clause = NULL;
8546 hash_set<tree> *struct_deref_set = NULL;
8547 tree *prev_list_p = NULL, *orig_list_p = list_p;
8548 int handled_depend_iterators = -1;
8549 int nowait = -1;
8551 ctx = new_omp_context (region_type);
8552 ctx->code = code;
8553 outer_ctx = ctx->outer_context;
8554 if (code == OMP_TARGET)
8556 if (!lang_GNU_Fortran ())
8557 ctx->defaultmap[GDMK_POINTER] = GOVD_MAP | GOVD_MAP_0LEN_ARRAY;
8558 ctx->defaultmap[GDMK_SCALAR] = GOVD_FIRSTPRIVATE;
8560 if (!lang_GNU_Fortran ())
8561 switch (code)
8563 case OMP_TARGET:
8564 case OMP_TARGET_DATA:
8565 case OMP_TARGET_ENTER_DATA:
8566 case OMP_TARGET_EXIT_DATA:
8567 case OACC_DECLARE:
8568 case OACC_HOST_DATA:
8569 case OACC_PARALLEL:
8570 case OACC_KERNELS:
8571 ctx->target_firstprivatize_array_bases = true;
8572 default:
8573 break;
8576 if (code == OMP_TARGET
8577 || code == OMP_TARGET_DATA
8578 || code == OMP_TARGET_ENTER_DATA
8579 || code == OMP_TARGET_EXIT_DATA)
8580 omp_target_reorder_clauses (list_p);
8582 while ((c = *list_p) != NULL)
8584 bool remove = false;
8585 bool notice_outer = true;
8586 const char *check_non_private = NULL;
8587 unsigned int flags;
8588 tree decl;
8590 switch (OMP_CLAUSE_CODE (c))
8592 case OMP_CLAUSE_PRIVATE:
8593 flags = GOVD_PRIVATE | GOVD_EXPLICIT;
8594 if (lang_hooks.decls.omp_private_outer_ref (OMP_CLAUSE_DECL (c)))
8596 flags |= GOVD_PRIVATE_OUTER_REF;
8597 OMP_CLAUSE_PRIVATE_OUTER_REF (c) = 1;
8599 else
8600 notice_outer = false;
8601 goto do_add;
8602 case OMP_CLAUSE_SHARED:
8603 flags = GOVD_SHARED | GOVD_EXPLICIT;
8604 goto do_add;
8605 case OMP_CLAUSE_FIRSTPRIVATE:
8606 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
8607 check_non_private = "firstprivate";
8608 goto do_add;
8609 case OMP_CLAUSE_LASTPRIVATE:
8610 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
8611 switch (code)
8613 case OMP_DISTRIBUTE:
8614 error_at (OMP_CLAUSE_LOCATION (c),
8615 "conditional %<lastprivate%> clause on "
8616 "%qs construct", "distribute");
8617 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
8618 break;
8619 case OMP_TASKLOOP:
8620 error_at (OMP_CLAUSE_LOCATION (c),
8621 "conditional %<lastprivate%> clause on "
8622 "%qs construct", "taskloop");
8623 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
8624 break;
8625 default:
8626 break;
8628 flags = GOVD_LASTPRIVATE | GOVD_SEEN | GOVD_EXPLICIT;
8629 if (code != OMP_LOOP)
8630 check_non_private = "lastprivate";
8631 decl = OMP_CLAUSE_DECL (c);
8632 if (error_operand_p (decl))
8633 goto do_add;
8634 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c)
8635 && !lang_hooks.decls.omp_scalar_p (decl))
8637 error_at (OMP_CLAUSE_LOCATION (c),
8638 "non-scalar variable %qD in conditional "
8639 "%<lastprivate%> clause", decl);
8640 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) = 0;
8642 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
8643 flags |= GOVD_LASTPRIVATE_CONDITIONAL;
8644 if (outer_ctx
8645 && (outer_ctx->region_type == ORT_COMBINED_PARALLEL
8646 || ((outer_ctx->region_type & ORT_COMBINED_TEAMS)
8647 == ORT_COMBINED_TEAMS))
8648 && splay_tree_lookup (outer_ctx->variables,
8649 (splay_tree_key) decl) == NULL)
8651 omp_add_variable (outer_ctx, decl, GOVD_SHARED | GOVD_SEEN);
8652 if (outer_ctx->outer_context)
8653 omp_notice_variable (outer_ctx->outer_context, decl, true);
8655 else if (outer_ctx
8656 && (outer_ctx->region_type & ORT_TASK) != 0
8657 && outer_ctx->combined_loop
8658 && splay_tree_lookup (outer_ctx->variables,
8659 (splay_tree_key) decl) == NULL)
8661 omp_add_variable (outer_ctx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
8662 if (outer_ctx->outer_context)
8663 omp_notice_variable (outer_ctx->outer_context, decl, true);
8665 else if (outer_ctx
8666 && (outer_ctx->region_type == ORT_WORKSHARE
8667 || outer_ctx->region_type == ORT_ACC)
8668 && outer_ctx->combined_loop
8669 && splay_tree_lookup (outer_ctx->variables,
8670 (splay_tree_key) decl) == NULL
8671 && !omp_check_private (outer_ctx, decl, false))
8673 omp_add_variable (outer_ctx, decl, GOVD_LASTPRIVATE | GOVD_SEEN);
8674 if (outer_ctx->outer_context
8675 && (outer_ctx->outer_context->region_type
8676 == ORT_COMBINED_PARALLEL)
8677 && splay_tree_lookup (outer_ctx->outer_context->variables,
8678 (splay_tree_key) decl) == NULL)
8680 struct gimplify_omp_ctx *octx = outer_ctx->outer_context;
8681 omp_add_variable (octx, decl, GOVD_SHARED | GOVD_SEEN);
8682 if (octx->outer_context)
8684 octx = octx->outer_context;
8685 if (octx->region_type == ORT_WORKSHARE
8686 && octx->combined_loop
8687 && splay_tree_lookup (octx->variables,
8688 (splay_tree_key) decl) == NULL
8689 && !omp_check_private (octx, decl, false))
8691 omp_add_variable (octx, decl,
8692 GOVD_LASTPRIVATE | GOVD_SEEN);
8693 octx = octx->outer_context;
8694 if (octx
8695 && ((octx->region_type & ORT_COMBINED_TEAMS)
8696 == ORT_COMBINED_TEAMS)
8697 && (splay_tree_lookup (octx->variables,
8698 (splay_tree_key) decl)
8699 == NULL))
8701 omp_add_variable (octx, decl,
8702 GOVD_SHARED | GOVD_SEEN);
8703 octx = octx->outer_context;
8706 if (octx)
8707 omp_notice_variable (octx, decl, true);
8710 else if (outer_ctx->outer_context)
8711 omp_notice_variable (outer_ctx->outer_context, decl, true);
8713 goto do_add;
8714 case OMP_CLAUSE_REDUCTION:
8715 if (OMP_CLAUSE_REDUCTION_TASK (c))
8717 if (region_type == ORT_WORKSHARE)
8719 if (nowait == -1)
8720 nowait = omp_find_clause (*list_p,
8721 OMP_CLAUSE_NOWAIT) != NULL_TREE;
8722 if (nowait
8723 && (outer_ctx == NULL
8724 || outer_ctx->region_type != ORT_COMBINED_PARALLEL))
8726 error_at (OMP_CLAUSE_LOCATION (c),
8727 "%<task%> reduction modifier on a construct "
8728 "with a %<nowait%> clause");
8729 OMP_CLAUSE_REDUCTION_TASK (c) = 0;
8732 else if ((region_type & ORT_PARALLEL) != ORT_PARALLEL)
8734 error_at (OMP_CLAUSE_LOCATION (c),
8735 "invalid %<task%> reduction modifier on construct "
8736 "other than %<parallel%>, %qs or %<sections%>",
8737 lang_GNU_Fortran () ? "do" : "for");
8738 OMP_CLAUSE_REDUCTION_TASK (c) = 0;
8741 if (OMP_CLAUSE_REDUCTION_INSCAN (c))
8742 switch (code)
8744 case OMP_SECTIONS:
8745 error_at (OMP_CLAUSE_LOCATION (c),
8746 "%<inscan%> %<reduction%> clause on "
8747 "%qs construct", "sections");
8748 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
8749 break;
8750 case OMP_PARALLEL:
8751 error_at (OMP_CLAUSE_LOCATION (c),
8752 "%<inscan%> %<reduction%> clause on "
8753 "%qs construct", "parallel");
8754 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
8755 break;
8756 case OMP_TEAMS:
8757 error_at (OMP_CLAUSE_LOCATION (c),
8758 "%<inscan%> %<reduction%> clause on "
8759 "%qs construct", "teams");
8760 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
8761 break;
8762 case OMP_TASKLOOP:
8763 error_at (OMP_CLAUSE_LOCATION (c),
8764 "%<inscan%> %<reduction%> clause on "
8765 "%qs construct", "taskloop");
8766 OMP_CLAUSE_REDUCTION_INSCAN (c) = 0;
8767 break;
8768 default:
8769 break;
8771 /* FALLTHRU */
8772 case OMP_CLAUSE_IN_REDUCTION:
8773 case OMP_CLAUSE_TASK_REDUCTION:
8774 flags = GOVD_REDUCTION | GOVD_SEEN | GOVD_EXPLICIT;
8775 /* OpenACC permits reductions on private variables. */
8776 if (!(region_type & ORT_ACC)
8777 /* taskgroup is actually not a worksharing region. */
8778 && code != OMP_TASKGROUP)
8779 check_non_private = omp_clause_code_name[OMP_CLAUSE_CODE (c)];
8780 decl = OMP_CLAUSE_DECL (c);
8781 if (TREE_CODE (decl) == MEM_REF)
8783 tree type = TREE_TYPE (decl);
8784 bool saved_into_ssa = gimplify_ctxp->into_ssa;
8785 gimplify_ctxp->into_ssa = false;
8786 if (gimplify_expr (&TYPE_MAX_VALUE (TYPE_DOMAIN (type)), pre_p,
8787 NULL, is_gimple_val, fb_rvalue, false)
8788 == GS_ERROR)
8790 gimplify_ctxp->into_ssa = saved_into_ssa;
8791 remove = true;
8792 break;
8794 gimplify_ctxp->into_ssa = saved_into_ssa;
8795 tree v = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
8796 if (DECL_P (v))
8798 omp_firstprivatize_variable (ctx, v);
8799 omp_notice_variable (ctx, v, true);
8801 decl = TREE_OPERAND (decl, 0);
8802 if (TREE_CODE (decl) == POINTER_PLUS_EXPR)
8804 gimplify_ctxp->into_ssa = false;
8805 if (gimplify_expr (&TREE_OPERAND (decl, 1), pre_p,
8806 NULL, is_gimple_val, fb_rvalue, false)
8807 == GS_ERROR)
8809 gimplify_ctxp->into_ssa = saved_into_ssa;
8810 remove = true;
8811 break;
8813 gimplify_ctxp->into_ssa = saved_into_ssa;
8814 v = TREE_OPERAND (decl, 1);
8815 if (DECL_P (v))
8817 omp_firstprivatize_variable (ctx, v);
8818 omp_notice_variable (ctx, v, true);
8820 decl = TREE_OPERAND (decl, 0);
8822 if (TREE_CODE (decl) == ADDR_EXPR
8823 || TREE_CODE (decl) == INDIRECT_REF)
8824 decl = TREE_OPERAND (decl, 0);
8826 goto do_add_decl;
8827 case OMP_CLAUSE_LINEAR:
8828 if (gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c), pre_p, NULL,
8829 is_gimple_val, fb_rvalue) == GS_ERROR)
8831 remove = true;
8832 break;
8834 else
8836 if (code == OMP_SIMD
8837 && !OMP_CLAUSE_LINEAR_NO_COPYIN (c))
8839 struct gimplify_omp_ctx *octx = outer_ctx;
8840 if (octx
8841 && octx->region_type == ORT_WORKSHARE
8842 && octx->combined_loop
8843 && !octx->distribute)
8845 if (octx->outer_context
8846 && (octx->outer_context->region_type
8847 == ORT_COMBINED_PARALLEL))
8848 octx = octx->outer_context->outer_context;
8849 else
8850 octx = octx->outer_context;
8852 if (octx
8853 && octx->region_type == ORT_WORKSHARE
8854 && octx->combined_loop
8855 && octx->distribute)
8857 error_at (OMP_CLAUSE_LOCATION (c),
8858 "%<linear%> clause for variable other than "
8859 "loop iterator specified on construct "
8860 "combined with %<distribute%>");
8861 remove = true;
8862 break;
8865 /* For combined #pragma omp parallel for simd, need to put
8866 lastprivate and perhaps firstprivate too on the
8867 parallel. Similarly for #pragma omp for simd. */
8868 struct gimplify_omp_ctx *octx = outer_ctx;
8869 decl = NULL_TREE;
8872 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
8873 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
8874 break;
8875 decl = OMP_CLAUSE_DECL (c);
8876 if (error_operand_p (decl))
8878 decl = NULL_TREE;
8879 break;
8881 flags = GOVD_SEEN;
8882 if (!OMP_CLAUSE_LINEAR_NO_COPYIN (c))
8883 flags |= GOVD_FIRSTPRIVATE;
8884 if (!OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
8885 flags |= GOVD_LASTPRIVATE;
8886 if (octx
8887 && octx->region_type == ORT_WORKSHARE
8888 && octx->combined_loop)
8890 if (octx->outer_context
8891 && (octx->outer_context->region_type
8892 == ORT_COMBINED_PARALLEL))
8893 octx = octx->outer_context;
8894 else if (omp_check_private (octx, decl, false))
8895 break;
8897 else if (octx
8898 && (octx->region_type & ORT_TASK) != 0
8899 && octx->combined_loop)
8901 else if (octx
8902 && octx->region_type == ORT_COMBINED_PARALLEL
8903 && ctx->region_type == ORT_WORKSHARE
8904 && octx == outer_ctx)
8905 flags = GOVD_SEEN | GOVD_SHARED;
8906 else if (octx
8907 && ((octx->region_type & ORT_COMBINED_TEAMS)
8908 == ORT_COMBINED_TEAMS))
8909 flags = GOVD_SEEN | GOVD_SHARED;
8910 else if (octx
8911 && octx->region_type == ORT_COMBINED_TARGET)
8913 flags &= ~GOVD_LASTPRIVATE;
8914 if (flags == GOVD_SEEN)
8915 break;
8917 else
8918 break;
8919 splay_tree_node on
8920 = splay_tree_lookup (octx->variables,
8921 (splay_tree_key) decl);
8922 if (on && (on->value & GOVD_DATA_SHARE_CLASS) != 0)
8924 octx = NULL;
8925 break;
8927 omp_add_variable (octx, decl, flags);
8928 if (octx->outer_context == NULL)
8929 break;
8930 octx = octx->outer_context;
8932 while (1);
8933 if (octx
8934 && decl
8935 && (!OMP_CLAUSE_LINEAR_NO_COPYIN (c)
8936 || !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
8937 omp_notice_variable (octx, decl, true);
8939 flags = GOVD_LINEAR | GOVD_EXPLICIT;
8940 if (OMP_CLAUSE_LINEAR_NO_COPYIN (c)
8941 && OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
8943 notice_outer = false;
8944 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
8946 goto do_add;
8948 case OMP_CLAUSE_MAP:
8949 decl = OMP_CLAUSE_DECL (c);
8950 if (error_operand_p (decl))
8951 remove = true;
8952 switch (code)
8954 case OMP_TARGET:
8955 break;
8956 case OACC_DATA:
8957 if (TREE_CODE (TREE_TYPE (decl)) != ARRAY_TYPE)
8958 break;
8959 /* FALLTHRU */
8960 case OMP_TARGET_DATA:
8961 case OMP_TARGET_ENTER_DATA:
8962 case OMP_TARGET_EXIT_DATA:
8963 case OACC_ENTER_DATA:
8964 case OACC_EXIT_DATA:
8965 case OACC_HOST_DATA:
8966 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
8967 || (OMP_CLAUSE_MAP_KIND (c)
8968 == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
8969 /* For target {,enter ,exit }data only the array slice is
8970 mapped, but not the pointer to it. */
8971 remove = true;
8972 break;
8973 default:
8974 break;
8976 /* For Fortran, not only the pointer to the data is mapped but also
8977 the address of the pointer, the array descriptor etc.; for
8978 'exit data' - and in particular for 'delete:' - having an 'alloc:'
8979 does not make sense. Likewise, for 'update' only transferring the
8980 data itself is needed as the rest has been handled in previous
8981 directives. However, for 'exit data', the array descriptor needs
8982 to be delete; hence, we turn the MAP_TO_PSET into a MAP_DELETE.
8984 NOTE: Generally, it is not safe to perform "enter data" operations
8985 on arrays where the data *or the descriptor* may go out of scope
8986 before a corresponding "exit data" operation -- and such a
8987 descriptor may be synthesized temporarily, e.g. to pass an
8988 explicit-shape array to a function expecting an assumed-shape
8989 argument. Performing "enter data" inside the called function
8990 would thus be problematic. */
8991 if (code == OMP_TARGET_EXIT_DATA
8992 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_TO_PSET)
8993 OMP_CLAUSE_SET_MAP_KIND (c, OMP_CLAUSE_MAP_KIND (*prev_list_p)
8994 == GOMP_MAP_DELETE
8995 ? GOMP_MAP_DELETE : GOMP_MAP_RELEASE);
8996 else if ((code == OMP_TARGET_EXIT_DATA || code == OMP_TARGET_UPDATE)
8997 && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_POINTER
8998 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_TO_PSET))
8999 remove = true;
9001 if (remove)
9002 break;
9003 if (DECL_P (decl) && outer_ctx && (region_type & ORT_ACC))
9005 struct gimplify_omp_ctx *octx;
9006 for (octx = outer_ctx; octx; octx = octx->outer_context)
9008 if (octx->region_type != ORT_ACC_HOST_DATA)
9009 break;
9010 splay_tree_node n2
9011 = splay_tree_lookup (octx->variables,
9012 (splay_tree_key) decl);
9013 if (n2)
9014 error_at (OMP_CLAUSE_LOCATION (c), "variable %qE "
9015 "declared in enclosing %<host_data%> region",
9016 DECL_NAME (decl));
9019 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
9020 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
9021 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
9022 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
9023 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
9025 remove = true;
9026 break;
9028 else if ((OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
9029 || (OMP_CLAUSE_MAP_KIND (c)
9030 == GOMP_MAP_FIRSTPRIVATE_REFERENCE)
9031 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9032 && TREE_CODE (OMP_CLAUSE_SIZE (c)) != INTEGER_CST)
9034 OMP_CLAUSE_SIZE (c)
9035 = get_initialized_tmp_var (OMP_CLAUSE_SIZE (c), pre_p, NULL,
9036 false);
9037 if ((region_type & ORT_TARGET) != 0)
9038 omp_add_variable (ctx, OMP_CLAUSE_SIZE (c),
9039 GOVD_FIRSTPRIVATE | GOVD_SEEN);
9042 if (!DECL_P (decl))
9044 tree d = decl, *pd;
9045 if (TREE_CODE (d) == ARRAY_REF)
9047 while (TREE_CODE (d) == ARRAY_REF)
9048 d = TREE_OPERAND (d, 0);
9049 if (TREE_CODE (d) == COMPONENT_REF
9050 && TREE_CODE (TREE_TYPE (d)) == ARRAY_TYPE)
9051 decl = d;
9053 pd = &OMP_CLAUSE_DECL (c);
9054 if (d == decl
9055 && TREE_CODE (decl) == INDIRECT_REF
9056 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
9057 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
9058 == REFERENCE_TYPE))
9060 pd = &TREE_OPERAND (decl, 0);
9061 decl = TREE_OPERAND (decl, 0);
9063 bool indir_p = false;
9064 tree orig_decl = decl;
9065 tree decl_ref = NULL_TREE;
9066 if ((region_type & (ORT_ACC | ORT_TARGET | ORT_TARGET_DATA)) != 0
9067 && TREE_CODE (*pd) == COMPONENT_REF
9068 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH
9069 && code != OACC_UPDATE)
9071 while (TREE_CODE (decl) == COMPONENT_REF)
9073 decl = TREE_OPERAND (decl, 0);
9074 if (((TREE_CODE (decl) == MEM_REF
9075 && integer_zerop (TREE_OPERAND (decl, 1)))
9076 || INDIRECT_REF_P (decl))
9077 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
9078 == POINTER_TYPE))
9080 indir_p = true;
9081 decl = TREE_OPERAND (decl, 0);
9083 if (TREE_CODE (decl) == INDIRECT_REF
9084 && DECL_P (TREE_OPERAND (decl, 0))
9085 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
9086 == REFERENCE_TYPE))
9088 decl_ref = decl;
9089 decl = TREE_OPERAND (decl, 0);
9093 else if (TREE_CODE (decl) == COMPONENT_REF)
9095 while (TREE_CODE (decl) == COMPONENT_REF)
9096 decl = TREE_OPERAND (decl, 0);
9097 if (TREE_CODE (decl) == INDIRECT_REF
9098 && DECL_P (TREE_OPERAND (decl, 0))
9099 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
9100 == REFERENCE_TYPE))
9101 decl = TREE_OPERAND (decl, 0);
9103 if (decl != orig_decl && DECL_P (decl) && indir_p)
9105 gomp_map_kind k
9106 = ((code == OACC_EXIT_DATA || code == OMP_TARGET_EXIT_DATA)
9107 ? GOMP_MAP_DETACH : GOMP_MAP_ATTACH);
9108 /* We have a dereference of a struct member. Make this an
9109 attach/detach operation, and ensure the base pointer is
9110 mapped as a FIRSTPRIVATE_POINTER. */
9111 OMP_CLAUSE_SET_MAP_KIND (c, k);
9112 flags = GOVD_MAP | GOVD_SEEN | GOVD_EXPLICIT;
9113 tree next_clause = OMP_CLAUSE_CHAIN (c);
9114 if (k == GOMP_MAP_ATTACH
9115 && code != OACC_ENTER_DATA
9116 && code != OMP_TARGET_ENTER_DATA
9117 && (!next_clause
9118 || (OMP_CLAUSE_CODE (next_clause) != OMP_CLAUSE_MAP)
9119 || (OMP_CLAUSE_MAP_KIND (next_clause)
9120 != GOMP_MAP_POINTER)
9121 || OMP_CLAUSE_DECL (next_clause) != decl)
9122 && (!struct_deref_set
9123 || !struct_deref_set->contains (decl)))
9125 if (!struct_deref_set)
9126 struct_deref_set = new hash_set<tree> ();
9127 /* As well as the attach, we also need a
9128 FIRSTPRIVATE_POINTER clause to properly map the
9129 pointer to the struct base. */
9130 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
9131 OMP_CLAUSE_MAP);
9132 OMP_CLAUSE_SET_MAP_KIND (c2, GOMP_MAP_ALLOC);
9133 OMP_CLAUSE_MAP_MAYBE_ZERO_LENGTH_ARRAY_SECTION (c2)
9134 = 1;
9135 tree charptr_zero
9136 = build_int_cst (build_pointer_type (char_type_node),
9138 OMP_CLAUSE_DECL (c2)
9139 = build2 (MEM_REF, char_type_node,
9140 decl_ref ? decl_ref : decl, charptr_zero);
9141 OMP_CLAUSE_SIZE (c2) = size_zero_node;
9142 tree c3 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
9143 OMP_CLAUSE_MAP);
9144 OMP_CLAUSE_SET_MAP_KIND (c3,
9145 GOMP_MAP_FIRSTPRIVATE_POINTER);
9146 OMP_CLAUSE_DECL (c3) = decl;
9147 OMP_CLAUSE_SIZE (c3) = size_zero_node;
9148 tree mapgrp = *prev_list_p;
9149 *prev_list_p = c2;
9150 OMP_CLAUSE_CHAIN (c3) = mapgrp;
9151 OMP_CLAUSE_CHAIN (c2) = c3;
9153 struct_deref_set->add (decl);
9155 goto do_add_decl;
9157 /* An "attach/detach" operation on an update directive should
9158 behave as a GOMP_MAP_ALWAYS_POINTER. Beware that
9159 unlike attach or detach map kinds, GOMP_MAP_ALWAYS_POINTER
9160 depends on the previous mapping. */
9161 if (code == OACC_UPDATE
9162 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9163 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_ALWAYS_POINTER);
9164 if (DECL_P (decl)
9165 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_TO_PSET
9166 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ATTACH
9167 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_DETACH
9168 && code != OACC_UPDATE
9169 && code != OMP_TARGET_UPDATE)
9171 if (error_operand_p (decl))
9173 remove = true;
9174 break;
9177 tree stype = TREE_TYPE (decl);
9178 if (TREE_CODE (stype) == REFERENCE_TYPE)
9179 stype = TREE_TYPE (stype);
9180 if (TYPE_SIZE_UNIT (stype) == NULL
9181 || TREE_CODE (TYPE_SIZE_UNIT (stype)) != INTEGER_CST)
9183 error_at (OMP_CLAUSE_LOCATION (c),
9184 "mapping field %qE of variable length "
9185 "structure", OMP_CLAUSE_DECL (c));
9186 remove = true;
9187 break;
9190 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_POINTER
9191 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9193 /* Error recovery. */
9194 if (prev_list_p == NULL)
9196 remove = true;
9197 break;
9199 if (OMP_CLAUSE_CHAIN (*prev_list_p) != c)
9201 tree ch = OMP_CLAUSE_CHAIN (*prev_list_p);
9202 if (ch == NULL_TREE || OMP_CLAUSE_CHAIN (ch) != c)
9204 remove = true;
9205 break;
9210 poly_offset_int offset1;
9211 poly_int64 bitpos1;
9212 tree base_ref;
9214 tree base
9215 = extract_base_bit_offset (OMP_CLAUSE_DECL (c), &base_ref,
9216 &bitpos1, &offset1);
9218 gcc_assert (base == decl);
9220 splay_tree_node n
9221 = splay_tree_lookup (ctx->variables, (splay_tree_key)decl);
9222 bool ptr = (OMP_CLAUSE_MAP_KIND (c)
9223 == GOMP_MAP_ALWAYS_POINTER);
9224 bool attach_detach = (OMP_CLAUSE_MAP_KIND (c)
9225 == GOMP_MAP_ATTACH_DETACH);
9226 bool attach = OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH
9227 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_DETACH;
9228 bool has_attachments = false;
9229 /* For OpenACC, pointers in structs should trigger an
9230 attach action. */
9231 if (attach_detach
9232 && ((region_type & (ORT_ACC | ORT_TARGET | ORT_TARGET_DATA))
9233 || code == OMP_TARGET_ENTER_DATA
9234 || code == OMP_TARGET_EXIT_DATA))
9237 /* Turn a GOMP_MAP_ATTACH_DETACH clause into a
9238 GOMP_MAP_ATTACH or GOMP_MAP_DETACH clause after we
9239 have detected a case that needs a GOMP_MAP_STRUCT
9240 mapping added. */
9241 gomp_map_kind k
9242 = ((code == OACC_EXIT_DATA || code == OMP_TARGET_EXIT_DATA)
9243 ? GOMP_MAP_DETACH : GOMP_MAP_ATTACH);
9244 OMP_CLAUSE_SET_MAP_KIND (c, k);
9245 has_attachments = true;
9247 if (n == NULL || (n->value & GOVD_MAP) == 0)
9249 tree l = build_omp_clause (OMP_CLAUSE_LOCATION (c),
9250 OMP_CLAUSE_MAP);
9251 gomp_map_kind k = attach ? GOMP_MAP_FORCE_PRESENT
9252 : GOMP_MAP_STRUCT;
9254 OMP_CLAUSE_SET_MAP_KIND (l, k);
9255 if (base_ref)
9256 OMP_CLAUSE_DECL (l) = unshare_expr (base_ref);
9257 else
9258 OMP_CLAUSE_DECL (l) = decl;
9259 OMP_CLAUSE_SIZE (l)
9260 = (!attach
9261 ? size_int (1)
9262 : DECL_P (OMP_CLAUSE_DECL (l))
9263 ? DECL_SIZE_UNIT (OMP_CLAUSE_DECL (l))
9264 : TYPE_SIZE_UNIT (TREE_TYPE (OMP_CLAUSE_DECL (l))));
9265 if (struct_map_to_clause == NULL)
9266 struct_map_to_clause = new hash_map<tree, tree>;
9267 struct_map_to_clause->put (decl, l);
9268 if (ptr || attach_detach)
9270 insert_struct_comp_map (code, c, l, *prev_list_p,
9271 NULL);
9272 *prev_list_p = l;
9273 prev_list_p = NULL;
9275 else
9277 OMP_CLAUSE_CHAIN (l) = c;
9278 *list_p = l;
9279 list_p = &OMP_CLAUSE_CHAIN (l);
9281 if (base_ref && code == OMP_TARGET)
9283 tree c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
9284 OMP_CLAUSE_MAP);
9285 enum gomp_map_kind mkind
9286 = GOMP_MAP_FIRSTPRIVATE_REFERENCE;
9287 OMP_CLAUSE_SET_MAP_KIND (c2, mkind);
9288 OMP_CLAUSE_DECL (c2) = decl;
9289 OMP_CLAUSE_SIZE (c2) = size_zero_node;
9290 OMP_CLAUSE_CHAIN (c2) = OMP_CLAUSE_CHAIN (l);
9291 OMP_CLAUSE_CHAIN (l) = c2;
9293 flags = GOVD_MAP | GOVD_EXPLICIT;
9294 if (GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c))
9295 || ptr
9296 || attach_detach)
9297 flags |= GOVD_SEEN;
9298 if (has_attachments)
9299 flags |= GOVD_MAP_HAS_ATTACHMENTS;
9300 goto do_add_decl;
9302 else if (struct_map_to_clause)
9304 tree *osc = struct_map_to_clause->get (decl);
9305 tree *sc = NULL, *scp = NULL;
9306 if (GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c))
9307 || ptr
9308 || attach_detach)
9309 n->value |= GOVD_SEEN;
9310 sc = &OMP_CLAUSE_CHAIN (*osc);
9311 if (*sc != c
9312 && (OMP_CLAUSE_MAP_KIND (*sc)
9313 == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
9314 sc = &OMP_CLAUSE_CHAIN (*sc);
9315 /* Here "prev_list_p" is the end of the inserted
9316 alloc/release nodes after the struct node, OSC. */
9317 for (; *sc != c; sc = &OMP_CLAUSE_CHAIN (*sc))
9318 if ((ptr || attach_detach) && sc == prev_list_p)
9319 break;
9320 else if (TREE_CODE (OMP_CLAUSE_DECL (*sc))
9321 != COMPONENT_REF
9322 && (TREE_CODE (OMP_CLAUSE_DECL (*sc))
9323 != INDIRECT_REF)
9324 && (TREE_CODE (OMP_CLAUSE_DECL (*sc))
9325 != ARRAY_REF))
9326 break;
9327 else
9329 tree sc_decl = OMP_CLAUSE_DECL (*sc);
9330 poly_offset_int offsetn;
9331 poly_int64 bitposn;
9332 tree base
9333 = extract_base_bit_offset (sc_decl, NULL,
9334 &bitposn, &offsetn);
9335 if (base != decl)
9336 break;
9337 if (scp)
9338 continue;
9339 if ((region_type & ORT_ACC) != 0)
9341 /* This duplicate checking code is currently only
9342 enabled for OpenACC. */
9343 tree d1 = OMP_CLAUSE_DECL (*sc);
9344 tree d2 = OMP_CLAUSE_DECL (c);
9345 while (TREE_CODE (d1) == ARRAY_REF)
9346 d1 = TREE_OPERAND (d1, 0);
9347 while (TREE_CODE (d2) == ARRAY_REF)
9348 d2 = TREE_OPERAND (d2, 0);
9349 if (TREE_CODE (d1) == INDIRECT_REF)
9350 d1 = TREE_OPERAND (d1, 0);
9351 if (TREE_CODE (d2) == INDIRECT_REF)
9352 d2 = TREE_OPERAND (d2, 0);
9353 while (TREE_CODE (d1) == COMPONENT_REF)
9354 if (TREE_CODE (d2) == COMPONENT_REF
9355 && TREE_OPERAND (d1, 1)
9356 == TREE_OPERAND (d2, 1))
9358 d1 = TREE_OPERAND (d1, 0);
9359 d2 = TREE_OPERAND (d2, 0);
9361 else
9362 break;
9363 if (d1 == d2)
9365 error_at (OMP_CLAUSE_LOCATION (c),
9366 "%qE appears more than once in map "
9367 "clauses", OMP_CLAUSE_DECL (c));
9368 remove = true;
9369 break;
9372 if (maybe_lt (offset1, offsetn)
9373 || (known_eq (offset1, offsetn)
9374 && maybe_lt (bitpos1, bitposn)))
9376 if (ptr || attach_detach)
9377 scp = sc;
9378 else
9379 break;
9382 if (remove)
9383 break;
9384 if (!attach)
9385 OMP_CLAUSE_SIZE (*osc)
9386 = size_binop (PLUS_EXPR, OMP_CLAUSE_SIZE (*osc),
9387 size_one_node);
9388 if (ptr || attach_detach)
9390 tree cl = insert_struct_comp_map (code, c, NULL,
9391 *prev_list_p, scp);
9392 if (sc == prev_list_p)
9394 *sc = cl;
9395 prev_list_p = NULL;
9397 else
9399 *prev_list_p = OMP_CLAUSE_CHAIN (c);
9400 list_p = prev_list_p;
9401 prev_list_p = NULL;
9402 OMP_CLAUSE_CHAIN (c) = *sc;
9403 *sc = cl;
9404 continue;
9407 else if (*sc != c)
9409 *list_p = OMP_CLAUSE_CHAIN (c);
9410 OMP_CLAUSE_CHAIN (c) = *sc;
9411 *sc = c;
9412 continue;
9416 else if ((code == OACC_ENTER_DATA
9417 || code == OACC_EXIT_DATA
9418 || code == OACC_DATA
9419 || code == OACC_PARALLEL
9420 || code == OACC_KERNELS
9421 || code == OACC_SERIAL)
9422 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9424 gomp_map_kind k = (code == OACC_EXIT_DATA
9425 ? GOMP_MAP_DETACH : GOMP_MAP_ATTACH);
9426 OMP_CLAUSE_SET_MAP_KIND (c, k);
9429 if (gimplify_expr (pd, pre_p, NULL, is_gimple_lvalue, fb_lvalue)
9430 == GS_ERROR)
9432 remove = true;
9433 break;
9436 if (!remove
9437 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ALWAYS_POINTER
9438 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_ATTACH_DETACH
9439 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_TO_PSET
9440 && OMP_CLAUSE_CHAIN (c)
9441 && OMP_CLAUSE_CODE (OMP_CLAUSE_CHAIN (c)) == OMP_CLAUSE_MAP
9442 && ((OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (c))
9443 == GOMP_MAP_ALWAYS_POINTER)
9444 || (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (c))
9445 == GOMP_MAP_ATTACH_DETACH)
9446 || (OMP_CLAUSE_MAP_KIND (OMP_CLAUSE_CHAIN (c))
9447 == GOMP_MAP_TO_PSET)))
9448 prev_list_p = list_p;
9450 break;
9452 else
9454 /* DECL_P (decl) == true */
9455 tree *sc;
9456 if (struct_map_to_clause
9457 && (sc = struct_map_to_clause->get (decl)) != NULL
9458 && OMP_CLAUSE_MAP_KIND (*sc) == GOMP_MAP_STRUCT
9459 && decl == OMP_CLAUSE_DECL (*sc))
9461 /* We have found a map of the whole structure after a
9462 leading GOMP_MAP_STRUCT has been created, so refill the
9463 leading clause into a map of the whole structure
9464 variable, and remove the current one.
9465 TODO: we should be able to remove some maps of the
9466 following structure element maps if they are of
9467 compatible TO/FROM/ALLOC type. */
9468 OMP_CLAUSE_SET_MAP_KIND (*sc, OMP_CLAUSE_MAP_KIND (c));
9469 OMP_CLAUSE_SIZE (*sc) = unshare_expr (OMP_CLAUSE_SIZE (c));
9470 remove = true;
9471 break;
9474 flags = GOVD_MAP | GOVD_EXPLICIT;
9475 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_TO
9476 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_TOFROM)
9477 flags |= GOVD_MAP_ALWAYS_TO;
9479 if ((code == OMP_TARGET
9480 || code == OMP_TARGET_DATA
9481 || code == OMP_TARGET_ENTER_DATA
9482 || code == OMP_TARGET_EXIT_DATA)
9483 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ATTACH_DETACH)
9485 for (struct gimplify_omp_ctx *octx = outer_ctx; octx;
9486 octx = octx->outer_context)
9488 splay_tree_node n
9489 = splay_tree_lookup (octx->variables,
9490 (splay_tree_key) OMP_CLAUSE_DECL (c));
9491 /* If this is contained in an outer OpenMP region as a
9492 firstprivate value, remove the attach/detach. */
9493 if (n && (n->value & GOVD_FIRSTPRIVATE))
9495 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FIRSTPRIVATE_POINTER);
9496 goto do_add;
9500 enum gomp_map_kind map_kind = (code == OMP_TARGET_EXIT_DATA
9501 ? GOMP_MAP_DETACH
9502 : GOMP_MAP_ATTACH);
9503 OMP_CLAUSE_SET_MAP_KIND (c, map_kind);
9506 goto do_add;
9508 case OMP_CLAUSE_DEPEND:
9509 if (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SINK)
9511 tree deps = OMP_CLAUSE_DECL (c);
9512 while (deps && TREE_CODE (deps) == TREE_LIST)
9514 if (TREE_CODE (TREE_PURPOSE (deps)) == TRUNC_DIV_EXPR
9515 && DECL_P (TREE_OPERAND (TREE_PURPOSE (deps), 1)))
9516 gimplify_expr (&TREE_OPERAND (TREE_PURPOSE (deps), 1),
9517 pre_p, NULL, is_gimple_val, fb_rvalue);
9518 deps = TREE_CHAIN (deps);
9520 break;
9522 else if (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SOURCE)
9523 break;
9524 if (handled_depend_iterators == -1)
9525 handled_depend_iterators = gimplify_omp_depend (list_p, pre_p);
9526 if (handled_depend_iterators)
9528 if (handled_depend_iterators == 2)
9529 remove = true;
9530 break;
9532 if (TREE_CODE (OMP_CLAUSE_DECL (c)) == COMPOUND_EXPR)
9534 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (c), 0), pre_p,
9535 NULL, is_gimple_val, fb_rvalue);
9536 OMP_CLAUSE_DECL (c) = TREE_OPERAND (OMP_CLAUSE_DECL (c), 1);
9538 if (error_operand_p (OMP_CLAUSE_DECL (c)))
9540 remove = true;
9541 break;
9543 OMP_CLAUSE_DECL (c) = build_fold_addr_expr (OMP_CLAUSE_DECL (c));
9544 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p, NULL,
9545 is_gimple_val, fb_rvalue) == GS_ERROR)
9547 remove = true;
9548 break;
9550 if (code == OMP_TASK)
9551 ctx->has_depend = true;
9552 break;
9554 case OMP_CLAUSE_TO:
9555 case OMP_CLAUSE_FROM:
9556 case OMP_CLAUSE__CACHE_:
9557 decl = OMP_CLAUSE_DECL (c);
9558 if (error_operand_p (decl))
9560 remove = true;
9561 break;
9563 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
9564 OMP_CLAUSE_SIZE (c) = DECL_P (decl) ? DECL_SIZE_UNIT (decl)
9565 : TYPE_SIZE_UNIT (TREE_TYPE (decl));
9566 if (gimplify_expr (&OMP_CLAUSE_SIZE (c), pre_p,
9567 NULL, is_gimple_val, fb_rvalue) == GS_ERROR)
9569 remove = true;
9570 break;
9572 if (!DECL_P (decl))
9574 if (gimplify_expr (&OMP_CLAUSE_DECL (c), pre_p,
9575 NULL, is_gimple_lvalue, fb_lvalue)
9576 == GS_ERROR)
9578 remove = true;
9579 break;
9581 break;
9583 goto do_notice;
9585 case OMP_CLAUSE_USE_DEVICE_PTR:
9586 case OMP_CLAUSE_USE_DEVICE_ADDR:
9587 flags = GOVD_EXPLICIT;
9588 goto do_add;
9590 case OMP_CLAUSE_IS_DEVICE_PTR:
9591 flags = GOVD_FIRSTPRIVATE | GOVD_EXPLICIT;
9592 goto do_add;
9594 do_add:
9595 decl = OMP_CLAUSE_DECL (c);
9596 do_add_decl:
9597 if (error_operand_p (decl))
9599 remove = true;
9600 break;
9602 if (DECL_NAME (decl) == NULL_TREE && (flags & GOVD_SHARED) == 0)
9604 tree t = omp_member_access_dummy_var (decl);
9605 if (t)
9607 tree v = DECL_VALUE_EXPR (decl);
9608 DECL_NAME (decl) = DECL_NAME (TREE_OPERAND (v, 1));
9609 if (outer_ctx)
9610 omp_notice_variable (outer_ctx, t, true);
9613 if (code == OACC_DATA
9614 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP
9615 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
9616 flags |= GOVD_MAP_0LEN_ARRAY;
9617 omp_add_variable (ctx, decl, flags);
9618 if ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
9619 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_IN_REDUCTION
9620 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_TASK_REDUCTION)
9621 && OMP_CLAUSE_REDUCTION_PLACEHOLDER (c))
9623 omp_add_variable (ctx, OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
9624 GOVD_LOCAL | GOVD_SEEN);
9625 if (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c)
9626 && walk_tree (&OMP_CLAUSE_REDUCTION_INIT (c),
9627 find_decl_expr,
9628 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
9629 NULL) == NULL_TREE)
9630 omp_add_variable (ctx,
9631 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c),
9632 GOVD_LOCAL | GOVD_SEEN);
9633 gimplify_omp_ctxp = ctx;
9634 push_gimplify_context ();
9636 OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c) = NULL;
9637 OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c) = NULL;
9639 gimplify_and_add (OMP_CLAUSE_REDUCTION_INIT (c),
9640 &OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c));
9641 pop_gimplify_context
9642 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_INIT (c)));
9643 push_gimplify_context ();
9644 gimplify_and_add (OMP_CLAUSE_REDUCTION_MERGE (c),
9645 &OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c));
9646 pop_gimplify_context
9647 (gimple_seq_first_stmt (OMP_CLAUSE_REDUCTION_GIMPLE_MERGE (c)));
9648 OMP_CLAUSE_REDUCTION_INIT (c) = NULL_TREE;
9649 OMP_CLAUSE_REDUCTION_MERGE (c) = NULL_TREE;
9651 gimplify_omp_ctxp = outer_ctx;
9653 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
9654 && OMP_CLAUSE_LASTPRIVATE_STMT (c))
9656 gimplify_omp_ctxp = ctx;
9657 push_gimplify_context ();
9658 if (TREE_CODE (OMP_CLAUSE_LASTPRIVATE_STMT (c)) != BIND_EXPR)
9660 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
9661 NULL, NULL);
9662 TREE_SIDE_EFFECTS (bind) = 1;
9663 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LASTPRIVATE_STMT (c);
9664 OMP_CLAUSE_LASTPRIVATE_STMT (c) = bind;
9666 gimplify_and_add (OMP_CLAUSE_LASTPRIVATE_STMT (c),
9667 &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c));
9668 pop_gimplify_context
9669 (gimple_seq_first_stmt (OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c)));
9670 OMP_CLAUSE_LASTPRIVATE_STMT (c) = NULL_TREE;
9672 gimplify_omp_ctxp = outer_ctx;
9674 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
9675 && OMP_CLAUSE_LINEAR_STMT (c))
9677 gimplify_omp_ctxp = ctx;
9678 push_gimplify_context ();
9679 if (TREE_CODE (OMP_CLAUSE_LINEAR_STMT (c)) != BIND_EXPR)
9681 tree bind = build3 (BIND_EXPR, void_type_node, NULL,
9682 NULL, NULL);
9683 TREE_SIDE_EFFECTS (bind) = 1;
9684 BIND_EXPR_BODY (bind) = OMP_CLAUSE_LINEAR_STMT (c);
9685 OMP_CLAUSE_LINEAR_STMT (c) = bind;
9687 gimplify_and_add (OMP_CLAUSE_LINEAR_STMT (c),
9688 &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c));
9689 pop_gimplify_context
9690 (gimple_seq_first_stmt (OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c)));
9691 OMP_CLAUSE_LINEAR_STMT (c) = NULL_TREE;
9693 gimplify_omp_ctxp = outer_ctx;
9695 if (notice_outer)
9696 goto do_notice;
9697 break;
9699 case OMP_CLAUSE_COPYIN:
9700 case OMP_CLAUSE_COPYPRIVATE:
9701 decl = OMP_CLAUSE_DECL (c);
9702 if (error_operand_p (decl))
9704 remove = true;
9705 break;
9707 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_COPYPRIVATE
9708 && !remove
9709 && !omp_check_private (ctx, decl, true))
9711 remove = true;
9712 if (is_global_var (decl))
9714 if (DECL_THREAD_LOCAL_P (decl))
9715 remove = false;
9716 else if (DECL_HAS_VALUE_EXPR_P (decl))
9718 tree value = get_base_address (DECL_VALUE_EXPR (decl));
9720 if (value
9721 && DECL_P (value)
9722 && DECL_THREAD_LOCAL_P (value))
9723 remove = false;
9726 if (remove)
9727 error_at (OMP_CLAUSE_LOCATION (c),
9728 "copyprivate variable %qE is not threadprivate"
9729 " or private in outer context", DECL_NAME (decl));
9731 do_notice:
9732 if ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
9733 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_FIRSTPRIVATE
9734 || OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE)
9735 && outer_ctx
9736 && ((region_type & ORT_TASKLOOP) == ORT_TASKLOOP
9737 || (region_type == ORT_WORKSHARE
9738 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
9739 && (OMP_CLAUSE_REDUCTION_INSCAN (c)
9740 || code == OMP_LOOP)))
9741 && (outer_ctx->region_type == ORT_COMBINED_PARALLEL
9742 || (code == OMP_LOOP
9743 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
9744 && ((outer_ctx->region_type & ORT_COMBINED_TEAMS)
9745 == ORT_COMBINED_TEAMS))))
9747 splay_tree_node on
9748 = splay_tree_lookup (outer_ctx->variables,
9749 (splay_tree_key)decl);
9750 if (on == NULL || (on->value & GOVD_DATA_SHARE_CLASS) == 0)
9752 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
9753 && TREE_CODE (OMP_CLAUSE_DECL (c)) == MEM_REF
9754 && (TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE
9755 || (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
9756 && (TREE_CODE (TREE_TYPE (TREE_TYPE (decl)))
9757 == POINTER_TYPE))))
9758 omp_firstprivatize_variable (outer_ctx, decl);
9759 else
9761 omp_add_variable (outer_ctx, decl,
9762 GOVD_SEEN | GOVD_SHARED);
9763 if (outer_ctx->outer_context)
9764 omp_notice_variable (outer_ctx->outer_context, decl,
9765 true);
9769 if (outer_ctx)
9770 omp_notice_variable (outer_ctx, decl, true);
9771 if (check_non_private
9772 && region_type == ORT_WORKSHARE
9773 && (OMP_CLAUSE_CODE (c) != OMP_CLAUSE_REDUCTION
9774 || decl == OMP_CLAUSE_DECL (c)
9775 || (TREE_CODE (OMP_CLAUSE_DECL (c)) == MEM_REF
9776 && (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c), 0))
9777 == ADDR_EXPR
9778 || (TREE_CODE (TREE_OPERAND (OMP_CLAUSE_DECL (c), 0))
9779 == POINTER_PLUS_EXPR
9780 && (TREE_CODE (TREE_OPERAND (TREE_OPERAND
9781 (OMP_CLAUSE_DECL (c), 0), 0))
9782 == ADDR_EXPR)))))
9783 && omp_check_private (ctx, decl, false))
9785 error ("%s variable %qE is private in outer context",
9786 check_non_private, DECL_NAME (decl));
9787 remove = true;
9789 break;
9791 case OMP_CLAUSE_DETACH:
9792 flags = GOVD_FIRSTPRIVATE | GOVD_SEEN;
9793 goto do_add;
9795 case OMP_CLAUSE_IF:
9796 if (OMP_CLAUSE_IF_MODIFIER (c) != ERROR_MARK
9797 && OMP_CLAUSE_IF_MODIFIER (c) != code)
9799 const char *p[2];
9800 for (int i = 0; i < 2; i++)
9801 switch (i ? OMP_CLAUSE_IF_MODIFIER (c) : code)
9803 case VOID_CST: p[i] = "cancel"; break;
9804 case OMP_PARALLEL: p[i] = "parallel"; break;
9805 case OMP_SIMD: p[i] = "simd"; break;
9806 case OMP_TASK: p[i] = "task"; break;
9807 case OMP_TASKLOOP: p[i] = "taskloop"; break;
9808 case OMP_TARGET_DATA: p[i] = "target data"; break;
9809 case OMP_TARGET: p[i] = "target"; break;
9810 case OMP_TARGET_UPDATE: p[i] = "target update"; break;
9811 case OMP_TARGET_ENTER_DATA:
9812 p[i] = "target enter data"; break;
9813 case OMP_TARGET_EXIT_DATA: p[i] = "target exit data"; break;
9814 default: gcc_unreachable ();
9816 error_at (OMP_CLAUSE_LOCATION (c),
9817 "expected %qs %<if%> clause modifier rather than %qs",
9818 p[0], p[1]);
9819 remove = true;
9821 /* Fall through. */
9823 case OMP_CLAUSE_FINAL:
9824 OMP_CLAUSE_OPERAND (c, 0)
9825 = gimple_boolify (OMP_CLAUSE_OPERAND (c, 0));
9826 /* Fall through. */
9828 case OMP_CLAUSE_SCHEDULE:
9829 case OMP_CLAUSE_NUM_THREADS:
9830 case OMP_CLAUSE_NUM_TEAMS:
9831 case OMP_CLAUSE_THREAD_LIMIT:
9832 case OMP_CLAUSE_DIST_SCHEDULE:
9833 case OMP_CLAUSE_DEVICE:
9834 case OMP_CLAUSE_PRIORITY:
9835 case OMP_CLAUSE_GRAINSIZE:
9836 case OMP_CLAUSE_NUM_TASKS:
9837 case OMP_CLAUSE_HINT:
9838 case OMP_CLAUSE_ASYNC:
9839 case OMP_CLAUSE_WAIT:
9840 case OMP_CLAUSE_NUM_GANGS:
9841 case OMP_CLAUSE_NUM_WORKERS:
9842 case OMP_CLAUSE_VECTOR_LENGTH:
9843 case OMP_CLAUSE_WORKER:
9844 case OMP_CLAUSE_VECTOR:
9845 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 0), pre_p, NULL,
9846 is_gimple_val, fb_rvalue) == GS_ERROR)
9847 remove = true;
9848 break;
9850 case OMP_CLAUSE_GANG:
9851 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 0), pre_p, NULL,
9852 is_gimple_val, fb_rvalue) == GS_ERROR)
9853 remove = true;
9854 if (gimplify_expr (&OMP_CLAUSE_OPERAND (c, 1), pre_p, NULL,
9855 is_gimple_val, fb_rvalue) == GS_ERROR)
9856 remove = true;
9857 break;
9859 case OMP_CLAUSE_NOWAIT:
9860 nowait = 1;
9861 break;
9863 case OMP_CLAUSE_ORDERED:
9864 case OMP_CLAUSE_UNTIED:
9865 case OMP_CLAUSE_COLLAPSE:
9866 case OMP_CLAUSE_TILE:
9867 case OMP_CLAUSE_AUTO:
9868 case OMP_CLAUSE_SEQ:
9869 case OMP_CLAUSE_INDEPENDENT:
9870 case OMP_CLAUSE_MERGEABLE:
9871 case OMP_CLAUSE_PROC_BIND:
9872 case OMP_CLAUSE_SAFELEN:
9873 case OMP_CLAUSE_SIMDLEN:
9874 case OMP_CLAUSE_NOGROUP:
9875 case OMP_CLAUSE_THREADS:
9876 case OMP_CLAUSE_SIMD:
9877 case OMP_CLAUSE_BIND:
9878 case OMP_CLAUSE_IF_PRESENT:
9879 case OMP_CLAUSE_FINALIZE:
9880 break;
9882 case OMP_CLAUSE_ORDER:
9883 ctx->order_concurrent = true;
9884 break;
9886 case OMP_CLAUSE_DEFAULTMAP:
9887 enum gimplify_defaultmap_kind gdmkmin, gdmkmax;
9888 switch (OMP_CLAUSE_DEFAULTMAP_CATEGORY (c))
9890 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_UNSPECIFIED:
9891 gdmkmin = GDMK_SCALAR;
9892 gdmkmax = GDMK_POINTER;
9893 break;
9894 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_SCALAR:
9895 gdmkmin = gdmkmax = GDMK_SCALAR;
9896 break;
9897 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_AGGREGATE:
9898 gdmkmin = gdmkmax = GDMK_AGGREGATE;
9899 break;
9900 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_ALLOCATABLE:
9901 gdmkmin = gdmkmax = GDMK_ALLOCATABLE;
9902 break;
9903 case OMP_CLAUSE_DEFAULTMAP_CATEGORY_POINTER:
9904 gdmkmin = gdmkmax = GDMK_POINTER;
9905 break;
9906 default:
9907 gcc_unreachable ();
9909 for (int gdmk = gdmkmin; gdmk <= gdmkmax; gdmk++)
9910 switch (OMP_CLAUSE_DEFAULTMAP_BEHAVIOR (c))
9912 case OMP_CLAUSE_DEFAULTMAP_ALLOC:
9913 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_ALLOC_ONLY;
9914 break;
9915 case OMP_CLAUSE_DEFAULTMAP_TO:
9916 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_TO_ONLY;
9917 break;
9918 case OMP_CLAUSE_DEFAULTMAP_FROM:
9919 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_FROM_ONLY;
9920 break;
9921 case OMP_CLAUSE_DEFAULTMAP_TOFROM:
9922 ctx->defaultmap[gdmk] = GOVD_MAP;
9923 break;
9924 case OMP_CLAUSE_DEFAULTMAP_FIRSTPRIVATE:
9925 ctx->defaultmap[gdmk] = GOVD_FIRSTPRIVATE;
9926 break;
9927 case OMP_CLAUSE_DEFAULTMAP_NONE:
9928 ctx->defaultmap[gdmk] = 0;
9929 break;
9930 case OMP_CLAUSE_DEFAULTMAP_DEFAULT:
9931 switch (gdmk)
9933 case GDMK_SCALAR:
9934 ctx->defaultmap[gdmk] = GOVD_FIRSTPRIVATE;
9935 break;
9936 case GDMK_AGGREGATE:
9937 case GDMK_ALLOCATABLE:
9938 ctx->defaultmap[gdmk] = GOVD_MAP;
9939 break;
9940 case GDMK_POINTER:
9941 ctx->defaultmap[gdmk] = GOVD_MAP | GOVD_MAP_0LEN_ARRAY;
9942 break;
9943 default:
9944 gcc_unreachable ();
9946 break;
9947 default:
9948 gcc_unreachable ();
9950 break;
9952 case OMP_CLAUSE_ALIGNED:
9953 decl = OMP_CLAUSE_DECL (c);
9954 if (error_operand_p (decl))
9956 remove = true;
9957 break;
9959 if (gimplify_expr (&OMP_CLAUSE_ALIGNED_ALIGNMENT (c), pre_p, NULL,
9960 is_gimple_val, fb_rvalue) == GS_ERROR)
9962 remove = true;
9963 break;
9965 if (!is_global_var (decl)
9966 && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
9967 omp_add_variable (ctx, decl, GOVD_ALIGNED);
9968 break;
9970 case OMP_CLAUSE_NONTEMPORAL:
9971 decl = OMP_CLAUSE_DECL (c);
9972 if (error_operand_p (decl))
9974 remove = true;
9975 break;
9977 omp_add_variable (ctx, decl, GOVD_NONTEMPORAL);
9978 break;
9980 case OMP_CLAUSE_ALLOCATE:
9981 decl = OMP_CLAUSE_DECL (c);
9982 if (error_operand_p (decl))
9984 remove = true;
9985 break;
9987 if (gimplify_expr (&OMP_CLAUSE_ALLOCATE_ALLOCATOR (c), pre_p, NULL,
9988 is_gimple_val, fb_rvalue) == GS_ERROR)
9990 remove = true;
9991 break;
9993 else if (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c) == NULL_TREE
9994 || (TREE_CODE (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c))
9995 == INTEGER_CST))
9997 else if (code == OMP_TASKLOOP
9998 || !DECL_P (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)))
9999 OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
10000 = get_initialized_tmp_var (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
10001 pre_p, NULL, false);
10002 break;
10004 case OMP_CLAUSE_DEFAULT:
10005 ctx->default_kind = OMP_CLAUSE_DEFAULT_KIND (c);
10006 break;
10008 case OMP_CLAUSE_INCLUSIVE:
10009 case OMP_CLAUSE_EXCLUSIVE:
10010 decl = OMP_CLAUSE_DECL (c);
10012 splay_tree_node n = splay_tree_lookup (outer_ctx->variables,
10013 (splay_tree_key) decl);
10014 if (n == NULL || (n->value & GOVD_REDUCTION) == 0)
10016 error_at (OMP_CLAUSE_LOCATION (c),
10017 "%qD specified in %qs clause but not in %<inscan%> "
10018 "%<reduction%> clause on the containing construct",
10019 decl, omp_clause_code_name[OMP_CLAUSE_CODE (c)]);
10020 remove = true;
10022 else
10024 n->value |= GOVD_REDUCTION_INSCAN;
10025 if (outer_ctx->region_type == ORT_SIMD
10026 && outer_ctx->outer_context
10027 && outer_ctx->outer_context->region_type == ORT_WORKSHARE)
10029 n = splay_tree_lookup (outer_ctx->outer_context->variables,
10030 (splay_tree_key) decl);
10031 if (n && (n->value & GOVD_REDUCTION) != 0)
10032 n->value |= GOVD_REDUCTION_INSCAN;
10036 break;
10038 default:
10039 gcc_unreachable ();
10042 if (code == OACC_DATA
10043 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP
10044 && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER
10045 || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_REFERENCE))
10046 remove = true;
10047 if (remove)
10048 *list_p = OMP_CLAUSE_CHAIN (c);
10049 else
10050 list_p = &OMP_CLAUSE_CHAIN (c);
10053 ctx->clauses = *orig_list_p;
10054 gimplify_omp_ctxp = ctx;
10055 if (struct_map_to_clause)
10056 delete struct_map_to_clause;
10057 if (struct_deref_set)
10058 delete struct_deref_set;
10061 /* Return true if DECL is a candidate for shared to firstprivate
10062 optimization. We only consider non-addressable scalars, not
10063 too big, and not references. */
10065 static bool
10066 omp_shared_to_firstprivate_optimizable_decl_p (tree decl)
10068 if (TREE_ADDRESSABLE (decl))
10069 return false;
10070 tree type = TREE_TYPE (decl);
10071 if (!is_gimple_reg_type (type)
10072 || TREE_CODE (type) == REFERENCE_TYPE
10073 || TREE_ADDRESSABLE (type))
10074 return false;
10075 /* Don't optimize too large decls, as each thread/task will have
10076 its own. */
10077 HOST_WIDE_INT len = int_size_in_bytes (type);
10078 if (len == -1 || len > 4 * POINTER_SIZE / BITS_PER_UNIT)
10079 return false;
10080 if (lang_hooks.decls.omp_privatize_by_reference (decl))
10081 return false;
10082 return true;
10085 /* Helper function of omp_find_stores_op and gimplify_adjust_omp_clauses*.
10086 For omp_shared_to_firstprivate_optimizable_decl_p decl mark it as
10087 GOVD_WRITTEN in outer contexts. */
10089 static void
10090 omp_mark_stores (struct gimplify_omp_ctx *ctx, tree decl)
10092 for (; ctx; ctx = ctx->outer_context)
10094 splay_tree_node n = splay_tree_lookup (ctx->variables,
10095 (splay_tree_key) decl);
10096 if (n == NULL)
10097 continue;
10098 else if (n->value & GOVD_SHARED)
10100 n->value |= GOVD_WRITTEN;
10101 return;
10103 else if (n->value & GOVD_DATA_SHARE_CLASS)
10104 return;
10108 /* Helper callback for walk_gimple_seq to discover possible stores
10109 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
10110 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
10111 for those. */
10113 static tree
10114 omp_find_stores_op (tree *tp, int *walk_subtrees, void *data)
10116 struct walk_stmt_info *wi = (struct walk_stmt_info *) data;
10118 *walk_subtrees = 0;
10119 if (!wi->is_lhs)
10120 return NULL_TREE;
10122 tree op = *tp;
10125 if (handled_component_p (op))
10126 op = TREE_OPERAND (op, 0);
10127 else if ((TREE_CODE (op) == MEM_REF || TREE_CODE (op) == TARGET_MEM_REF)
10128 && TREE_CODE (TREE_OPERAND (op, 0)) == ADDR_EXPR)
10129 op = TREE_OPERAND (TREE_OPERAND (op, 0), 0);
10130 else
10131 break;
10133 while (1);
10134 if (!DECL_P (op) || !omp_shared_to_firstprivate_optimizable_decl_p (op))
10135 return NULL_TREE;
10137 omp_mark_stores (gimplify_omp_ctxp, op);
10138 return NULL_TREE;
10141 /* Helper callback for walk_gimple_seq to discover possible stores
10142 to omp_shared_to_firstprivate_optimizable_decl_p decls and set
10143 GOVD_WRITTEN if they are GOVD_SHARED in some outer context
10144 for those. */
10146 static tree
10147 omp_find_stores_stmt (gimple_stmt_iterator *gsi_p,
10148 bool *handled_ops_p,
10149 struct walk_stmt_info *wi)
10151 gimple *stmt = gsi_stmt (*gsi_p);
10152 switch (gimple_code (stmt))
10154 /* Don't recurse on OpenMP constructs for which
10155 gimplify_adjust_omp_clauses already handled the bodies,
10156 except handle gimple_omp_for_pre_body. */
10157 case GIMPLE_OMP_FOR:
10158 *handled_ops_p = true;
10159 if (gimple_omp_for_pre_body (stmt))
10160 walk_gimple_seq (gimple_omp_for_pre_body (stmt),
10161 omp_find_stores_stmt, omp_find_stores_op, wi);
10162 break;
10163 case GIMPLE_OMP_PARALLEL:
10164 case GIMPLE_OMP_TASK:
10165 case GIMPLE_OMP_SECTIONS:
10166 case GIMPLE_OMP_SINGLE:
10167 case GIMPLE_OMP_TARGET:
10168 case GIMPLE_OMP_TEAMS:
10169 case GIMPLE_OMP_CRITICAL:
10170 *handled_ops_p = true;
10171 break;
10172 default:
10173 break;
10175 return NULL_TREE;
10178 struct gimplify_adjust_omp_clauses_data
10180 tree *list_p;
10181 gimple_seq *pre_p;
10184 /* For all variables that were not actually used within the context,
10185 remove PRIVATE, SHARED, and FIRSTPRIVATE clauses. */
10187 static int
10188 gimplify_adjust_omp_clauses_1 (splay_tree_node n, void *data)
10190 tree *list_p = ((struct gimplify_adjust_omp_clauses_data *) data)->list_p;
10191 gimple_seq *pre_p
10192 = ((struct gimplify_adjust_omp_clauses_data *) data)->pre_p;
10193 tree decl = (tree) n->key;
10194 unsigned flags = n->value;
10195 enum omp_clause_code code;
10196 tree clause;
10197 bool private_debug;
10199 if (gimplify_omp_ctxp->region_type == ORT_COMBINED_PARALLEL
10200 && (flags & GOVD_LASTPRIVATE_CONDITIONAL) != 0)
10201 flags = GOVD_SHARED | GOVD_SEEN | GOVD_WRITTEN;
10202 if (flags & (GOVD_EXPLICIT | GOVD_LOCAL))
10203 return 0;
10204 if ((flags & GOVD_SEEN) == 0)
10205 return 0;
10206 if ((flags & GOVD_MAP_HAS_ATTACHMENTS) != 0)
10207 return 0;
10208 if (flags & GOVD_DEBUG_PRIVATE)
10210 gcc_assert ((flags & GOVD_DATA_SHARE_CLASS) == GOVD_SHARED);
10211 private_debug = true;
10213 else if (flags & GOVD_MAP)
10214 private_debug = false;
10215 else
10216 private_debug
10217 = lang_hooks.decls.omp_private_debug_clause (decl,
10218 !!(flags & GOVD_SHARED));
10219 if (private_debug)
10220 code = OMP_CLAUSE_PRIVATE;
10221 else if (flags & GOVD_MAP)
10223 code = OMP_CLAUSE_MAP;
10224 if ((gimplify_omp_ctxp->region_type & ORT_ACC) == 0
10225 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl))))
10227 error ("%<_Atomic%> %qD in implicit %<map%> clause", decl);
10228 return 0;
10230 if (VAR_P (decl)
10231 && DECL_IN_CONSTANT_POOL (decl)
10232 && !lookup_attribute ("omp declare target",
10233 DECL_ATTRIBUTES (decl)))
10235 tree id = get_identifier ("omp declare target");
10236 DECL_ATTRIBUTES (decl)
10237 = tree_cons (id, NULL_TREE, DECL_ATTRIBUTES (decl));
10238 varpool_node *node = varpool_node::get (decl);
10239 if (node)
10241 node->offloadable = 1;
10242 if (ENABLE_OFFLOADING)
10243 g->have_offload = true;
10247 else if (flags & GOVD_SHARED)
10249 if (is_global_var (decl))
10251 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
10252 while (ctx != NULL)
10254 splay_tree_node on
10255 = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10256 if (on && (on->value & (GOVD_FIRSTPRIVATE | GOVD_LASTPRIVATE
10257 | GOVD_PRIVATE | GOVD_REDUCTION
10258 | GOVD_LINEAR | GOVD_MAP)) != 0)
10259 break;
10260 ctx = ctx->outer_context;
10262 if (ctx == NULL)
10263 return 0;
10265 code = OMP_CLAUSE_SHARED;
10266 /* Don't optimize shared into firstprivate for read-only vars
10267 on tasks with depend clause, we shouldn't try to copy them
10268 until the dependencies are satisfied. */
10269 if (gimplify_omp_ctxp->has_depend)
10270 flags |= GOVD_WRITTEN;
10272 else if (flags & GOVD_PRIVATE)
10273 code = OMP_CLAUSE_PRIVATE;
10274 else if (flags & GOVD_FIRSTPRIVATE)
10276 code = OMP_CLAUSE_FIRSTPRIVATE;
10277 if ((gimplify_omp_ctxp->region_type & ORT_TARGET)
10278 && (gimplify_omp_ctxp->region_type & ORT_ACC) == 0
10279 && TYPE_ATOMIC (strip_array_types (TREE_TYPE (decl))))
10281 error ("%<_Atomic%> %qD in implicit %<firstprivate%> clause on "
10282 "%<target%> construct", decl);
10283 return 0;
10286 else if (flags & GOVD_LASTPRIVATE)
10287 code = OMP_CLAUSE_LASTPRIVATE;
10288 else if (flags & (GOVD_ALIGNED | GOVD_NONTEMPORAL))
10289 return 0;
10290 else if (flags & GOVD_CONDTEMP)
10292 code = OMP_CLAUSE__CONDTEMP_;
10293 gimple_add_tmp_var (decl);
10295 else
10296 gcc_unreachable ();
10298 if (((flags & GOVD_LASTPRIVATE)
10299 || (code == OMP_CLAUSE_SHARED && (flags & GOVD_WRITTEN)))
10300 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
10301 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
10303 tree chain = *list_p;
10304 clause = build_omp_clause (input_location, code);
10305 OMP_CLAUSE_DECL (clause) = decl;
10306 OMP_CLAUSE_CHAIN (clause) = chain;
10307 if (private_debug)
10308 OMP_CLAUSE_PRIVATE_DEBUG (clause) = 1;
10309 else if (code == OMP_CLAUSE_PRIVATE && (flags & GOVD_PRIVATE_OUTER_REF))
10310 OMP_CLAUSE_PRIVATE_OUTER_REF (clause) = 1;
10311 else if (code == OMP_CLAUSE_SHARED
10312 && (flags & GOVD_WRITTEN) == 0
10313 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
10314 OMP_CLAUSE_SHARED_READONLY (clause) = 1;
10315 else if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_EXPLICIT) == 0)
10316 OMP_CLAUSE_FIRSTPRIVATE_IMPLICIT (clause) = 1;
10317 else if (code == OMP_CLAUSE_MAP && (flags & GOVD_MAP_0LEN_ARRAY) != 0)
10319 tree nc = build_omp_clause (input_location, OMP_CLAUSE_MAP);
10320 OMP_CLAUSE_DECL (nc) = decl;
10321 if (TREE_CODE (TREE_TYPE (decl)) == REFERENCE_TYPE
10322 && TREE_CODE (TREE_TYPE (TREE_TYPE (decl))) == POINTER_TYPE)
10323 OMP_CLAUSE_DECL (clause)
10324 = build_simple_mem_ref_loc (input_location, decl);
10325 OMP_CLAUSE_DECL (clause)
10326 = build2 (MEM_REF, char_type_node, OMP_CLAUSE_DECL (clause),
10327 build_int_cst (build_pointer_type (char_type_node), 0));
10328 OMP_CLAUSE_SIZE (clause) = size_zero_node;
10329 OMP_CLAUSE_SIZE (nc) = size_zero_node;
10330 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_ALLOC);
10331 OMP_CLAUSE_MAP_MAYBE_ZERO_LENGTH_ARRAY_SECTION (clause) = 1;
10332 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_POINTER);
10333 OMP_CLAUSE_CHAIN (nc) = chain;
10334 OMP_CLAUSE_CHAIN (clause) = nc;
10335 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10336 gimplify_omp_ctxp = ctx->outer_context;
10337 gimplify_expr (&TREE_OPERAND (OMP_CLAUSE_DECL (clause), 0),
10338 pre_p, NULL, is_gimple_val, fb_rvalue);
10339 gimplify_omp_ctxp = ctx;
10341 else if (code == OMP_CLAUSE_MAP)
10343 int kind;
10344 /* Not all combinations of these GOVD_MAP flags are actually valid. */
10345 switch (flags & (GOVD_MAP_TO_ONLY
10346 | GOVD_MAP_FORCE
10347 | GOVD_MAP_FORCE_PRESENT
10348 | GOVD_MAP_ALLOC_ONLY
10349 | GOVD_MAP_FROM_ONLY))
10351 case 0:
10352 kind = GOMP_MAP_TOFROM;
10353 break;
10354 case GOVD_MAP_FORCE:
10355 kind = GOMP_MAP_TOFROM | GOMP_MAP_FLAG_FORCE;
10356 break;
10357 case GOVD_MAP_TO_ONLY:
10358 kind = GOMP_MAP_TO;
10359 break;
10360 case GOVD_MAP_FROM_ONLY:
10361 kind = GOMP_MAP_FROM;
10362 break;
10363 case GOVD_MAP_ALLOC_ONLY:
10364 kind = GOMP_MAP_ALLOC;
10365 break;
10366 case GOVD_MAP_TO_ONLY | GOVD_MAP_FORCE:
10367 kind = GOMP_MAP_TO | GOMP_MAP_FLAG_FORCE;
10368 break;
10369 case GOVD_MAP_FORCE_PRESENT:
10370 kind = GOMP_MAP_FORCE_PRESENT;
10371 break;
10372 default:
10373 gcc_unreachable ();
10375 OMP_CLAUSE_SET_MAP_KIND (clause, kind);
10376 if (DECL_SIZE (decl)
10377 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
10379 tree decl2 = DECL_VALUE_EXPR (decl);
10380 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
10381 decl2 = TREE_OPERAND (decl2, 0);
10382 gcc_assert (DECL_P (decl2));
10383 tree mem = build_simple_mem_ref (decl2);
10384 OMP_CLAUSE_DECL (clause) = mem;
10385 OMP_CLAUSE_SIZE (clause) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
10386 if (gimplify_omp_ctxp->outer_context)
10388 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp->outer_context;
10389 omp_notice_variable (ctx, decl2, true);
10390 omp_notice_variable (ctx, OMP_CLAUSE_SIZE (clause), true);
10392 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
10393 OMP_CLAUSE_MAP);
10394 OMP_CLAUSE_DECL (nc) = decl;
10395 OMP_CLAUSE_SIZE (nc) = size_zero_node;
10396 if (gimplify_omp_ctxp->target_firstprivatize_array_bases)
10397 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_POINTER);
10398 else
10399 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
10400 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
10401 OMP_CLAUSE_CHAIN (clause) = nc;
10403 else if (gimplify_omp_ctxp->target_firstprivatize_array_bases
10404 && lang_hooks.decls.omp_privatize_by_reference (decl))
10406 OMP_CLAUSE_DECL (clause) = build_simple_mem_ref (decl);
10407 OMP_CLAUSE_SIZE (clause)
10408 = unshare_expr (TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (decl))));
10409 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10410 gimplify_omp_ctxp = ctx->outer_context;
10411 gimplify_expr (&OMP_CLAUSE_SIZE (clause),
10412 pre_p, NULL, is_gimple_val, fb_rvalue);
10413 gimplify_omp_ctxp = ctx;
10414 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (clause),
10415 OMP_CLAUSE_MAP);
10416 OMP_CLAUSE_DECL (nc) = decl;
10417 OMP_CLAUSE_SIZE (nc) = size_zero_node;
10418 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_FIRSTPRIVATE_REFERENCE);
10419 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (clause);
10420 OMP_CLAUSE_CHAIN (clause) = nc;
10422 else
10423 OMP_CLAUSE_SIZE (clause) = DECL_SIZE_UNIT (decl);
10425 if (code == OMP_CLAUSE_FIRSTPRIVATE && (flags & GOVD_LASTPRIVATE) != 0)
10427 tree nc = build_omp_clause (input_location, OMP_CLAUSE_LASTPRIVATE);
10428 OMP_CLAUSE_DECL (nc) = decl;
10429 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (nc) = 1;
10430 OMP_CLAUSE_CHAIN (nc) = chain;
10431 OMP_CLAUSE_CHAIN (clause) = nc;
10432 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10433 gimplify_omp_ctxp = ctx->outer_context;
10434 lang_hooks.decls.omp_finish_clause (nc, pre_p,
10435 (ctx->region_type & ORT_ACC) != 0);
10436 gimplify_omp_ctxp = ctx;
10438 *list_p = clause;
10439 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10440 gimplify_omp_ctxp = ctx->outer_context;
10441 lang_hooks.decls.omp_finish_clause (clause, pre_p,
10442 (ctx->region_type & ORT_ACC) != 0);
10443 if (gimplify_omp_ctxp)
10444 for (; clause != chain; clause = OMP_CLAUSE_CHAIN (clause))
10445 if (OMP_CLAUSE_CODE (clause) == OMP_CLAUSE_MAP
10446 && DECL_P (OMP_CLAUSE_SIZE (clause)))
10447 omp_notice_variable (gimplify_omp_ctxp, OMP_CLAUSE_SIZE (clause),
10448 true);
10449 gimplify_omp_ctxp = ctx;
10450 return 0;
10453 static void
10454 gimplify_adjust_omp_clauses (gimple_seq *pre_p, gimple_seq body, tree *list_p,
10455 enum tree_code code)
10457 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
10458 tree *orig_list_p = list_p;
10459 tree c, decl;
10460 bool has_inscan_reductions = false;
10462 if (body)
10464 struct gimplify_omp_ctx *octx;
10465 for (octx = ctx; octx; octx = octx->outer_context)
10466 if ((octx->region_type & (ORT_PARALLEL | ORT_TASK | ORT_TEAMS)) != 0)
10467 break;
10468 if (octx)
10470 struct walk_stmt_info wi;
10471 memset (&wi, 0, sizeof (wi));
10472 walk_gimple_seq (body, omp_find_stores_stmt,
10473 omp_find_stores_op, &wi);
10477 if (ctx->add_safelen1)
10479 /* If there are VLAs in the body of simd loop, prevent
10480 vectorization. */
10481 gcc_assert (ctx->region_type == ORT_SIMD);
10482 c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_SAFELEN);
10483 OMP_CLAUSE_SAFELEN_EXPR (c) = integer_one_node;
10484 OMP_CLAUSE_CHAIN (c) = *list_p;
10485 *list_p = c;
10486 list_p = &OMP_CLAUSE_CHAIN (c);
10489 if (ctx->region_type == ORT_WORKSHARE
10490 && ctx->outer_context
10491 && ctx->outer_context->region_type == ORT_COMBINED_PARALLEL)
10493 for (c = ctx->outer_context->clauses; c; c = OMP_CLAUSE_CHAIN (c))
10494 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
10495 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
10497 decl = OMP_CLAUSE_DECL (c);
10498 splay_tree_node n
10499 = splay_tree_lookup (ctx->outer_context->variables,
10500 (splay_tree_key) decl);
10501 gcc_checking_assert (!splay_tree_lookup (ctx->variables,
10502 (splay_tree_key) decl));
10503 omp_add_variable (ctx, decl, n->value);
10504 tree c2 = copy_node (c);
10505 OMP_CLAUSE_CHAIN (c2) = *list_p;
10506 *list_p = c2;
10507 if ((n->value & GOVD_FIRSTPRIVATE) == 0)
10508 continue;
10509 c2 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
10510 OMP_CLAUSE_FIRSTPRIVATE);
10511 OMP_CLAUSE_DECL (c2) = decl;
10512 OMP_CLAUSE_CHAIN (c2) = *list_p;
10513 *list_p = c2;
10516 while ((c = *list_p) != NULL)
10518 splay_tree_node n;
10519 bool remove = false;
10521 switch (OMP_CLAUSE_CODE (c))
10523 case OMP_CLAUSE_FIRSTPRIVATE:
10524 if ((ctx->region_type & ORT_TARGET)
10525 && (ctx->region_type & ORT_ACC) == 0
10526 && TYPE_ATOMIC (strip_array_types
10527 (TREE_TYPE (OMP_CLAUSE_DECL (c)))))
10529 error_at (OMP_CLAUSE_LOCATION (c),
10530 "%<_Atomic%> %qD in %<firstprivate%> clause on "
10531 "%<target%> construct", OMP_CLAUSE_DECL (c));
10532 remove = true;
10533 break;
10535 /* FALLTHRU */
10536 case OMP_CLAUSE_PRIVATE:
10537 case OMP_CLAUSE_SHARED:
10538 case OMP_CLAUSE_LINEAR:
10539 decl = OMP_CLAUSE_DECL (c);
10540 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10541 remove = !(n->value & GOVD_SEEN);
10542 if ((n->value & GOVD_LASTPRIVATE_CONDITIONAL) != 0
10543 && code == OMP_PARALLEL
10544 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_FIRSTPRIVATE)
10545 remove = true;
10546 if (! remove)
10548 bool shared = OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED;
10549 if ((n->value & GOVD_DEBUG_PRIVATE)
10550 || lang_hooks.decls.omp_private_debug_clause (decl, shared))
10552 gcc_assert ((n->value & GOVD_DEBUG_PRIVATE) == 0
10553 || ((n->value & GOVD_DATA_SHARE_CLASS)
10554 == GOVD_SHARED));
10555 OMP_CLAUSE_SET_CODE (c, OMP_CLAUSE_PRIVATE);
10556 OMP_CLAUSE_PRIVATE_DEBUG (c) = 1;
10558 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
10559 && ctx->has_depend
10560 && DECL_P (decl))
10561 n->value |= GOVD_WRITTEN;
10562 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
10563 && (n->value & GOVD_WRITTEN) == 0
10564 && DECL_P (decl)
10565 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
10566 OMP_CLAUSE_SHARED_READONLY (c) = 1;
10567 else if (DECL_P (decl)
10568 && ((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_SHARED
10569 && (n->value & GOVD_WRITTEN) != 0)
10570 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
10571 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)))
10572 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
10573 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
10575 else
10576 n->value &= ~GOVD_EXPLICIT;
10577 break;
10579 case OMP_CLAUSE_LASTPRIVATE:
10580 /* Make sure OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE is set to
10581 accurately reflect the presence of a FIRSTPRIVATE clause. */
10582 decl = OMP_CLAUSE_DECL (c);
10583 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10584 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c)
10585 = (n->value & GOVD_FIRSTPRIVATE) != 0;
10586 if (code == OMP_DISTRIBUTE
10587 && OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
10589 remove = true;
10590 error_at (OMP_CLAUSE_LOCATION (c),
10591 "same variable used in %<firstprivate%> and "
10592 "%<lastprivate%> clauses on %<distribute%> "
10593 "construct");
10595 if (!remove
10596 && OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
10597 && DECL_P (decl)
10598 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
10599 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
10600 if (OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c) && code == OMP_PARALLEL)
10601 remove = true;
10602 break;
10604 case OMP_CLAUSE_ALIGNED:
10605 decl = OMP_CLAUSE_DECL (c);
10606 if (!is_global_var (decl))
10608 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10609 remove = n == NULL || !(n->value & GOVD_SEEN);
10610 if (!remove && TREE_CODE (TREE_TYPE (decl)) == POINTER_TYPE)
10612 struct gimplify_omp_ctx *octx;
10613 if (n != NULL
10614 && (n->value & (GOVD_DATA_SHARE_CLASS
10615 & ~GOVD_FIRSTPRIVATE)))
10616 remove = true;
10617 else
10618 for (octx = ctx->outer_context; octx;
10619 octx = octx->outer_context)
10621 n = splay_tree_lookup (octx->variables,
10622 (splay_tree_key) decl);
10623 if (n == NULL)
10624 continue;
10625 if (n->value & GOVD_LOCAL)
10626 break;
10627 /* We have to avoid assigning a shared variable
10628 to itself when trying to add
10629 __builtin_assume_aligned. */
10630 if (n->value & GOVD_SHARED)
10632 remove = true;
10633 break;
10638 else if (TREE_CODE (TREE_TYPE (decl)) == ARRAY_TYPE)
10640 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10641 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
10642 remove = true;
10644 break;
10646 case OMP_CLAUSE_NONTEMPORAL:
10647 decl = OMP_CLAUSE_DECL (c);
10648 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10649 remove = n == NULL || !(n->value & GOVD_SEEN);
10650 break;
10652 case OMP_CLAUSE_MAP:
10653 if (code == OMP_TARGET_EXIT_DATA
10654 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_ALWAYS_POINTER)
10656 remove = true;
10657 break;
10659 decl = OMP_CLAUSE_DECL (c);
10660 /* Data clauses associated with reductions must be
10661 compatible with present_or_copy. Warn and adjust the clause
10662 if that is not the case. */
10663 if (ctx->region_type == ORT_ACC_PARALLEL
10664 || ctx->region_type == ORT_ACC_SERIAL)
10666 tree t = DECL_P (decl) ? decl : TREE_OPERAND (decl, 0);
10667 n = NULL;
10669 if (DECL_P (t))
10670 n = splay_tree_lookup (ctx->variables, (splay_tree_key) t);
10672 if (n && (n->value & GOVD_REDUCTION))
10674 enum gomp_map_kind kind = OMP_CLAUSE_MAP_KIND (c);
10676 OMP_CLAUSE_MAP_IN_REDUCTION (c) = 1;
10677 if ((kind & GOMP_MAP_TOFROM) != GOMP_MAP_TOFROM
10678 && kind != GOMP_MAP_FORCE_PRESENT
10679 && kind != GOMP_MAP_POINTER)
10681 warning_at (OMP_CLAUSE_LOCATION (c), 0,
10682 "incompatible data clause with reduction "
10683 "on %qE; promoting to %<present_or_copy%>",
10684 DECL_NAME (t));
10685 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_TOFROM);
10689 if (!DECL_P (decl))
10691 if ((ctx->region_type & ORT_TARGET) != 0
10692 && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_FIRSTPRIVATE_POINTER)
10694 if (TREE_CODE (decl) == INDIRECT_REF
10695 && TREE_CODE (TREE_OPERAND (decl, 0)) == COMPONENT_REF
10696 && (TREE_CODE (TREE_TYPE (TREE_OPERAND (decl, 0)))
10697 == REFERENCE_TYPE))
10698 decl = TREE_OPERAND (decl, 0);
10699 if (TREE_CODE (decl) == COMPONENT_REF)
10701 while (TREE_CODE (decl) == COMPONENT_REF)
10702 decl = TREE_OPERAND (decl, 0);
10703 if (DECL_P (decl))
10705 n = splay_tree_lookup (ctx->variables,
10706 (splay_tree_key) decl);
10707 if (!(n->value & GOVD_SEEN))
10708 remove = true;
10712 break;
10714 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10715 if ((ctx->region_type & ORT_TARGET) != 0
10716 && !(n->value & GOVD_SEEN)
10717 && GOMP_MAP_ALWAYS_P (OMP_CLAUSE_MAP_KIND (c)) == 0
10718 && (!is_global_var (decl)
10719 || !lookup_attribute ("omp declare target link",
10720 DECL_ATTRIBUTES (decl))))
10722 remove = true;
10723 /* For struct element mapping, if struct is never referenced
10724 in target block and none of the mapping has always modifier,
10725 remove all the struct element mappings, which immediately
10726 follow the GOMP_MAP_STRUCT map clause. */
10727 if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT)
10729 HOST_WIDE_INT cnt = tree_to_shwi (OMP_CLAUSE_SIZE (c));
10730 while (cnt--)
10731 OMP_CLAUSE_CHAIN (c)
10732 = OMP_CLAUSE_CHAIN (OMP_CLAUSE_CHAIN (c));
10735 else if (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_STRUCT
10736 && (code == OMP_TARGET_EXIT_DATA
10737 || code == OACC_EXIT_DATA))
10738 remove = true;
10739 else if (DECL_SIZE (decl)
10740 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST
10741 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_POINTER
10742 && OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FIRSTPRIVATE_POINTER
10743 && (OMP_CLAUSE_MAP_KIND (c)
10744 != GOMP_MAP_FIRSTPRIVATE_REFERENCE))
10746 /* For GOMP_MAP_FORCE_DEVICEPTR, we'll never enter here, because
10747 for these, TREE_CODE (DECL_SIZE (decl)) will always be
10748 INTEGER_CST. */
10749 gcc_assert (OMP_CLAUSE_MAP_KIND (c) != GOMP_MAP_FORCE_DEVICEPTR);
10751 tree decl2 = DECL_VALUE_EXPR (decl);
10752 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
10753 decl2 = TREE_OPERAND (decl2, 0);
10754 gcc_assert (DECL_P (decl2));
10755 tree mem = build_simple_mem_ref (decl2);
10756 OMP_CLAUSE_DECL (c) = mem;
10757 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
10758 if (ctx->outer_context)
10760 omp_notice_variable (ctx->outer_context, decl2, true);
10761 omp_notice_variable (ctx->outer_context,
10762 OMP_CLAUSE_SIZE (c), true);
10764 if (((ctx->region_type & ORT_TARGET) != 0
10765 || !ctx->target_firstprivatize_array_bases)
10766 && ((n->value & GOVD_SEEN) == 0
10767 || (n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE)) == 0))
10769 tree nc = build_omp_clause (OMP_CLAUSE_LOCATION (c),
10770 OMP_CLAUSE_MAP);
10771 OMP_CLAUSE_DECL (nc) = decl;
10772 OMP_CLAUSE_SIZE (nc) = size_zero_node;
10773 if (ctx->target_firstprivatize_array_bases)
10774 OMP_CLAUSE_SET_MAP_KIND (nc,
10775 GOMP_MAP_FIRSTPRIVATE_POINTER);
10776 else
10777 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_POINTER);
10778 OMP_CLAUSE_CHAIN (nc) = OMP_CLAUSE_CHAIN (c);
10779 OMP_CLAUSE_CHAIN (c) = nc;
10780 c = nc;
10783 else
10785 if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
10786 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
10787 gcc_assert ((n->value & GOVD_SEEN) == 0
10788 || ((n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE))
10789 == 0));
10791 break;
10793 case OMP_CLAUSE_TO:
10794 case OMP_CLAUSE_FROM:
10795 case OMP_CLAUSE__CACHE_:
10796 decl = OMP_CLAUSE_DECL (c);
10797 if (!DECL_P (decl))
10798 break;
10799 if (DECL_SIZE (decl)
10800 && TREE_CODE (DECL_SIZE (decl)) != INTEGER_CST)
10802 tree decl2 = DECL_VALUE_EXPR (decl);
10803 gcc_assert (TREE_CODE (decl2) == INDIRECT_REF);
10804 decl2 = TREE_OPERAND (decl2, 0);
10805 gcc_assert (DECL_P (decl2));
10806 tree mem = build_simple_mem_ref (decl2);
10807 OMP_CLAUSE_DECL (c) = mem;
10808 OMP_CLAUSE_SIZE (c) = TYPE_SIZE_UNIT (TREE_TYPE (decl));
10809 if (ctx->outer_context)
10811 omp_notice_variable (ctx->outer_context, decl2, true);
10812 omp_notice_variable (ctx->outer_context,
10813 OMP_CLAUSE_SIZE (c), true);
10816 else if (OMP_CLAUSE_SIZE (c) == NULL_TREE)
10817 OMP_CLAUSE_SIZE (c) = DECL_SIZE_UNIT (decl);
10818 break;
10820 case OMP_CLAUSE_REDUCTION:
10821 if (OMP_CLAUSE_REDUCTION_INSCAN (c))
10823 decl = OMP_CLAUSE_DECL (c);
10824 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10825 if ((n->value & GOVD_REDUCTION_INSCAN) == 0)
10827 remove = true;
10828 error_at (OMP_CLAUSE_LOCATION (c),
10829 "%qD specified in %<inscan%> %<reduction%> clause "
10830 "but not in %<scan%> directive clause", decl);
10831 break;
10833 has_inscan_reductions = true;
10835 /* FALLTHRU */
10836 case OMP_CLAUSE_IN_REDUCTION:
10837 case OMP_CLAUSE_TASK_REDUCTION:
10838 decl = OMP_CLAUSE_DECL (c);
10839 /* OpenACC reductions need a present_or_copy data clause.
10840 Add one if necessary. Emit error when the reduction is private. */
10841 if (ctx->region_type == ORT_ACC_PARALLEL
10842 || ctx->region_type == ORT_ACC_SERIAL)
10844 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10845 if (n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE))
10847 remove = true;
10848 error_at (OMP_CLAUSE_LOCATION (c), "invalid private "
10849 "reduction on %qE", DECL_NAME (decl));
10851 else if ((n->value & GOVD_MAP) == 0)
10853 tree next = OMP_CLAUSE_CHAIN (c);
10854 tree nc = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_MAP);
10855 OMP_CLAUSE_SET_MAP_KIND (nc, GOMP_MAP_TOFROM);
10856 OMP_CLAUSE_DECL (nc) = decl;
10857 OMP_CLAUSE_CHAIN (c) = nc;
10858 lang_hooks.decls.omp_finish_clause (nc, pre_p,
10859 (ctx->region_type
10860 & ORT_ACC) != 0);
10861 while (1)
10863 OMP_CLAUSE_MAP_IN_REDUCTION (nc) = 1;
10864 if (OMP_CLAUSE_CHAIN (nc) == NULL)
10865 break;
10866 nc = OMP_CLAUSE_CHAIN (nc);
10868 OMP_CLAUSE_CHAIN (nc) = next;
10869 n->value |= GOVD_MAP;
10872 if (DECL_P (decl)
10873 && omp_shared_to_firstprivate_optimizable_decl_p (decl))
10874 omp_mark_stores (gimplify_omp_ctxp->outer_context, decl);
10875 break;
10877 case OMP_CLAUSE_ALLOCATE:
10878 decl = OMP_CLAUSE_DECL (c);
10879 n = splay_tree_lookup (ctx->variables, (splay_tree_key) decl);
10880 if (n != NULL && !(n->value & GOVD_SEEN))
10882 if ((n->value & (GOVD_PRIVATE | GOVD_FIRSTPRIVATE | GOVD_LINEAR))
10883 != 0
10884 && (n->value & (GOVD_REDUCTION | GOVD_LASTPRIVATE)) == 0)
10885 remove = true;
10887 if (!remove
10888 && OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
10889 && TREE_CODE (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)) != INTEGER_CST
10890 && ((ctx->region_type & (ORT_PARALLEL | ORT_TARGET)) != 0
10891 || (ctx->region_type & ORT_TASKLOOP) == ORT_TASK
10892 || (ctx->region_type & ORT_HOST_TEAMS) == ORT_HOST_TEAMS))
10894 tree allocator = OMP_CLAUSE_ALLOCATE_ALLOCATOR (c);
10895 n = splay_tree_lookup (ctx->variables, (splay_tree_key) allocator);
10896 if (n == NULL)
10898 enum omp_clause_default_kind default_kind
10899 = ctx->default_kind;
10900 ctx->default_kind = OMP_CLAUSE_DEFAULT_FIRSTPRIVATE;
10901 omp_notice_variable (ctx, OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
10902 true);
10903 ctx->default_kind = default_kind;
10905 else
10906 omp_notice_variable (ctx, OMP_CLAUSE_ALLOCATE_ALLOCATOR (c),
10907 true);
10909 break;
10911 case OMP_CLAUSE_COPYIN:
10912 case OMP_CLAUSE_COPYPRIVATE:
10913 case OMP_CLAUSE_IF:
10914 case OMP_CLAUSE_NUM_THREADS:
10915 case OMP_CLAUSE_NUM_TEAMS:
10916 case OMP_CLAUSE_THREAD_LIMIT:
10917 case OMP_CLAUSE_DIST_SCHEDULE:
10918 case OMP_CLAUSE_DEVICE:
10919 case OMP_CLAUSE_SCHEDULE:
10920 case OMP_CLAUSE_NOWAIT:
10921 case OMP_CLAUSE_ORDERED:
10922 case OMP_CLAUSE_DEFAULT:
10923 case OMP_CLAUSE_UNTIED:
10924 case OMP_CLAUSE_COLLAPSE:
10925 case OMP_CLAUSE_FINAL:
10926 case OMP_CLAUSE_MERGEABLE:
10927 case OMP_CLAUSE_PROC_BIND:
10928 case OMP_CLAUSE_SAFELEN:
10929 case OMP_CLAUSE_SIMDLEN:
10930 case OMP_CLAUSE_DEPEND:
10931 case OMP_CLAUSE_PRIORITY:
10932 case OMP_CLAUSE_GRAINSIZE:
10933 case OMP_CLAUSE_NUM_TASKS:
10934 case OMP_CLAUSE_NOGROUP:
10935 case OMP_CLAUSE_THREADS:
10936 case OMP_CLAUSE_SIMD:
10937 case OMP_CLAUSE_HINT:
10938 case OMP_CLAUSE_DEFAULTMAP:
10939 case OMP_CLAUSE_ORDER:
10940 case OMP_CLAUSE_BIND:
10941 case OMP_CLAUSE_DETACH:
10942 case OMP_CLAUSE_USE_DEVICE_PTR:
10943 case OMP_CLAUSE_USE_DEVICE_ADDR:
10944 case OMP_CLAUSE_IS_DEVICE_PTR:
10945 case OMP_CLAUSE_ASYNC:
10946 case OMP_CLAUSE_WAIT:
10947 case OMP_CLAUSE_INDEPENDENT:
10948 case OMP_CLAUSE_NUM_GANGS:
10949 case OMP_CLAUSE_NUM_WORKERS:
10950 case OMP_CLAUSE_VECTOR_LENGTH:
10951 case OMP_CLAUSE_GANG:
10952 case OMP_CLAUSE_WORKER:
10953 case OMP_CLAUSE_VECTOR:
10954 case OMP_CLAUSE_AUTO:
10955 case OMP_CLAUSE_SEQ:
10956 case OMP_CLAUSE_TILE:
10957 case OMP_CLAUSE_IF_PRESENT:
10958 case OMP_CLAUSE_FINALIZE:
10959 case OMP_CLAUSE_INCLUSIVE:
10960 case OMP_CLAUSE_EXCLUSIVE:
10961 break;
10963 default:
10964 gcc_unreachable ();
10967 if (remove)
10968 *list_p = OMP_CLAUSE_CHAIN (c);
10969 else
10970 list_p = &OMP_CLAUSE_CHAIN (c);
10973 /* Add in any implicit data sharing. */
10974 struct gimplify_adjust_omp_clauses_data data;
10975 data.list_p = list_p;
10976 data.pre_p = pre_p;
10977 splay_tree_foreach (ctx->variables, gimplify_adjust_omp_clauses_1, &data);
10979 if (has_inscan_reductions)
10980 for (c = *orig_list_p; c; c = OMP_CLAUSE_CHAIN (c))
10981 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
10982 && !OMP_CLAUSE_LINEAR_NO_COPYIN (c))
10984 error_at (OMP_CLAUSE_LOCATION (c),
10985 "%<inscan%> %<reduction%> clause used together with "
10986 "%<linear%> clause for a variable other than loop "
10987 "iterator");
10988 break;
10991 gimplify_omp_ctxp = ctx->outer_context;
10992 delete_omp_context (ctx);
10995 /* Return 0 if CONSTRUCTS selectors don't match the OpenMP context,
10996 -1 if unknown yet (simd is involved, won't be known until vectorization)
10997 and 1 if they do. If SCORES is non-NULL, it should point to an array
10998 of at least 2*NCONSTRUCTS+2 ints, and will be filled with the positions
10999 of the CONSTRUCTS (position -1 if it will never match) followed by
11000 number of constructs in the OpenMP context construct trait. If the
11001 score depends on whether it will be in a declare simd clone or not,
11002 the function returns 2 and there will be two sets of the scores, the first
11003 one for the case that it is not in a declare simd clone, the other
11004 that it is in a declare simd clone. */
11007 omp_construct_selector_matches (enum tree_code *constructs, int nconstructs,
11008 int *scores)
11010 int matched = 0, cnt = 0;
11011 bool simd_seen = false;
11012 bool target_seen = false;
11013 int declare_simd_cnt = -1;
11014 auto_vec<enum tree_code, 16> codes;
11015 for (struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp; ctx;)
11017 if (((ctx->region_type & ORT_PARALLEL) && ctx->code == OMP_PARALLEL)
11018 || ((ctx->region_type & (ORT_TARGET | ORT_IMPLICIT_TARGET | ORT_ACC))
11019 == ORT_TARGET && ctx->code == OMP_TARGET)
11020 || ((ctx->region_type & ORT_TEAMS) && ctx->code == OMP_TEAMS)
11021 || (ctx->region_type == ORT_WORKSHARE && ctx->code == OMP_FOR)
11022 || (ctx->region_type == ORT_SIMD
11023 && ctx->code == OMP_SIMD
11024 && !omp_find_clause (ctx->clauses, OMP_CLAUSE_BIND)))
11026 ++cnt;
11027 if (scores)
11028 codes.safe_push (ctx->code);
11029 else if (matched < nconstructs && ctx->code == constructs[matched])
11031 if (ctx->code == OMP_SIMD)
11033 if (matched)
11034 return 0;
11035 simd_seen = true;
11037 ++matched;
11039 if (ctx->code == OMP_TARGET)
11041 if (scores == NULL)
11042 return matched < nconstructs ? 0 : simd_seen ? -1 : 1;
11043 target_seen = true;
11044 break;
11047 else if (ctx->region_type == ORT_WORKSHARE
11048 && ctx->code == OMP_LOOP
11049 && ctx->outer_context
11050 && ctx->outer_context->region_type == ORT_COMBINED_PARALLEL
11051 && ctx->outer_context->outer_context
11052 && ctx->outer_context->outer_context->code == OMP_LOOP
11053 && ctx->outer_context->outer_context->distribute)
11054 ctx = ctx->outer_context->outer_context;
11055 ctx = ctx->outer_context;
11057 if (!target_seen
11058 && lookup_attribute ("omp declare simd",
11059 DECL_ATTRIBUTES (current_function_decl)))
11061 /* Declare simd is a maybe case, it is supposed to be added only to the
11062 omp-simd-clone.c added clones and not to the base function. */
11063 declare_simd_cnt = cnt++;
11064 if (scores)
11065 codes.safe_push (OMP_SIMD);
11066 else if (cnt == 0
11067 && constructs[0] == OMP_SIMD)
11069 gcc_assert (matched == 0);
11070 simd_seen = true;
11071 if (++matched == nconstructs)
11072 return -1;
11075 if (tree attr = lookup_attribute ("omp declare variant variant",
11076 DECL_ATTRIBUTES (current_function_decl)))
11078 enum tree_code variant_constructs[5];
11079 int variant_nconstructs = 0;
11080 if (!target_seen)
11081 variant_nconstructs
11082 = omp_constructor_traits_to_codes (TREE_VALUE (attr),
11083 variant_constructs);
11084 for (int i = 0; i < variant_nconstructs; i++)
11086 ++cnt;
11087 if (scores)
11088 codes.safe_push (variant_constructs[i]);
11089 else if (matched < nconstructs
11090 && variant_constructs[i] == constructs[matched])
11092 if (variant_constructs[i] == OMP_SIMD)
11094 if (matched)
11095 return 0;
11096 simd_seen = true;
11098 ++matched;
11102 if (!target_seen
11103 && lookup_attribute ("omp declare target block",
11104 DECL_ATTRIBUTES (current_function_decl)))
11106 if (scores)
11107 codes.safe_push (OMP_TARGET);
11108 else if (matched < nconstructs && constructs[matched] == OMP_TARGET)
11109 ++matched;
11111 if (scores)
11113 for (int pass = 0; pass < (declare_simd_cnt == -1 ? 1 : 2); pass++)
11115 int j = codes.length () - 1;
11116 for (int i = nconstructs - 1; i >= 0; i--)
11118 while (j >= 0
11119 && (pass != 0 || declare_simd_cnt != j)
11120 && constructs[i] != codes[j])
11121 --j;
11122 if (pass == 0 && declare_simd_cnt != -1 && j > declare_simd_cnt)
11123 *scores++ = j - 1;
11124 else
11125 *scores++ = j;
11127 *scores++ = ((pass == 0 && declare_simd_cnt != -1)
11128 ? codes.length () - 1 : codes.length ());
11130 return declare_simd_cnt == -1 ? 1 : 2;
11132 if (matched == nconstructs)
11133 return simd_seen ? -1 : 1;
11134 return 0;
11137 /* Gimplify OACC_CACHE. */
11139 static void
11140 gimplify_oacc_cache (tree *expr_p, gimple_seq *pre_p)
11142 tree expr = *expr_p;
11144 gimplify_scan_omp_clauses (&OACC_CACHE_CLAUSES (expr), pre_p, ORT_ACC,
11145 OACC_CACHE);
11146 gimplify_adjust_omp_clauses (pre_p, NULL, &OACC_CACHE_CLAUSES (expr),
11147 OACC_CACHE);
11149 /* TODO: Do something sensible with this information. */
11151 *expr_p = NULL_TREE;
11154 /* Helper function of gimplify_oacc_declare. The helper's purpose is to,
11155 if required, translate 'kind' in CLAUSE into an 'entry' kind and 'exit'
11156 kind. The entry kind will replace the one in CLAUSE, while the exit
11157 kind will be used in a new omp_clause and returned to the caller. */
11159 static tree
11160 gimplify_oacc_declare_1 (tree clause)
11162 HOST_WIDE_INT kind, new_op;
11163 bool ret = false;
11164 tree c = NULL;
11166 kind = OMP_CLAUSE_MAP_KIND (clause);
11168 switch (kind)
11170 case GOMP_MAP_ALLOC:
11171 new_op = GOMP_MAP_RELEASE;
11172 ret = true;
11173 break;
11175 case GOMP_MAP_FROM:
11176 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_FORCE_ALLOC);
11177 new_op = GOMP_MAP_FROM;
11178 ret = true;
11179 break;
11181 case GOMP_MAP_TOFROM:
11182 OMP_CLAUSE_SET_MAP_KIND (clause, GOMP_MAP_TO);
11183 new_op = GOMP_MAP_FROM;
11184 ret = true;
11185 break;
11187 case GOMP_MAP_DEVICE_RESIDENT:
11188 case GOMP_MAP_FORCE_DEVICEPTR:
11189 case GOMP_MAP_FORCE_PRESENT:
11190 case GOMP_MAP_LINK:
11191 case GOMP_MAP_POINTER:
11192 case GOMP_MAP_TO:
11193 break;
11195 default:
11196 gcc_unreachable ();
11197 break;
11200 if (ret)
11202 c = build_omp_clause (OMP_CLAUSE_LOCATION (clause), OMP_CLAUSE_MAP);
11203 OMP_CLAUSE_SET_MAP_KIND (c, new_op);
11204 OMP_CLAUSE_DECL (c) = OMP_CLAUSE_DECL (clause);
11207 return c;
11210 /* Gimplify OACC_DECLARE. */
11212 static void
11213 gimplify_oacc_declare (tree *expr_p, gimple_seq *pre_p)
11215 tree expr = *expr_p;
11216 gomp_target *stmt;
11217 tree clauses, t, decl;
11219 clauses = OACC_DECLARE_CLAUSES (expr);
11221 gimplify_scan_omp_clauses (&clauses, pre_p, ORT_TARGET_DATA, OACC_DECLARE);
11222 gimplify_adjust_omp_clauses (pre_p, NULL, &clauses, OACC_DECLARE);
11224 for (t = clauses; t; t = OMP_CLAUSE_CHAIN (t))
11226 decl = OMP_CLAUSE_DECL (t);
11228 if (TREE_CODE (decl) == MEM_REF)
11229 decl = TREE_OPERAND (decl, 0);
11231 if (VAR_P (decl) && !is_oacc_declared (decl))
11233 tree attr = get_identifier ("oacc declare target");
11234 DECL_ATTRIBUTES (decl) = tree_cons (attr, NULL_TREE,
11235 DECL_ATTRIBUTES (decl));
11238 if (VAR_P (decl)
11239 && !is_global_var (decl)
11240 && DECL_CONTEXT (decl) == current_function_decl)
11242 tree c = gimplify_oacc_declare_1 (t);
11243 if (c)
11245 if (oacc_declare_returns == NULL)
11246 oacc_declare_returns = new hash_map<tree, tree>;
11248 oacc_declare_returns->put (decl, c);
11252 if (gimplify_omp_ctxp)
11253 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_SEEN);
11256 stmt = gimple_build_omp_target (NULL, GF_OMP_TARGET_KIND_OACC_DECLARE,
11257 clauses);
11259 gimplify_seq_add_stmt (pre_p, stmt);
11261 *expr_p = NULL_TREE;
11264 /* Gimplify the contents of an OMP_PARALLEL statement. This involves
11265 gimplification of the body, as well as scanning the body for used
11266 variables. We need to do this scan now, because variable-sized
11267 decls will be decomposed during gimplification. */
11269 static void
11270 gimplify_omp_parallel (tree *expr_p, gimple_seq *pre_p)
11272 tree expr = *expr_p;
11273 gimple *g;
11274 gimple_seq body = NULL;
11276 gimplify_scan_omp_clauses (&OMP_PARALLEL_CLAUSES (expr), pre_p,
11277 OMP_PARALLEL_COMBINED (expr)
11278 ? ORT_COMBINED_PARALLEL
11279 : ORT_PARALLEL, OMP_PARALLEL);
11281 push_gimplify_context ();
11283 g = gimplify_and_return_first (OMP_PARALLEL_BODY (expr), &body);
11284 if (gimple_code (g) == GIMPLE_BIND)
11285 pop_gimplify_context (g);
11286 else
11287 pop_gimplify_context (NULL);
11289 gimplify_adjust_omp_clauses (pre_p, body, &OMP_PARALLEL_CLAUSES (expr),
11290 OMP_PARALLEL);
11292 g = gimple_build_omp_parallel (body,
11293 OMP_PARALLEL_CLAUSES (expr),
11294 NULL_TREE, NULL_TREE);
11295 if (OMP_PARALLEL_COMBINED (expr))
11296 gimple_omp_set_subcode (g, GF_OMP_PARALLEL_COMBINED);
11297 gimplify_seq_add_stmt (pre_p, g);
11298 *expr_p = NULL_TREE;
11301 /* Gimplify the contents of an OMP_TASK statement. This involves
11302 gimplification of the body, as well as scanning the body for used
11303 variables. We need to do this scan now, because variable-sized
11304 decls will be decomposed during gimplification. */
11306 static void
11307 gimplify_omp_task (tree *expr_p, gimple_seq *pre_p)
11309 tree expr = *expr_p;
11310 gimple *g;
11311 gimple_seq body = NULL;
11313 if (OMP_TASK_BODY (expr) == NULL_TREE)
11314 for (tree c = OMP_TASK_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
11315 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
11316 && OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_MUTEXINOUTSET)
11318 error_at (OMP_CLAUSE_LOCATION (c),
11319 "%<mutexinoutset%> kind in %<depend%> clause on a "
11320 "%<taskwait%> construct");
11321 break;
11324 gimplify_scan_omp_clauses (&OMP_TASK_CLAUSES (expr), pre_p,
11325 omp_find_clause (OMP_TASK_CLAUSES (expr),
11326 OMP_CLAUSE_UNTIED)
11327 ? ORT_UNTIED_TASK : ORT_TASK, OMP_TASK);
11329 if (OMP_TASK_BODY (expr))
11331 push_gimplify_context ();
11333 g = gimplify_and_return_first (OMP_TASK_BODY (expr), &body);
11334 if (gimple_code (g) == GIMPLE_BIND)
11335 pop_gimplify_context (g);
11336 else
11337 pop_gimplify_context (NULL);
11340 gimplify_adjust_omp_clauses (pre_p, body, &OMP_TASK_CLAUSES (expr),
11341 OMP_TASK);
11343 g = gimple_build_omp_task (body,
11344 OMP_TASK_CLAUSES (expr),
11345 NULL_TREE, NULL_TREE,
11346 NULL_TREE, NULL_TREE, NULL_TREE);
11347 if (OMP_TASK_BODY (expr) == NULL_TREE)
11348 gimple_omp_task_set_taskwait_p (g, true);
11349 gimplify_seq_add_stmt (pre_p, g);
11350 *expr_p = NULL_TREE;
11353 /* Helper function for gimplify_omp_for. If *TP is not a gimple constant,
11354 force it into a temporary initialized in PRE_P and add firstprivate clause
11355 to ORIG_FOR_STMT. */
11357 static void
11358 gimplify_omp_taskloop_expr (tree type, tree *tp, gimple_seq *pre_p,
11359 tree orig_for_stmt)
11361 if (*tp == NULL || is_gimple_constant (*tp))
11362 return;
11364 *tp = get_initialized_tmp_var (*tp, pre_p, NULL, false);
11365 /* Reference to pointer conversion is considered useless,
11366 but is significant for firstprivate clause. Force it
11367 here. */
11368 if (type
11369 && TREE_CODE (type) == POINTER_TYPE
11370 && TREE_CODE (TREE_TYPE (*tp)) == REFERENCE_TYPE)
11372 tree v = create_tmp_var (TYPE_MAIN_VARIANT (type));
11373 tree m = build2 (INIT_EXPR, TREE_TYPE (v), v, *tp);
11374 gimplify_and_add (m, pre_p);
11375 *tp = v;
11378 tree c = build_omp_clause (input_location, OMP_CLAUSE_FIRSTPRIVATE);
11379 OMP_CLAUSE_DECL (c) = *tp;
11380 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (orig_for_stmt);
11381 OMP_FOR_CLAUSES (orig_for_stmt) = c;
11384 /* Gimplify the gross structure of an OMP_FOR statement. */
11386 static enum gimplify_status
11387 gimplify_omp_for (tree *expr_p, gimple_seq *pre_p)
11389 tree for_stmt, orig_for_stmt, inner_for_stmt = NULL_TREE, decl, var, t;
11390 enum gimplify_status ret = GS_ALL_DONE;
11391 enum gimplify_status tret;
11392 gomp_for *gfor;
11393 gimple_seq for_body, for_pre_body;
11394 int i;
11395 bitmap has_decl_expr = NULL;
11396 enum omp_region_type ort = ORT_WORKSHARE;
11397 bool openacc = TREE_CODE (*expr_p) == OACC_LOOP;
11399 orig_for_stmt = for_stmt = *expr_p;
11401 bool loop_p = (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_BIND)
11402 != NULL_TREE);
11403 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
11405 tree *data[4] = { NULL, NULL, NULL, NULL };
11406 gcc_assert (TREE_CODE (for_stmt) != OACC_LOOP);
11407 inner_for_stmt = walk_tree (&OMP_FOR_BODY (for_stmt),
11408 find_combined_omp_for, data, NULL);
11409 if (inner_for_stmt == NULL_TREE)
11411 gcc_assert (seen_error ());
11412 *expr_p = NULL_TREE;
11413 return GS_ERROR;
11415 if (data[2] && OMP_FOR_PRE_BODY (*data[2]))
11417 append_to_statement_list_force (OMP_FOR_PRE_BODY (*data[2]),
11418 &OMP_FOR_PRE_BODY (for_stmt));
11419 OMP_FOR_PRE_BODY (*data[2]) = NULL_TREE;
11421 if (OMP_FOR_PRE_BODY (inner_for_stmt))
11423 append_to_statement_list_force (OMP_FOR_PRE_BODY (inner_for_stmt),
11424 &OMP_FOR_PRE_BODY (for_stmt));
11425 OMP_FOR_PRE_BODY (inner_for_stmt) = NULL_TREE;
11428 if (data[0])
11430 /* We have some statements or variable declarations in between
11431 the composite construct directives. Move them around the
11432 inner_for_stmt. */
11433 data[0] = expr_p;
11434 for (i = 0; i < 3; i++)
11435 if (data[i])
11437 tree t = *data[i];
11438 if (i < 2 && data[i + 1] == &OMP_BODY (t))
11439 data[i + 1] = data[i];
11440 *data[i] = OMP_BODY (t);
11441 tree body = build3 (BIND_EXPR, void_type_node, NULL_TREE,
11442 NULL_TREE, make_node (BLOCK));
11443 OMP_BODY (t) = body;
11444 append_to_statement_list_force (inner_for_stmt,
11445 &BIND_EXPR_BODY (body));
11446 *data[3] = t;
11447 data[3] = tsi_stmt_ptr (tsi_start (BIND_EXPR_BODY (body)));
11448 gcc_assert (*data[3] == inner_for_stmt);
11450 return GS_OK;
11453 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (inner_for_stmt)); i++)
11454 if (!loop_p
11455 && OMP_FOR_ORIG_DECLS (inner_for_stmt)
11456 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
11457 i)) == TREE_LIST
11458 && TREE_PURPOSE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
11459 i)))
11461 tree orig = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt), i);
11462 /* Class iterators aren't allowed on OMP_SIMD, so the only
11463 case we need to solve is distribute parallel for. They are
11464 allowed on the loop construct, but that is already handled
11465 in gimplify_omp_loop. */
11466 gcc_assert (TREE_CODE (inner_for_stmt) == OMP_FOR
11467 && TREE_CODE (for_stmt) == OMP_DISTRIBUTE
11468 && data[1]);
11469 tree orig_decl = TREE_PURPOSE (orig);
11470 tree last = TREE_VALUE (orig);
11471 tree *pc;
11472 for (pc = &OMP_FOR_CLAUSES (inner_for_stmt);
11473 *pc; pc = &OMP_CLAUSE_CHAIN (*pc))
11474 if ((OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_PRIVATE
11475 || OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_LASTPRIVATE)
11476 && OMP_CLAUSE_DECL (*pc) == orig_decl)
11477 break;
11478 if (*pc == NULL_TREE)
11480 tree *spc;
11481 for (spc = &OMP_PARALLEL_CLAUSES (*data[1]);
11482 *spc; spc = &OMP_CLAUSE_CHAIN (*spc))
11483 if (OMP_CLAUSE_CODE (*spc) == OMP_CLAUSE_PRIVATE
11484 && OMP_CLAUSE_DECL (*spc) == orig_decl)
11485 break;
11486 if (*spc)
11488 tree c = *spc;
11489 *spc = OMP_CLAUSE_CHAIN (c);
11490 OMP_CLAUSE_CHAIN (c) = NULL_TREE;
11491 *pc = c;
11494 if (*pc == NULL_TREE)
11496 else if (OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_PRIVATE)
11498 /* private clause will appear only on inner_for_stmt.
11499 Change it into firstprivate, and add private clause
11500 on for_stmt. */
11501 tree c = copy_node (*pc);
11502 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
11503 OMP_FOR_CLAUSES (for_stmt) = c;
11504 OMP_CLAUSE_CODE (*pc) = OMP_CLAUSE_FIRSTPRIVATE;
11505 lang_hooks.decls.omp_finish_clause (*pc, pre_p, openacc);
11507 else
11509 /* lastprivate clause will appear on both inner_for_stmt
11510 and for_stmt. Add firstprivate clause to
11511 inner_for_stmt. */
11512 tree c = build_omp_clause (OMP_CLAUSE_LOCATION (*pc),
11513 OMP_CLAUSE_FIRSTPRIVATE);
11514 OMP_CLAUSE_DECL (c) = OMP_CLAUSE_DECL (*pc);
11515 OMP_CLAUSE_CHAIN (c) = *pc;
11516 *pc = c;
11517 lang_hooks.decls.omp_finish_clause (*pc, pre_p, openacc);
11519 tree c = build_omp_clause (UNKNOWN_LOCATION,
11520 OMP_CLAUSE_FIRSTPRIVATE);
11521 OMP_CLAUSE_DECL (c) = last;
11522 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
11523 OMP_PARALLEL_CLAUSES (*data[1]) = c;
11524 c = build_omp_clause (UNKNOWN_LOCATION,
11525 *pc ? OMP_CLAUSE_SHARED
11526 : OMP_CLAUSE_FIRSTPRIVATE);
11527 OMP_CLAUSE_DECL (c) = orig_decl;
11528 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
11529 OMP_PARALLEL_CLAUSES (*data[1]) = c;
11531 /* Similarly, take care of C++ range for temporaries, those should
11532 be firstprivate on OMP_PARALLEL if any. */
11533 if (data[1])
11534 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (inner_for_stmt)); i++)
11535 if (OMP_FOR_ORIG_DECLS (inner_for_stmt)
11536 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
11537 i)) == TREE_LIST
11538 && TREE_CHAIN (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt),
11539 i)))
11541 tree orig
11542 = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (inner_for_stmt), i);
11543 tree v = TREE_CHAIN (orig);
11544 tree c = build_omp_clause (UNKNOWN_LOCATION,
11545 OMP_CLAUSE_FIRSTPRIVATE);
11546 /* First add firstprivate clause for the __for_end artificial
11547 decl. */
11548 OMP_CLAUSE_DECL (c) = TREE_VEC_ELT (v, 1);
11549 if (TREE_CODE (TREE_TYPE (OMP_CLAUSE_DECL (c)))
11550 == REFERENCE_TYPE)
11551 OMP_CLAUSE_FIRSTPRIVATE_NO_REFERENCE (c) = 1;
11552 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
11553 OMP_PARALLEL_CLAUSES (*data[1]) = c;
11554 if (TREE_VEC_ELT (v, 0))
11556 /* And now the same for __for_range artificial decl if it
11557 exists. */
11558 c = build_omp_clause (UNKNOWN_LOCATION,
11559 OMP_CLAUSE_FIRSTPRIVATE);
11560 OMP_CLAUSE_DECL (c) = TREE_VEC_ELT (v, 0);
11561 if (TREE_CODE (TREE_TYPE (OMP_CLAUSE_DECL (c)))
11562 == REFERENCE_TYPE)
11563 OMP_CLAUSE_FIRSTPRIVATE_NO_REFERENCE (c) = 1;
11564 OMP_CLAUSE_CHAIN (c) = OMP_PARALLEL_CLAUSES (*data[1]);
11565 OMP_PARALLEL_CLAUSES (*data[1]) = c;
11570 switch (TREE_CODE (for_stmt))
11572 case OMP_FOR:
11573 if (OMP_FOR_NON_RECTANGULAR (inner_for_stmt ? inner_for_stmt : for_stmt))
11575 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
11576 OMP_CLAUSE_SCHEDULE))
11577 error_at (EXPR_LOCATION (for_stmt),
11578 "%qs clause may not appear on non-rectangular %qs",
11579 "schedule", "for");
11580 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ORDERED))
11581 error_at (EXPR_LOCATION (for_stmt),
11582 "%qs clause may not appear on non-rectangular %qs",
11583 "ordered", "for");
11585 break;
11586 case OMP_DISTRIBUTE:
11587 if (OMP_FOR_NON_RECTANGULAR (inner_for_stmt ? inner_for_stmt : for_stmt)
11588 && omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
11589 OMP_CLAUSE_DIST_SCHEDULE))
11590 error_at (EXPR_LOCATION (for_stmt),
11591 "%qs clause may not appear on non-rectangular %qs",
11592 "dist_schedule", "distribute");
11593 break;
11594 case OACC_LOOP:
11595 ort = ORT_ACC;
11596 break;
11597 case OMP_TASKLOOP:
11598 if (omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_UNTIED))
11599 ort = ORT_UNTIED_TASKLOOP;
11600 else
11601 ort = ORT_TASKLOOP;
11602 break;
11603 case OMP_SIMD:
11604 ort = ORT_SIMD;
11605 break;
11606 default:
11607 gcc_unreachable ();
11610 /* Set OMP_CLAUSE_LINEAR_NO_COPYIN flag on explicit linear
11611 clause for the IV. */
11612 if (ort == ORT_SIMD && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
11614 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), 0);
11615 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
11616 decl = TREE_OPERAND (t, 0);
11617 for (tree c = OMP_FOR_CLAUSES (for_stmt); c; c = OMP_CLAUSE_CHAIN (c))
11618 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
11619 && OMP_CLAUSE_DECL (c) == decl)
11621 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
11622 break;
11626 if (TREE_CODE (for_stmt) != OMP_TASKLOOP)
11627 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (for_stmt), pre_p, ort,
11628 loop_p && TREE_CODE (for_stmt) != OMP_SIMD
11629 ? OMP_LOOP : TREE_CODE (for_stmt));
11631 if (TREE_CODE (for_stmt) == OMP_DISTRIBUTE)
11632 gimplify_omp_ctxp->distribute = true;
11634 /* Handle OMP_FOR_INIT. */
11635 for_pre_body = NULL;
11636 if ((ort == ORT_SIMD
11637 || (inner_for_stmt && TREE_CODE (inner_for_stmt) == OMP_SIMD))
11638 && OMP_FOR_PRE_BODY (for_stmt))
11640 has_decl_expr = BITMAP_ALLOC (NULL);
11641 if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == DECL_EXPR
11642 && TREE_CODE (DECL_EXPR_DECL (OMP_FOR_PRE_BODY (for_stmt)))
11643 == VAR_DECL)
11645 t = OMP_FOR_PRE_BODY (for_stmt);
11646 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
11648 else if (TREE_CODE (OMP_FOR_PRE_BODY (for_stmt)) == STATEMENT_LIST)
11650 tree_stmt_iterator si;
11651 for (si = tsi_start (OMP_FOR_PRE_BODY (for_stmt)); !tsi_end_p (si);
11652 tsi_next (&si))
11654 t = tsi_stmt (si);
11655 if (TREE_CODE (t) == DECL_EXPR
11656 && TREE_CODE (DECL_EXPR_DECL (t)) == VAR_DECL)
11657 bitmap_set_bit (has_decl_expr, DECL_UID (DECL_EXPR_DECL (t)));
11661 if (OMP_FOR_PRE_BODY (for_stmt))
11663 if (TREE_CODE (for_stmt) != OMP_TASKLOOP || gimplify_omp_ctxp)
11664 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
11665 else
11667 struct gimplify_omp_ctx ctx;
11668 memset (&ctx, 0, sizeof (ctx));
11669 ctx.region_type = ORT_NONE;
11670 gimplify_omp_ctxp = &ctx;
11671 gimplify_and_add (OMP_FOR_PRE_BODY (for_stmt), &for_pre_body);
11672 gimplify_omp_ctxp = NULL;
11675 OMP_FOR_PRE_BODY (for_stmt) = NULL_TREE;
11677 if (OMP_FOR_INIT (for_stmt) == NULL_TREE)
11678 for_stmt = inner_for_stmt;
11680 /* For taskloop, need to gimplify the start, end and step before the
11681 taskloop, outside of the taskloop omp context. */
11682 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
11684 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
11686 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
11687 gimple_seq *for_pre_p = (gimple_seq_empty_p (for_pre_body)
11688 ? pre_p : &for_pre_body);
11689 tree type = TREE_TYPE (TREE_OPERAND (t, 0));
11690 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
11692 tree v = TREE_OPERAND (t, 1);
11693 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 1),
11694 for_pre_p, orig_for_stmt);
11695 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 2),
11696 for_pre_p, orig_for_stmt);
11698 else
11699 gimplify_omp_taskloop_expr (type, &TREE_OPERAND (t, 1), for_pre_p,
11700 orig_for_stmt);
11702 /* Handle OMP_FOR_COND. */
11703 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
11704 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
11706 tree v = TREE_OPERAND (t, 1);
11707 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 1),
11708 for_pre_p, orig_for_stmt);
11709 gimplify_omp_taskloop_expr (type, &TREE_VEC_ELT (v, 2),
11710 for_pre_p, orig_for_stmt);
11712 else
11713 gimplify_omp_taskloop_expr (type, &TREE_OPERAND (t, 1), for_pre_p,
11714 orig_for_stmt);
11716 /* Handle OMP_FOR_INCR. */
11717 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
11718 if (TREE_CODE (t) == MODIFY_EXPR)
11720 decl = TREE_OPERAND (t, 0);
11721 t = TREE_OPERAND (t, 1);
11722 tree *tp = &TREE_OPERAND (t, 1);
11723 if (TREE_CODE (t) == PLUS_EXPR && *tp == decl)
11724 tp = &TREE_OPERAND (t, 0);
11726 gimplify_omp_taskloop_expr (NULL_TREE, tp, for_pre_p,
11727 orig_for_stmt);
11731 gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (orig_for_stmt), pre_p, ort,
11732 OMP_TASKLOOP);
11735 if (orig_for_stmt != for_stmt)
11736 gimplify_omp_ctxp->combined_loop = true;
11738 for_body = NULL;
11739 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
11740 == TREE_VEC_LENGTH (OMP_FOR_COND (for_stmt)));
11741 gcc_assert (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
11742 == TREE_VEC_LENGTH (OMP_FOR_INCR (for_stmt)));
11744 tree c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ORDERED);
11745 bool is_doacross = false;
11746 if (c && OMP_CLAUSE_ORDERED_EXPR (c))
11748 is_doacross = true;
11749 gimplify_omp_ctxp->loop_iter_var.create (TREE_VEC_LENGTH
11750 (OMP_FOR_INIT (for_stmt))
11751 * 2);
11753 int collapse = 1, tile = 0;
11754 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_COLLAPSE);
11755 if (c)
11756 collapse = tree_to_shwi (OMP_CLAUSE_COLLAPSE_EXPR (c));
11757 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_TILE);
11758 if (c)
11759 tile = list_length (OMP_CLAUSE_TILE_LIST (c));
11760 c = omp_find_clause (OMP_FOR_CLAUSES (for_stmt), OMP_CLAUSE_ALLOCATE);
11761 hash_set<tree> *allocate_uids = NULL;
11762 if (c)
11764 allocate_uids = new hash_set<tree>;
11765 for (; c; c = OMP_CLAUSE_CHAIN (c))
11766 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_ALLOCATE)
11767 allocate_uids->add (OMP_CLAUSE_DECL (c));
11769 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
11771 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
11772 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
11773 decl = TREE_OPERAND (t, 0);
11774 gcc_assert (DECL_P (decl));
11775 gcc_assert (INTEGRAL_TYPE_P (TREE_TYPE (decl))
11776 || POINTER_TYPE_P (TREE_TYPE (decl)));
11777 if (is_doacross)
11779 if (TREE_CODE (for_stmt) == OMP_FOR && OMP_FOR_ORIG_DECLS (for_stmt))
11781 tree orig_decl = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
11782 if (TREE_CODE (orig_decl) == TREE_LIST)
11784 orig_decl = TREE_PURPOSE (orig_decl);
11785 if (!orig_decl)
11786 orig_decl = decl;
11788 gimplify_omp_ctxp->loop_iter_var.quick_push (orig_decl);
11790 else
11791 gimplify_omp_ctxp->loop_iter_var.quick_push (decl);
11792 gimplify_omp_ctxp->loop_iter_var.quick_push (decl);
11795 /* Make sure the iteration variable is private. */
11796 tree c = NULL_TREE;
11797 tree c2 = NULL_TREE;
11798 if (orig_for_stmt != for_stmt)
11800 /* Preserve this information until we gimplify the inner simd. */
11801 if (has_decl_expr
11802 && bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
11803 TREE_PRIVATE (t) = 1;
11805 else if (ort == ORT_SIMD)
11807 splay_tree_node n = splay_tree_lookup (gimplify_omp_ctxp->variables,
11808 (splay_tree_key) decl);
11809 omp_is_private (gimplify_omp_ctxp, decl,
11810 1 + (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt))
11811 != 1));
11812 if (n != NULL && (n->value & GOVD_DATA_SHARE_CLASS) != 0)
11814 omp_notice_variable (gimplify_omp_ctxp, decl, true);
11815 if (n->value & GOVD_LASTPRIVATE_CONDITIONAL)
11816 for (tree c3 = omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
11817 OMP_CLAUSE_LASTPRIVATE);
11818 c3; c3 = omp_find_clause (OMP_CLAUSE_CHAIN (c3),
11819 OMP_CLAUSE_LASTPRIVATE))
11820 if (OMP_CLAUSE_DECL (c3) == decl)
11822 warning_at (OMP_CLAUSE_LOCATION (c3), 0,
11823 "conditional %<lastprivate%> on loop "
11824 "iterator %qD ignored", decl);
11825 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c3) = 0;
11826 n->value &= ~GOVD_LASTPRIVATE_CONDITIONAL;
11829 else if (TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1 && !loop_p)
11831 c = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
11832 OMP_CLAUSE_LINEAR_NO_COPYIN (c) = 1;
11833 unsigned int flags = GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN;
11834 if ((has_decl_expr
11835 && bitmap_bit_p (has_decl_expr, DECL_UID (decl)))
11836 || TREE_PRIVATE (t))
11838 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
11839 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
11841 struct gimplify_omp_ctx *outer
11842 = gimplify_omp_ctxp->outer_context;
11843 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
11845 if (outer->region_type == ORT_WORKSHARE
11846 && outer->combined_loop)
11848 n = splay_tree_lookup (outer->variables,
11849 (splay_tree_key)decl);
11850 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
11852 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
11853 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
11855 else
11857 struct gimplify_omp_ctx *octx = outer->outer_context;
11858 if (octx
11859 && octx->region_type == ORT_COMBINED_PARALLEL
11860 && octx->outer_context
11861 && (octx->outer_context->region_type
11862 == ORT_WORKSHARE)
11863 && octx->outer_context->combined_loop)
11865 octx = octx->outer_context;
11866 n = splay_tree_lookup (octx->variables,
11867 (splay_tree_key)decl);
11868 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
11870 OMP_CLAUSE_LINEAR_NO_COPYOUT (c) = 1;
11871 flags |= GOVD_LINEAR_LASTPRIVATE_NO_OUTER;
11878 OMP_CLAUSE_DECL (c) = decl;
11879 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
11880 OMP_FOR_CLAUSES (for_stmt) = c;
11881 omp_add_variable (gimplify_omp_ctxp, decl, flags);
11882 if (outer && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c))
11884 if (outer->region_type == ORT_WORKSHARE
11885 && outer->combined_loop)
11887 if (outer->outer_context
11888 && (outer->outer_context->region_type
11889 == ORT_COMBINED_PARALLEL))
11890 outer = outer->outer_context;
11891 else if (omp_check_private (outer, decl, false))
11892 outer = NULL;
11894 else if (((outer->region_type & ORT_TASKLOOP)
11895 == ORT_TASKLOOP)
11896 && outer->combined_loop
11897 && !omp_check_private (gimplify_omp_ctxp,
11898 decl, false))
11900 else if (outer->region_type != ORT_COMBINED_PARALLEL)
11902 omp_notice_variable (outer, decl, true);
11903 outer = NULL;
11905 if (outer)
11907 n = splay_tree_lookup (outer->variables,
11908 (splay_tree_key)decl);
11909 if (n == NULL || (n->value & GOVD_DATA_SHARE_CLASS) == 0)
11911 omp_add_variable (outer, decl,
11912 GOVD_LASTPRIVATE | GOVD_SEEN);
11913 if (outer->region_type == ORT_COMBINED_PARALLEL
11914 && outer->outer_context
11915 && (outer->outer_context->region_type
11916 == ORT_WORKSHARE)
11917 && outer->outer_context->combined_loop)
11919 outer = outer->outer_context;
11920 n = splay_tree_lookup (outer->variables,
11921 (splay_tree_key)decl);
11922 if (omp_check_private (outer, decl, false))
11923 outer = NULL;
11924 else if (n == NULL
11925 || ((n->value & GOVD_DATA_SHARE_CLASS)
11926 == 0))
11927 omp_add_variable (outer, decl,
11928 GOVD_LASTPRIVATE
11929 | GOVD_SEEN);
11930 else
11931 outer = NULL;
11933 if (outer && outer->outer_context
11934 && ((outer->outer_context->region_type
11935 & ORT_COMBINED_TEAMS) == ORT_COMBINED_TEAMS
11936 || (((outer->region_type & ORT_TASKLOOP)
11937 == ORT_TASKLOOP)
11938 && (outer->outer_context->region_type
11939 == ORT_COMBINED_PARALLEL))))
11941 outer = outer->outer_context;
11942 n = splay_tree_lookup (outer->variables,
11943 (splay_tree_key)decl);
11944 if (n == NULL
11945 || (n->value & GOVD_DATA_SHARE_CLASS) == 0)
11946 omp_add_variable (outer, decl,
11947 GOVD_SHARED | GOVD_SEEN);
11948 else
11949 outer = NULL;
11951 if (outer && outer->outer_context)
11952 omp_notice_variable (outer->outer_context, decl,
11953 true);
11958 else
11960 bool lastprivate
11961 = (!has_decl_expr
11962 || !bitmap_bit_p (has_decl_expr, DECL_UID (decl)));
11963 if (TREE_PRIVATE (t))
11964 lastprivate = false;
11965 if (loop_p && OMP_FOR_ORIG_DECLS (for_stmt))
11967 tree elt = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
11968 if (TREE_CODE (elt) == TREE_LIST && TREE_PURPOSE (elt))
11969 lastprivate = false;
11972 struct gimplify_omp_ctx *outer
11973 = gimplify_omp_ctxp->outer_context;
11974 if (outer && lastprivate)
11976 if (outer->region_type == ORT_WORKSHARE
11977 && outer->combined_loop)
11979 n = splay_tree_lookup (outer->variables,
11980 (splay_tree_key)decl);
11981 if (n != NULL && (n->value & GOVD_LOCAL) != 0)
11983 lastprivate = false;
11984 outer = NULL;
11986 else if (outer->outer_context
11987 && (outer->outer_context->region_type
11988 == ORT_COMBINED_PARALLEL))
11989 outer = outer->outer_context;
11990 else if (omp_check_private (outer, decl, false))
11991 outer = NULL;
11993 else if (((outer->region_type & ORT_TASKLOOP)
11994 == ORT_TASKLOOP)
11995 && outer->combined_loop
11996 && !omp_check_private (gimplify_omp_ctxp,
11997 decl, false))
11999 else if (outer->region_type != ORT_COMBINED_PARALLEL)
12001 omp_notice_variable (outer, decl, true);
12002 outer = NULL;
12004 if (outer)
12006 n = splay_tree_lookup (outer->variables,
12007 (splay_tree_key)decl);
12008 if (n == NULL || (n->value & GOVD_DATA_SHARE_CLASS) == 0)
12010 omp_add_variable (outer, decl,
12011 GOVD_LASTPRIVATE | GOVD_SEEN);
12012 if (outer->region_type == ORT_COMBINED_PARALLEL
12013 && outer->outer_context
12014 && (outer->outer_context->region_type
12015 == ORT_WORKSHARE)
12016 && outer->outer_context->combined_loop)
12018 outer = outer->outer_context;
12019 n = splay_tree_lookup (outer->variables,
12020 (splay_tree_key)decl);
12021 if (omp_check_private (outer, decl, false))
12022 outer = NULL;
12023 else if (n == NULL
12024 || ((n->value & GOVD_DATA_SHARE_CLASS)
12025 == 0))
12026 omp_add_variable (outer, decl,
12027 GOVD_LASTPRIVATE
12028 | GOVD_SEEN);
12029 else
12030 outer = NULL;
12032 if (outer && outer->outer_context
12033 && ((outer->outer_context->region_type
12034 & ORT_COMBINED_TEAMS) == ORT_COMBINED_TEAMS
12035 || (((outer->region_type & ORT_TASKLOOP)
12036 == ORT_TASKLOOP)
12037 && (outer->outer_context->region_type
12038 == ORT_COMBINED_PARALLEL))))
12040 outer = outer->outer_context;
12041 n = splay_tree_lookup (outer->variables,
12042 (splay_tree_key)decl);
12043 if (n == NULL
12044 || (n->value & GOVD_DATA_SHARE_CLASS) == 0)
12045 omp_add_variable (outer, decl,
12046 GOVD_SHARED | GOVD_SEEN);
12047 else
12048 outer = NULL;
12050 if (outer && outer->outer_context)
12051 omp_notice_variable (outer->outer_context, decl,
12052 true);
12057 c = build_omp_clause (input_location,
12058 lastprivate ? OMP_CLAUSE_LASTPRIVATE
12059 : OMP_CLAUSE_PRIVATE);
12060 OMP_CLAUSE_DECL (c) = decl;
12061 OMP_CLAUSE_CHAIN (c) = OMP_FOR_CLAUSES (for_stmt);
12062 OMP_FOR_CLAUSES (for_stmt) = c;
12063 omp_add_variable (gimplify_omp_ctxp, decl,
12064 (lastprivate ? GOVD_LASTPRIVATE : GOVD_PRIVATE)
12065 | GOVD_EXPLICIT | GOVD_SEEN);
12066 c = NULL_TREE;
12069 else if (omp_is_private (gimplify_omp_ctxp, decl, 0))
12071 omp_notice_variable (gimplify_omp_ctxp, decl, true);
12072 splay_tree_node n = splay_tree_lookup (gimplify_omp_ctxp->variables,
12073 (splay_tree_key) decl);
12074 if (n && (n->value & GOVD_LASTPRIVATE_CONDITIONAL))
12075 for (tree c3 = omp_find_clause (OMP_FOR_CLAUSES (for_stmt),
12076 OMP_CLAUSE_LASTPRIVATE);
12077 c3; c3 = omp_find_clause (OMP_CLAUSE_CHAIN (c3),
12078 OMP_CLAUSE_LASTPRIVATE))
12079 if (OMP_CLAUSE_DECL (c3) == decl)
12081 warning_at (OMP_CLAUSE_LOCATION (c3), 0,
12082 "conditional %<lastprivate%> on loop "
12083 "iterator %qD ignored", decl);
12084 OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c3) = 0;
12085 n->value &= ~GOVD_LASTPRIVATE_CONDITIONAL;
12088 else
12089 omp_add_variable (gimplify_omp_ctxp, decl, GOVD_PRIVATE | GOVD_SEEN);
12091 /* If DECL is not a gimple register, create a temporary variable to act
12092 as an iteration counter. This is valid, since DECL cannot be
12093 modified in the body of the loop. Similarly for any iteration vars
12094 in simd with collapse > 1 where the iterator vars must be
12095 lastprivate. And similarly for vars mentioned in allocate clauses. */
12096 if (orig_for_stmt != for_stmt)
12097 var = decl;
12098 else if (!is_gimple_reg (decl)
12099 || (ort == ORT_SIMD
12100 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) > 1)
12101 || (allocate_uids && allocate_uids->contains (decl)))
12103 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
12104 /* Make sure omp_add_variable is not called on it prematurely.
12105 We call it ourselves a few lines later. */
12106 gimplify_omp_ctxp = NULL;
12107 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
12108 gimplify_omp_ctxp = ctx;
12109 TREE_OPERAND (t, 0) = var;
12111 gimplify_seq_add_stmt (&for_body, gimple_build_assign (decl, var));
12113 if (ort == ORT_SIMD
12114 && TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)) == 1)
12116 c2 = build_omp_clause (input_location, OMP_CLAUSE_LINEAR);
12117 OMP_CLAUSE_LINEAR_NO_COPYIN (c2) = 1;
12118 OMP_CLAUSE_LINEAR_NO_COPYOUT (c2) = 1;
12119 OMP_CLAUSE_DECL (c2) = var;
12120 OMP_CLAUSE_CHAIN (c2) = OMP_FOR_CLAUSES (for_stmt);
12121 OMP_FOR_CLAUSES (for_stmt) = c2;
12122 omp_add_variable (gimplify_omp_ctxp, var,
12123 GOVD_LINEAR | GOVD_EXPLICIT | GOVD_SEEN);
12124 if (c == NULL_TREE)
12126 c = c2;
12127 c2 = NULL_TREE;
12130 else
12131 omp_add_variable (gimplify_omp_ctxp, var,
12132 GOVD_PRIVATE | GOVD_SEEN);
12134 else
12135 var = decl;
12137 gimplify_omp_ctxp->in_for_exprs = true;
12138 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
12140 tree lb = TREE_OPERAND (t, 1);
12141 tret = gimplify_expr (&TREE_VEC_ELT (lb, 1), &for_pre_body, NULL,
12142 is_gimple_val, fb_rvalue, false);
12143 ret = MIN (ret, tret);
12144 tret = gimplify_expr (&TREE_VEC_ELT (lb, 2), &for_pre_body, NULL,
12145 is_gimple_val, fb_rvalue, false);
12147 else
12148 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
12149 is_gimple_val, fb_rvalue, false);
12150 gimplify_omp_ctxp->in_for_exprs = false;
12151 ret = MIN (ret, tret);
12152 if (ret == GS_ERROR)
12153 return ret;
12155 /* Handle OMP_FOR_COND. */
12156 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
12157 gcc_assert (COMPARISON_CLASS_P (t));
12158 gcc_assert (TREE_OPERAND (t, 0) == decl);
12160 gimplify_omp_ctxp->in_for_exprs = true;
12161 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC)
12163 tree ub = TREE_OPERAND (t, 1);
12164 tret = gimplify_expr (&TREE_VEC_ELT (ub, 1), &for_pre_body, NULL,
12165 is_gimple_val, fb_rvalue, false);
12166 ret = MIN (ret, tret);
12167 tret = gimplify_expr (&TREE_VEC_ELT (ub, 2), &for_pre_body, NULL,
12168 is_gimple_val, fb_rvalue, false);
12170 else
12171 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
12172 is_gimple_val, fb_rvalue, false);
12173 gimplify_omp_ctxp->in_for_exprs = false;
12174 ret = MIN (ret, tret);
12176 /* Handle OMP_FOR_INCR. */
12177 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
12178 switch (TREE_CODE (t))
12180 case PREINCREMENT_EXPR:
12181 case POSTINCREMENT_EXPR:
12183 tree decl = TREE_OPERAND (t, 0);
12184 /* c_omp_for_incr_canonicalize_ptr() should have been
12185 called to massage things appropriately. */
12186 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
12188 if (orig_for_stmt != for_stmt)
12189 break;
12190 t = build_int_cst (TREE_TYPE (decl), 1);
12191 if (c)
12192 OMP_CLAUSE_LINEAR_STEP (c) = t;
12193 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
12194 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
12195 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
12196 break;
12199 case PREDECREMENT_EXPR:
12200 case POSTDECREMENT_EXPR:
12201 /* c_omp_for_incr_canonicalize_ptr() should have been
12202 called to massage things appropriately. */
12203 gcc_assert (!POINTER_TYPE_P (TREE_TYPE (decl)));
12204 if (orig_for_stmt != for_stmt)
12205 break;
12206 t = build_int_cst (TREE_TYPE (decl), -1);
12207 if (c)
12208 OMP_CLAUSE_LINEAR_STEP (c) = t;
12209 t = build2 (PLUS_EXPR, TREE_TYPE (decl), var, t);
12210 t = build2 (MODIFY_EXPR, TREE_TYPE (var), var, t);
12211 TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i) = t;
12212 break;
12214 case MODIFY_EXPR:
12215 gcc_assert (TREE_OPERAND (t, 0) == decl);
12216 TREE_OPERAND (t, 0) = var;
12218 t = TREE_OPERAND (t, 1);
12219 switch (TREE_CODE (t))
12221 case PLUS_EXPR:
12222 if (TREE_OPERAND (t, 1) == decl)
12224 TREE_OPERAND (t, 1) = TREE_OPERAND (t, 0);
12225 TREE_OPERAND (t, 0) = var;
12226 break;
12229 /* Fallthru. */
12230 case MINUS_EXPR:
12231 case POINTER_PLUS_EXPR:
12232 gcc_assert (TREE_OPERAND (t, 0) == decl);
12233 TREE_OPERAND (t, 0) = var;
12234 break;
12235 default:
12236 gcc_unreachable ();
12239 gimplify_omp_ctxp->in_for_exprs = true;
12240 tret = gimplify_expr (&TREE_OPERAND (t, 1), &for_pre_body, NULL,
12241 is_gimple_val, fb_rvalue, false);
12242 ret = MIN (ret, tret);
12243 if (c)
12245 tree step = TREE_OPERAND (t, 1);
12246 tree stept = TREE_TYPE (decl);
12247 if (POINTER_TYPE_P (stept))
12248 stept = sizetype;
12249 step = fold_convert (stept, step);
12250 if (TREE_CODE (t) == MINUS_EXPR)
12251 step = fold_build1 (NEGATE_EXPR, stept, step);
12252 OMP_CLAUSE_LINEAR_STEP (c) = step;
12253 if (step != TREE_OPERAND (t, 1))
12255 tret = gimplify_expr (&OMP_CLAUSE_LINEAR_STEP (c),
12256 &for_pre_body, NULL,
12257 is_gimple_val, fb_rvalue, false);
12258 ret = MIN (ret, tret);
12261 gimplify_omp_ctxp->in_for_exprs = false;
12262 break;
12264 default:
12265 gcc_unreachable ();
12268 if (c2)
12270 gcc_assert (c);
12271 OMP_CLAUSE_LINEAR_STEP (c2) = OMP_CLAUSE_LINEAR_STEP (c);
12274 if ((var != decl || collapse > 1 || tile) && orig_for_stmt == for_stmt)
12276 for (c = OMP_FOR_CLAUSES (for_stmt); c ; c = OMP_CLAUSE_CHAIN (c))
12277 if (((OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
12278 && OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c) == NULL)
12279 || (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LINEAR
12280 && !OMP_CLAUSE_LINEAR_NO_COPYOUT (c)
12281 && OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c) == NULL))
12282 && OMP_CLAUSE_DECL (c) == decl)
12284 if (is_doacross && (collapse == 1 || i >= collapse))
12285 t = var;
12286 else
12288 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
12289 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
12290 gcc_assert (TREE_OPERAND (t, 0) == var);
12291 t = TREE_OPERAND (t, 1);
12292 gcc_assert (TREE_CODE (t) == PLUS_EXPR
12293 || TREE_CODE (t) == MINUS_EXPR
12294 || TREE_CODE (t) == POINTER_PLUS_EXPR);
12295 gcc_assert (TREE_OPERAND (t, 0) == var);
12296 t = build2 (TREE_CODE (t), TREE_TYPE (decl),
12297 is_doacross ? var : decl,
12298 TREE_OPERAND (t, 1));
12300 gimple_seq *seq;
12301 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE)
12302 seq = &OMP_CLAUSE_LASTPRIVATE_GIMPLE_SEQ (c);
12303 else
12304 seq = &OMP_CLAUSE_LINEAR_GIMPLE_SEQ (c);
12305 push_gimplify_context ();
12306 gimplify_assign (decl, t, seq);
12307 gimple *bind = NULL;
12308 if (gimplify_ctxp->temps)
12310 bind = gimple_build_bind (NULL_TREE, *seq, NULL_TREE);
12311 *seq = NULL;
12312 gimplify_seq_add_stmt (seq, bind);
12314 pop_gimplify_context (bind);
12317 if (OMP_FOR_NON_RECTANGULAR (for_stmt) && var != decl)
12318 for (int j = i + 1; j < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); j++)
12320 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), j);
12321 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
12322 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
12323 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
12324 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
12325 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), j);
12326 gcc_assert (COMPARISON_CLASS_P (t));
12327 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
12328 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
12329 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
12333 BITMAP_FREE (has_decl_expr);
12334 delete allocate_uids;
12336 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP
12337 || (loop_p && orig_for_stmt == for_stmt))
12339 push_gimplify_context ();
12340 if (TREE_CODE (OMP_FOR_BODY (orig_for_stmt)) != BIND_EXPR)
12342 OMP_FOR_BODY (orig_for_stmt)
12343 = build3 (BIND_EXPR, void_type_node, NULL,
12344 OMP_FOR_BODY (orig_for_stmt), NULL);
12345 TREE_SIDE_EFFECTS (OMP_FOR_BODY (orig_for_stmt)) = 1;
12349 gimple *g = gimplify_and_return_first (OMP_FOR_BODY (orig_for_stmt),
12350 &for_body);
12352 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP
12353 || (loop_p && orig_for_stmt == for_stmt))
12355 if (gimple_code (g) == GIMPLE_BIND)
12356 pop_gimplify_context (g);
12357 else
12358 pop_gimplify_context (NULL);
12361 if (orig_for_stmt != for_stmt)
12362 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
12364 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
12365 decl = TREE_OPERAND (t, 0);
12366 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
12367 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
12368 gimplify_omp_ctxp = ctx->outer_context;
12369 var = create_tmp_var (TREE_TYPE (decl), get_name (decl));
12370 gimplify_omp_ctxp = ctx;
12371 omp_add_variable (gimplify_omp_ctxp, var, GOVD_PRIVATE | GOVD_SEEN);
12372 TREE_OPERAND (t, 0) = var;
12373 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
12374 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
12375 TREE_OPERAND (TREE_OPERAND (t, 1), 0) = var;
12376 if (OMP_FOR_NON_RECTANGULAR (for_stmt))
12377 for (int j = i + 1;
12378 j < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); j++)
12380 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), j);
12381 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
12382 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
12383 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
12385 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
12386 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
12388 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), j);
12389 gcc_assert (COMPARISON_CLASS_P (t));
12390 if (TREE_CODE (TREE_OPERAND (t, 1)) == TREE_VEC
12391 && TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) == decl)
12393 TREE_OPERAND (t, 1) = copy_node (TREE_OPERAND (t, 1));
12394 TREE_VEC_ELT (TREE_OPERAND (t, 1), 0) = var;
12399 gimplify_adjust_omp_clauses (pre_p, for_body,
12400 &OMP_FOR_CLAUSES (orig_for_stmt),
12401 TREE_CODE (orig_for_stmt));
12403 int kind;
12404 switch (TREE_CODE (orig_for_stmt))
12406 case OMP_FOR: kind = GF_OMP_FOR_KIND_FOR; break;
12407 case OMP_SIMD: kind = GF_OMP_FOR_KIND_SIMD; break;
12408 case OMP_DISTRIBUTE: kind = GF_OMP_FOR_KIND_DISTRIBUTE; break;
12409 case OMP_TASKLOOP: kind = GF_OMP_FOR_KIND_TASKLOOP; break;
12410 case OACC_LOOP: kind = GF_OMP_FOR_KIND_OACC_LOOP; break;
12411 default:
12412 gcc_unreachable ();
12414 if (loop_p && kind == GF_OMP_FOR_KIND_SIMD)
12416 gimplify_seq_add_seq (pre_p, for_pre_body);
12417 for_pre_body = NULL;
12419 gfor = gimple_build_omp_for (for_body, kind, OMP_FOR_CLAUSES (orig_for_stmt),
12420 TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)),
12421 for_pre_body);
12422 if (orig_for_stmt != for_stmt)
12423 gimple_omp_for_set_combined_p (gfor, true);
12424 if (gimplify_omp_ctxp
12425 && (gimplify_omp_ctxp->combined_loop
12426 || (gimplify_omp_ctxp->region_type == ORT_COMBINED_PARALLEL
12427 && gimplify_omp_ctxp->outer_context
12428 && gimplify_omp_ctxp->outer_context->combined_loop)))
12430 gimple_omp_for_set_combined_into_p (gfor, true);
12431 if (gimplify_omp_ctxp->combined_loop)
12432 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_SIMD);
12433 else
12434 gcc_assert (TREE_CODE (orig_for_stmt) == OMP_FOR);
12437 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
12439 t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
12440 gimple_omp_for_set_index (gfor, i, TREE_OPERAND (t, 0));
12441 gimple_omp_for_set_initial (gfor, i, TREE_OPERAND (t, 1));
12442 t = TREE_VEC_ELT (OMP_FOR_COND (for_stmt), i);
12443 gimple_omp_for_set_cond (gfor, i, TREE_CODE (t));
12444 gimple_omp_for_set_final (gfor, i, TREE_OPERAND (t, 1));
12445 t = TREE_VEC_ELT (OMP_FOR_INCR (for_stmt), i);
12446 gimple_omp_for_set_incr (gfor, i, TREE_OPERAND (t, 1));
12449 /* OMP_TASKLOOP is gimplified as two GIMPLE_OMP_FOR taskloop
12450 constructs with GIMPLE_OMP_TASK sandwiched in between them.
12451 The outer taskloop stands for computing the number of iterations,
12452 counts for collapsed loops and holding taskloop specific clauses.
12453 The task construct stands for the effect of data sharing on the
12454 explicit task it creates and the inner taskloop stands for expansion
12455 of the static loop inside of the explicit task construct. */
12456 if (TREE_CODE (orig_for_stmt) == OMP_TASKLOOP)
12458 tree *gfor_clauses_ptr = gimple_omp_for_clauses_ptr (gfor);
12459 tree task_clauses = NULL_TREE;
12460 tree c = *gfor_clauses_ptr;
12461 tree *gtask_clauses_ptr = &task_clauses;
12462 tree outer_for_clauses = NULL_TREE;
12463 tree *gforo_clauses_ptr = &outer_for_clauses;
12464 bitmap lastprivate_uids = NULL;
12465 if (omp_find_clause (c, OMP_CLAUSE_ALLOCATE))
12467 c = omp_find_clause (c, OMP_CLAUSE_LASTPRIVATE);
12468 if (c)
12470 lastprivate_uids = BITMAP_ALLOC (NULL);
12471 for (; c; c = omp_find_clause (OMP_CLAUSE_CHAIN (c),
12472 OMP_CLAUSE_LASTPRIVATE))
12473 bitmap_set_bit (lastprivate_uids,
12474 DECL_UID (OMP_CLAUSE_DECL (c)));
12476 c = *gfor_clauses_ptr;
12478 for (; c; c = OMP_CLAUSE_CHAIN (c))
12479 switch (OMP_CLAUSE_CODE (c))
12481 /* These clauses are allowed on task, move them there. */
12482 case OMP_CLAUSE_SHARED:
12483 case OMP_CLAUSE_FIRSTPRIVATE:
12484 case OMP_CLAUSE_DEFAULT:
12485 case OMP_CLAUSE_IF:
12486 case OMP_CLAUSE_UNTIED:
12487 case OMP_CLAUSE_FINAL:
12488 case OMP_CLAUSE_MERGEABLE:
12489 case OMP_CLAUSE_PRIORITY:
12490 case OMP_CLAUSE_REDUCTION:
12491 case OMP_CLAUSE_IN_REDUCTION:
12492 *gtask_clauses_ptr = c;
12493 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12494 break;
12495 case OMP_CLAUSE_PRIVATE:
12496 if (OMP_CLAUSE_PRIVATE_TASKLOOP_IV (c))
12498 /* We want private on outer for and firstprivate
12499 on task. */
12500 *gtask_clauses_ptr
12501 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
12502 OMP_CLAUSE_FIRSTPRIVATE);
12503 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
12504 lang_hooks.decls.omp_finish_clause (*gtask_clauses_ptr, NULL,
12505 openacc);
12506 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
12507 *gforo_clauses_ptr = c;
12508 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12510 else
12512 *gtask_clauses_ptr = c;
12513 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12515 break;
12516 /* These clauses go into outer taskloop clauses. */
12517 case OMP_CLAUSE_GRAINSIZE:
12518 case OMP_CLAUSE_NUM_TASKS:
12519 case OMP_CLAUSE_NOGROUP:
12520 *gforo_clauses_ptr = c;
12521 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12522 break;
12523 /* Collapse clause we duplicate on both taskloops. */
12524 case OMP_CLAUSE_COLLAPSE:
12525 *gfor_clauses_ptr = c;
12526 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12527 *gforo_clauses_ptr = copy_node (c);
12528 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr);
12529 break;
12530 /* For lastprivate, keep the clause on inner taskloop, and add
12531 a shared clause on task. If the same decl is also firstprivate,
12532 add also firstprivate clause on the inner taskloop. */
12533 case OMP_CLAUSE_LASTPRIVATE:
12534 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c))
12536 /* For taskloop C++ lastprivate IVs, we want:
12537 1) private on outer taskloop
12538 2) firstprivate and shared on task
12539 3) lastprivate on inner taskloop */
12540 *gtask_clauses_ptr
12541 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
12542 OMP_CLAUSE_FIRSTPRIVATE);
12543 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
12544 lang_hooks.decls.omp_finish_clause (*gtask_clauses_ptr, NULL,
12545 openacc);
12546 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
12547 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c) = 1;
12548 *gforo_clauses_ptr = build_omp_clause (OMP_CLAUSE_LOCATION (c),
12549 OMP_CLAUSE_PRIVATE);
12550 OMP_CLAUSE_DECL (*gforo_clauses_ptr) = OMP_CLAUSE_DECL (c);
12551 OMP_CLAUSE_PRIVATE_TASKLOOP_IV (*gforo_clauses_ptr) = 1;
12552 TREE_TYPE (*gforo_clauses_ptr) = TREE_TYPE (c);
12553 gforo_clauses_ptr = &OMP_CLAUSE_CHAIN (*gforo_clauses_ptr);
12555 *gfor_clauses_ptr = c;
12556 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12557 *gtask_clauses_ptr
12558 = build_omp_clause (OMP_CLAUSE_LOCATION (c), OMP_CLAUSE_SHARED);
12559 OMP_CLAUSE_DECL (*gtask_clauses_ptr) = OMP_CLAUSE_DECL (c);
12560 if (OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (c))
12561 OMP_CLAUSE_SHARED_FIRSTPRIVATE (*gtask_clauses_ptr) = 1;
12562 gtask_clauses_ptr
12563 = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
12564 break;
12565 /* Allocate clause we duplicate on task and inner taskloop
12566 if the decl is lastprivate, otherwise just put on task. */
12567 case OMP_CLAUSE_ALLOCATE:
12568 if (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)
12569 && DECL_P (OMP_CLAUSE_ALLOCATE_ALLOCATOR (c)))
12571 /* Additionally, put firstprivate clause on task
12572 for the allocator if it is not constant. */
12573 *gtask_clauses_ptr
12574 = build_omp_clause (OMP_CLAUSE_LOCATION (c),
12575 OMP_CLAUSE_FIRSTPRIVATE);
12576 OMP_CLAUSE_DECL (*gtask_clauses_ptr)
12577 = OMP_CLAUSE_ALLOCATE_ALLOCATOR (c);
12578 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
12580 if (lastprivate_uids
12581 && bitmap_bit_p (lastprivate_uids,
12582 DECL_UID (OMP_CLAUSE_DECL (c))))
12584 *gfor_clauses_ptr = c;
12585 gfor_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12586 *gtask_clauses_ptr = copy_node (c);
12587 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (*gtask_clauses_ptr);
12589 else
12591 *gtask_clauses_ptr = c;
12592 gtask_clauses_ptr = &OMP_CLAUSE_CHAIN (c);
12594 break;
12595 default:
12596 gcc_unreachable ();
12598 *gfor_clauses_ptr = NULL_TREE;
12599 *gtask_clauses_ptr = NULL_TREE;
12600 *gforo_clauses_ptr = NULL_TREE;
12601 BITMAP_FREE (lastprivate_uids);
12602 g = gimple_build_bind (NULL_TREE, gfor, NULL_TREE);
12603 g = gimple_build_omp_task (g, task_clauses, NULL_TREE, NULL_TREE,
12604 NULL_TREE, NULL_TREE, NULL_TREE);
12605 gimple_omp_task_set_taskloop_p (g, true);
12606 g = gimple_build_bind (NULL_TREE, g, NULL_TREE);
12607 gomp_for *gforo
12608 = gimple_build_omp_for (g, GF_OMP_FOR_KIND_TASKLOOP, outer_for_clauses,
12609 gimple_omp_for_collapse (gfor),
12610 gimple_omp_for_pre_body (gfor));
12611 gimple_omp_for_set_pre_body (gfor, NULL);
12612 gimple_omp_for_set_combined_p (gforo, true);
12613 gimple_omp_for_set_combined_into_p (gfor, true);
12614 for (i = 0; i < (int) gimple_omp_for_collapse (gfor); i++)
12616 tree type = TREE_TYPE (gimple_omp_for_index (gfor, i));
12617 tree v = create_tmp_var (type);
12618 gimple_omp_for_set_index (gforo, i, v);
12619 t = unshare_expr (gimple_omp_for_initial (gfor, i));
12620 gimple_omp_for_set_initial (gforo, i, t);
12621 gimple_omp_for_set_cond (gforo, i,
12622 gimple_omp_for_cond (gfor, i));
12623 t = unshare_expr (gimple_omp_for_final (gfor, i));
12624 gimple_omp_for_set_final (gforo, i, t);
12625 t = unshare_expr (gimple_omp_for_incr (gfor, i));
12626 gcc_assert (TREE_OPERAND (t, 0) == gimple_omp_for_index (gfor, i));
12627 TREE_OPERAND (t, 0) = v;
12628 gimple_omp_for_set_incr (gforo, i, t);
12629 t = build_omp_clause (input_location, OMP_CLAUSE_PRIVATE);
12630 OMP_CLAUSE_DECL (t) = v;
12631 OMP_CLAUSE_CHAIN (t) = gimple_omp_for_clauses (gforo);
12632 gimple_omp_for_set_clauses (gforo, t);
12633 if (OMP_FOR_NON_RECTANGULAR (for_stmt))
12635 tree *p1 = NULL, *p2 = NULL;
12636 t = gimple_omp_for_initial (gforo, i);
12637 if (TREE_CODE (t) == TREE_VEC)
12638 p1 = &TREE_VEC_ELT (t, 0);
12639 t = gimple_omp_for_final (gforo, i);
12640 if (TREE_CODE (t) == TREE_VEC)
12642 if (p1)
12643 p2 = &TREE_VEC_ELT (t, 0);
12644 else
12645 p1 = &TREE_VEC_ELT (t, 0);
12647 if (p1)
12649 int j;
12650 for (j = 0; j < i; j++)
12651 if (*p1 == gimple_omp_for_index (gfor, j))
12653 *p1 = gimple_omp_for_index (gforo, j);
12654 if (p2)
12655 *p2 = *p1;
12656 break;
12658 gcc_assert (j < i);
12662 gimplify_seq_add_stmt (pre_p, gforo);
12664 else
12665 gimplify_seq_add_stmt (pre_p, gfor);
12667 if (TREE_CODE (orig_for_stmt) == OMP_FOR)
12669 struct gimplify_omp_ctx *ctx = gimplify_omp_ctxp;
12670 unsigned lastprivate_conditional = 0;
12671 while (ctx
12672 && (ctx->region_type == ORT_TARGET_DATA
12673 || ctx->region_type == ORT_TASKGROUP))
12674 ctx = ctx->outer_context;
12675 if (ctx && (ctx->region_type & ORT_PARALLEL) != 0)
12676 for (tree c = gimple_omp_for_clauses (gfor);
12677 c; c = OMP_CLAUSE_CHAIN (c))
12678 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
12679 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
12680 ++lastprivate_conditional;
12681 if (lastprivate_conditional)
12683 struct omp_for_data fd;
12684 omp_extract_for_data (gfor, &fd, NULL);
12685 tree type = build_array_type_nelts (unsigned_type_for (fd.iter_type),
12686 lastprivate_conditional);
12687 tree var = create_tmp_var_raw (type);
12688 tree c = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE__CONDTEMP_);
12689 OMP_CLAUSE_DECL (c) = var;
12690 OMP_CLAUSE_CHAIN (c) = gimple_omp_for_clauses (gfor);
12691 gimple_omp_for_set_clauses (gfor, c);
12692 omp_add_variable (ctx, var, GOVD_CONDTEMP | GOVD_SEEN);
12695 else if (TREE_CODE (orig_for_stmt) == OMP_SIMD)
12697 unsigned lastprivate_conditional = 0;
12698 for (tree c = gimple_omp_for_clauses (gfor); c; c = OMP_CLAUSE_CHAIN (c))
12699 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_LASTPRIVATE
12700 && OMP_CLAUSE_LASTPRIVATE_CONDITIONAL (c))
12701 ++lastprivate_conditional;
12702 if (lastprivate_conditional)
12704 struct omp_for_data fd;
12705 omp_extract_for_data (gfor, &fd, NULL);
12706 tree type = unsigned_type_for (fd.iter_type);
12707 while (lastprivate_conditional--)
12709 tree c = build_omp_clause (UNKNOWN_LOCATION,
12710 OMP_CLAUSE__CONDTEMP_);
12711 OMP_CLAUSE_DECL (c) = create_tmp_var (type);
12712 OMP_CLAUSE_CHAIN (c) = gimple_omp_for_clauses (gfor);
12713 gimple_omp_for_set_clauses (gfor, c);
12718 if (ret != GS_ALL_DONE)
12719 return GS_ERROR;
12720 *expr_p = NULL_TREE;
12721 return GS_ALL_DONE;
12724 /* Helper for gimplify_omp_loop, called through walk_tree. */
12726 static tree
12727 replace_reduction_placeholders (tree *tp, int *walk_subtrees, void *data)
12729 if (DECL_P (*tp))
12731 tree *d = (tree *) data;
12732 if (*tp == OMP_CLAUSE_REDUCTION_PLACEHOLDER (d[0]))
12734 *tp = OMP_CLAUSE_REDUCTION_PLACEHOLDER (d[1]);
12735 *walk_subtrees = 0;
12737 else if (*tp == OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (d[0]))
12739 *tp = OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (d[1]);
12740 *walk_subtrees = 0;
12743 return NULL_TREE;
12746 /* Gimplify the gross structure of an OMP_LOOP statement. */
12748 static enum gimplify_status
12749 gimplify_omp_loop (tree *expr_p, gimple_seq *pre_p)
12751 tree for_stmt = *expr_p;
12752 tree clauses = OMP_FOR_CLAUSES (for_stmt);
12753 struct gimplify_omp_ctx *octx = gimplify_omp_ctxp;
12754 enum omp_clause_bind_kind kind = OMP_CLAUSE_BIND_THREAD;
12755 int i;
12757 /* If order is not present, the behavior is as if order(concurrent)
12758 appeared. */
12759 tree order = omp_find_clause (clauses, OMP_CLAUSE_ORDER);
12760 if (order == NULL_TREE)
12762 order = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_ORDER);
12763 OMP_CLAUSE_CHAIN (order) = clauses;
12764 OMP_FOR_CLAUSES (for_stmt) = clauses = order;
12767 tree bind = omp_find_clause (clauses, OMP_CLAUSE_BIND);
12768 if (bind == NULL_TREE)
12770 if (!flag_openmp) /* flag_openmp_simd */
12772 else if (octx && (octx->region_type & ORT_TEAMS) != 0)
12773 kind = OMP_CLAUSE_BIND_TEAMS;
12774 else if (octx && (octx->region_type & ORT_PARALLEL) != 0)
12775 kind = OMP_CLAUSE_BIND_PARALLEL;
12776 else
12778 for (; octx; octx = octx->outer_context)
12780 if ((octx->region_type & ORT_ACC) != 0
12781 || octx->region_type == ORT_NONE
12782 || octx->region_type == ORT_IMPLICIT_TARGET)
12783 continue;
12784 break;
12786 if (octx == NULL && !in_omp_construct)
12787 error_at (EXPR_LOCATION (for_stmt),
12788 "%<bind%> clause not specified on a %<loop%> "
12789 "construct not nested inside another OpenMP construct");
12791 bind = build_omp_clause (UNKNOWN_LOCATION, OMP_CLAUSE_BIND);
12792 OMP_CLAUSE_CHAIN (bind) = clauses;
12793 OMP_CLAUSE_BIND_KIND (bind) = kind;
12794 OMP_FOR_CLAUSES (for_stmt) = bind;
12796 else
12797 switch (OMP_CLAUSE_BIND_KIND (bind))
12799 case OMP_CLAUSE_BIND_THREAD:
12800 break;
12801 case OMP_CLAUSE_BIND_PARALLEL:
12802 if (!flag_openmp) /* flag_openmp_simd */
12804 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
12805 break;
12807 for (; octx; octx = octx->outer_context)
12808 if (octx->region_type == ORT_SIMD
12809 && omp_find_clause (octx->clauses, OMP_CLAUSE_BIND) == NULL_TREE)
12811 error_at (EXPR_LOCATION (for_stmt),
12812 "%<bind(parallel)%> on a %<loop%> construct nested "
12813 "inside %<simd%> construct");
12814 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
12815 break;
12817 kind = OMP_CLAUSE_BIND_PARALLEL;
12818 break;
12819 case OMP_CLAUSE_BIND_TEAMS:
12820 if (!flag_openmp) /* flag_openmp_simd */
12822 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
12823 break;
12825 if ((octx
12826 && octx->region_type != ORT_IMPLICIT_TARGET
12827 && octx->region_type != ORT_NONE
12828 && (octx->region_type & ORT_TEAMS) == 0)
12829 || in_omp_construct)
12831 error_at (EXPR_LOCATION (for_stmt),
12832 "%<bind(teams)%> on a %<loop%> region not strictly "
12833 "nested inside of a %<teams%> region");
12834 OMP_CLAUSE_BIND_KIND (bind) = OMP_CLAUSE_BIND_THREAD;
12835 break;
12837 kind = OMP_CLAUSE_BIND_TEAMS;
12838 break;
12839 default:
12840 gcc_unreachable ();
12843 for (tree *pc = &OMP_FOR_CLAUSES (for_stmt); *pc; )
12844 switch (OMP_CLAUSE_CODE (*pc))
12846 case OMP_CLAUSE_REDUCTION:
12847 if (OMP_CLAUSE_REDUCTION_INSCAN (*pc))
12849 error_at (OMP_CLAUSE_LOCATION (*pc),
12850 "%<inscan%> %<reduction%> clause on "
12851 "%qs construct", "loop");
12852 OMP_CLAUSE_REDUCTION_INSCAN (*pc) = 0;
12854 if (OMP_CLAUSE_REDUCTION_TASK (*pc))
12856 error_at (OMP_CLAUSE_LOCATION (*pc),
12857 "invalid %<task%> reduction modifier on construct "
12858 "other than %<parallel%>, %qs or %<sections%>",
12859 lang_GNU_Fortran () ? "do" : "for");
12860 OMP_CLAUSE_REDUCTION_TASK (*pc) = 0;
12862 pc = &OMP_CLAUSE_CHAIN (*pc);
12863 break;
12864 case OMP_CLAUSE_LASTPRIVATE:
12865 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
12867 tree t = TREE_VEC_ELT (OMP_FOR_INIT (for_stmt), i);
12868 gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
12869 if (OMP_CLAUSE_DECL (*pc) == TREE_OPERAND (t, 0))
12870 break;
12871 if (OMP_FOR_ORIG_DECLS (for_stmt)
12872 && TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt),
12873 i)) == TREE_LIST
12874 && TREE_PURPOSE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt),
12875 i)))
12877 tree orig = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
12878 if (OMP_CLAUSE_DECL (*pc) == TREE_PURPOSE (orig))
12879 break;
12882 if (i == TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)))
12884 error_at (OMP_CLAUSE_LOCATION (*pc),
12885 "%<lastprivate%> clause on a %<loop%> construct refers "
12886 "to a variable %qD which is not the loop iterator",
12887 OMP_CLAUSE_DECL (*pc));
12888 *pc = OMP_CLAUSE_CHAIN (*pc);
12889 break;
12891 pc = &OMP_CLAUSE_CHAIN (*pc);
12892 break;
12893 default:
12894 pc = &OMP_CLAUSE_CHAIN (*pc);
12895 break;
12898 TREE_SET_CODE (for_stmt, OMP_SIMD);
12900 int last;
12901 switch (kind)
12903 case OMP_CLAUSE_BIND_THREAD: last = 0; break;
12904 case OMP_CLAUSE_BIND_PARALLEL: last = 1; break;
12905 case OMP_CLAUSE_BIND_TEAMS: last = 2; break;
12907 for (int pass = 1; pass <= last; pass++)
12909 if (pass == 2)
12911 tree bind = build3 (BIND_EXPR, void_type_node, NULL, NULL, NULL);
12912 append_to_statement_list (*expr_p, &BIND_EXPR_BODY (bind));
12913 *expr_p = make_node (OMP_PARALLEL);
12914 TREE_TYPE (*expr_p) = void_type_node;
12915 OMP_PARALLEL_BODY (*expr_p) = bind;
12916 OMP_PARALLEL_COMBINED (*expr_p) = 1;
12917 SET_EXPR_LOCATION (*expr_p, EXPR_LOCATION (for_stmt));
12918 tree *pc = &OMP_PARALLEL_CLAUSES (*expr_p);
12919 for (i = 0; i < TREE_VEC_LENGTH (OMP_FOR_INIT (for_stmt)); i++)
12920 if (OMP_FOR_ORIG_DECLS (for_stmt)
12921 && (TREE_CODE (TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i))
12922 == TREE_LIST))
12924 tree elt = TREE_VEC_ELT (OMP_FOR_ORIG_DECLS (for_stmt), i);
12925 if (TREE_PURPOSE (elt) && TREE_VALUE (elt))
12927 *pc = build_omp_clause (UNKNOWN_LOCATION,
12928 OMP_CLAUSE_FIRSTPRIVATE);
12929 OMP_CLAUSE_DECL (*pc) = TREE_VALUE (elt);
12930 pc = &OMP_CLAUSE_CHAIN (*pc);
12934 tree t = make_node (pass == 2 ? OMP_DISTRIBUTE : OMP_FOR);
12935 tree *pc = &OMP_FOR_CLAUSES (t);
12936 TREE_TYPE (t) = void_type_node;
12937 OMP_FOR_BODY (t) = *expr_p;
12938 SET_EXPR_LOCATION (t, EXPR_LOCATION (for_stmt));
12939 for (tree c = OMP_FOR_CLAUSES (for_stmt); c; c = OMP_CLAUSE_CHAIN (c))
12940 switch (OMP_CLAUSE_CODE (c))
12942 case OMP_CLAUSE_BIND:
12943 case OMP_CLAUSE_ORDER:
12944 case OMP_CLAUSE_COLLAPSE:
12945 *pc = copy_node (c);
12946 pc = &OMP_CLAUSE_CHAIN (*pc);
12947 break;
12948 case OMP_CLAUSE_PRIVATE:
12949 case OMP_CLAUSE_FIRSTPRIVATE:
12950 /* Only needed on innermost. */
12951 break;
12952 case OMP_CLAUSE_LASTPRIVATE:
12953 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c) && pass != last)
12955 *pc = build_omp_clause (OMP_CLAUSE_LOCATION (c),
12956 OMP_CLAUSE_FIRSTPRIVATE);
12957 OMP_CLAUSE_DECL (*pc) = OMP_CLAUSE_DECL (c);
12958 lang_hooks.decls.omp_finish_clause (*pc, NULL, false);
12959 pc = &OMP_CLAUSE_CHAIN (*pc);
12961 *pc = copy_node (c);
12962 OMP_CLAUSE_LASTPRIVATE_STMT (*pc) = NULL_TREE;
12963 TREE_TYPE (*pc) = unshare_expr (TREE_TYPE (c));
12964 if (OMP_CLAUSE_LASTPRIVATE_LOOP_IV (c))
12966 if (pass != last)
12967 OMP_CLAUSE_LASTPRIVATE_FIRSTPRIVATE (*pc) = 1;
12968 else
12969 lang_hooks.decls.omp_finish_clause (*pc, NULL, false);
12970 OMP_CLAUSE_LASTPRIVATE_LOOP_IV (*pc) = 0;
12972 pc = &OMP_CLAUSE_CHAIN (*pc);
12973 break;
12974 case OMP_CLAUSE_REDUCTION:
12975 *pc = copy_node (c);
12976 OMP_CLAUSE_DECL (*pc) = unshare_expr (OMP_CLAUSE_DECL (c));
12977 TREE_TYPE (*pc) = unshare_expr (TREE_TYPE (c));
12978 OMP_CLAUSE_REDUCTION_INIT (*pc)
12979 = unshare_expr (OMP_CLAUSE_REDUCTION_INIT (c));
12980 OMP_CLAUSE_REDUCTION_MERGE (*pc)
12981 = unshare_expr (OMP_CLAUSE_REDUCTION_MERGE (c));
12982 if (OMP_CLAUSE_REDUCTION_PLACEHOLDER (*pc))
12984 OMP_CLAUSE_REDUCTION_PLACEHOLDER (*pc)
12985 = copy_node (OMP_CLAUSE_REDUCTION_PLACEHOLDER (c));
12986 if (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (*pc))
12987 OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (*pc)
12988 = copy_node (OMP_CLAUSE_REDUCTION_DECL_PLACEHOLDER (c));
12989 tree nc = *pc;
12990 tree data[2] = { c, nc };
12991 walk_tree_without_duplicates (&OMP_CLAUSE_REDUCTION_INIT (nc),
12992 replace_reduction_placeholders,
12993 data);
12994 walk_tree_without_duplicates (&OMP_CLAUSE_REDUCTION_MERGE (nc),
12995 replace_reduction_placeholders,
12996 data);
12998 pc = &OMP_CLAUSE_CHAIN (*pc);
12999 break;
13000 default:
13001 gcc_unreachable ();
13003 *pc = NULL_TREE;
13004 *expr_p = t;
13006 return gimplify_omp_for (expr_p, pre_p);
13010 /* Helper function of optimize_target_teams, find OMP_TEAMS inside
13011 of OMP_TARGET's body. */
13013 static tree
13014 find_omp_teams (tree *tp, int *walk_subtrees, void *)
13016 *walk_subtrees = 0;
13017 switch (TREE_CODE (*tp))
13019 case OMP_TEAMS:
13020 return *tp;
13021 case BIND_EXPR:
13022 case STATEMENT_LIST:
13023 *walk_subtrees = 1;
13024 break;
13025 default:
13026 break;
13028 return NULL_TREE;
13031 /* Helper function of optimize_target_teams, determine if the expression
13032 can be computed safely before the target construct on the host. */
13034 static tree
13035 computable_teams_clause (tree *tp, int *walk_subtrees, void *)
13037 splay_tree_node n;
13039 if (TYPE_P (*tp))
13041 *walk_subtrees = 0;
13042 return NULL_TREE;
13044 switch (TREE_CODE (*tp))
13046 case VAR_DECL:
13047 case PARM_DECL:
13048 case RESULT_DECL:
13049 *walk_subtrees = 0;
13050 if (error_operand_p (*tp)
13051 || !INTEGRAL_TYPE_P (TREE_TYPE (*tp))
13052 || DECL_HAS_VALUE_EXPR_P (*tp)
13053 || DECL_THREAD_LOCAL_P (*tp)
13054 || TREE_SIDE_EFFECTS (*tp)
13055 || TREE_THIS_VOLATILE (*tp))
13056 return *tp;
13057 if (is_global_var (*tp)
13058 && (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (*tp))
13059 || lookup_attribute ("omp declare target link",
13060 DECL_ATTRIBUTES (*tp))))
13061 return *tp;
13062 if (VAR_P (*tp)
13063 && !DECL_SEEN_IN_BIND_EXPR_P (*tp)
13064 && !is_global_var (*tp)
13065 && decl_function_context (*tp) == current_function_decl)
13066 return *tp;
13067 n = splay_tree_lookup (gimplify_omp_ctxp->variables,
13068 (splay_tree_key) *tp);
13069 if (n == NULL)
13071 if (gimplify_omp_ctxp->defaultmap[GDMK_SCALAR] & GOVD_FIRSTPRIVATE)
13072 return NULL_TREE;
13073 return *tp;
13075 else if (n->value & GOVD_LOCAL)
13076 return *tp;
13077 else if (n->value & GOVD_FIRSTPRIVATE)
13078 return NULL_TREE;
13079 else if ((n->value & (GOVD_MAP | GOVD_MAP_ALWAYS_TO))
13080 == (GOVD_MAP | GOVD_MAP_ALWAYS_TO))
13081 return NULL_TREE;
13082 return *tp;
13083 case INTEGER_CST:
13084 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp)))
13085 return *tp;
13086 return NULL_TREE;
13087 case TARGET_EXPR:
13088 if (TARGET_EXPR_INITIAL (*tp)
13089 || TREE_CODE (TARGET_EXPR_SLOT (*tp)) != VAR_DECL)
13090 return *tp;
13091 return computable_teams_clause (&TARGET_EXPR_SLOT (*tp),
13092 walk_subtrees, NULL);
13093 /* Allow some reasonable subset of integral arithmetics. */
13094 case PLUS_EXPR:
13095 case MINUS_EXPR:
13096 case MULT_EXPR:
13097 case TRUNC_DIV_EXPR:
13098 case CEIL_DIV_EXPR:
13099 case FLOOR_DIV_EXPR:
13100 case ROUND_DIV_EXPR:
13101 case TRUNC_MOD_EXPR:
13102 case CEIL_MOD_EXPR:
13103 case FLOOR_MOD_EXPR:
13104 case ROUND_MOD_EXPR:
13105 case RDIV_EXPR:
13106 case EXACT_DIV_EXPR:
13107 case MIN_EXPR:
13108 case MAX_EXPR:
13109 case LSHIFT_EXPR:
13110 case RSHIFT_EXPR:
13111 case BIT_IOR_EXPR:
13112 case BIT_XOR_EXPR:
13113 case BIT_AND_EXPR:
13114 case NEGATE_EXPR:
13115 case ABS_EXPR:
13116 case BIT_NOT_EXPR:
13117 case NON_LVALUE_EXPR:
13118 CASE_CONVERT:
13119 if (!INTEGRAL_TYPE_P (TREE_TYPE (*tp)))
13120 return *tp;
13121 return NULL_TREE;
13122 /* And disallow anything else, except for comparisons. */
13123 default:
13124 if (COMPARISON_CLASS_P (*tp))
13125 return NULL_TREE;
13126 return *tp;
13130 /* Try to determine if the num_teams and/or thread_limit expressions
13131 can have their values determined already before entering the
13132 target construct.
13133 INTEGER_CSTs trivially are,
13134 integral decls that are firstprivate (explicitly or implicitly)
13135 or explicitly map(always, to:) or map(always, tofrom:) on the target
13136 region too, and expressions involving simple arithmetics on those
13137 too, function calls are not ok, dereferencing something neither etc.
13138 Add NUM_TEAMS and THREAD_LIMIT clauses to the OMP_CLAUSES of
13139 EXPR based on what we find:
13140 0 stands for clause not specified at all, use implementation default
13141 -1 stands for value that can't be determined easily before entering
13142 the target construct.
13143 If teams construct is not present at all, use 1 for num_teams
13144 and 0 for thread_limit (only one team is involved, and the thread
13145 limit is implementation defined. */
13147 static void
13148 optimize_target_teams (tree target, gimple_seq *pre_p)
13150 tree body = OMP_BODY (target);
13151 tree teams = walk_tree (&body, find_omp_teams, NULL, NULL);
13152 tree num_teams = integer_zero_node;
13153 tree thread_limit = integer_zero_node;
13154 location_t num_teams_loc = EXPR_LOCATION (target);
13155 location_t thread_limit_loc = EXPR_LOCATION (target);
13156 tree c, *p, expr;
13157 struct gimplify_omp_ctx *target_ctx = gimplify_omp_ctxp;
13159 if (teams == NULL_TREE)
13160 num_teams = integer_one_node;
13161 else
13162 for (c = OMP_TEAMS_CLAUSES (teams); c; c = OMP_CLAUSE_CHAIN (c))
13164 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_NUM_TEAMS)
13166 p = &num_teams;
13167 num_teams_loc = OMP_CLAUSE_LOCATION (c);
13169 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_THREAD_LIMIT)
13171 p = &thread_limit;
13172 thread_limit_loc = OMP_CLAUSE_LOCATION (c);
13174 else
13175 continue;
13176 expr = OMP_CLAUSE_OPERAND (c, 0);
13177 if (TREE_CODE (expr) == INTEGER_CST)
13179 *p = expr;
13180 continue;
13182 if (walk_tree (&expr, computable_teams_clause, NULL, NULL))
13184 *p = integer_minus_one_node;
13185 continue;
13187 *p = expr;
13188 gimplify_omp_ctxp = gimplify_omp_ctxp->outer_context;
13189 if (gimplify_expr (p, pre_p, NULL, is_gimple_val, fb_rvalue, false)
13190 == GS_ERROR)
13192 gimplify_omp_ctxp = target_ctx;
13193 *p = integer_minus_one_node;
13194 continue;
13196 gimplify_omp_ctxp = target_ctx;
13197 if (!DECL_P (expr) && TREE_CODE (expr) != TARGET_EXPR)
13198 OMP_CLAUSE_OPERAND (c, 0) = *p;
13200 c = build_omp_clause (thread_limit_loc, OMP_CLAUSE_THREAD_LIMIT);
13201 OMP_CLAUSE_THREAD_LIMIT_EXPR (c) = thread_limit;
13202 OMP_CLAUSE_CHAIN (c) = OMP_TARGET_CLAUSES (target);
13203 OMP_TARGET_CLAUSES (target) = c;
13204 c = build_omp_clause (num_teams_loc, OMP_CLAUSE_NUM_TEAMS);
13205 OMP_CLAUSE_NUM_TEAMS_EXPR (c) = num_teams;
13206 OMP_CLAUSE_CHAIN (c) = OMP_TARGET_CLAUSES (target);
13207 OMP_TARGET_CLAUSES (target) = c;
13210 /* Gimplify the gross structure of several OMP constructs. */
13212 static void
13213 gimplify_omp_workshare (tree *expr_p, gimple_seq *pre_p)
13215 tree expr = *expr_p;
13216 gimple *stmt;
13217 gimple_seq body = NULL;
13218 enum omp_region_type ort;
13220 switch (TREE_CODE (expr))
13222 case OMP_SECTIONS:
13223 case OMP_SINGLE:
13224 ort = ORT_WORKSHARE;
13225 break;
13226 case OMP_TARGET:
13227 ort = OMP_TARGET_COMBINED (expr) ? ORT_COMBINED_TARGET : ORT_TARGET;
13228 break;
13229 case OACC_KERNELS:
13230 ort = ORT_ACC_KERNELS;
13231 break;
13232 case OACC_PARALLEL:
13233 ort = ORT_ACC_PARALLEL;
13234 break;
13235 case OACC_SERIAL:
13236 ort = ORT_ACC_SERIAL;
13237 break;
13238 case OACC_DATA:
13239 ort = ORT_ACC_DATA;
13240 break;
13241 case OMP_TARGET_DATA:
13242 ort = ORT_TARGET_DATA;
13243 break;
13244 case OMP_TEAMS:
13245 ort = OMP_TEAMS_COMBINED (expr) ? ORT_COMBINED_TEAMS : ORT_TEAMS;
13246 if (gimplify_omp_ctxp == NULL
13247 || gimplify_omp_ctxp->region_type == ORT_IMPLICIT_TARGET)
13248 ort = (enum omp_region_type) (ort | ORT_HOST_TEAMS);
13249 break;
13250 case OACC_HOST_DATA:
13251 ort = ORT_ACC_HOST_DATA;
13252 break;
13253 default:
13254 gcc_unreachable ();
13257 bool save_in_omp_construct = in_omp_construct;
13258 if ((ort & ORT_ACC) == 0)
13259 in_omp_construct = false;
13260 gimplify_scan_omp_clauses (&OMP_CLAUSES (expr), pre_p, ort,
13261 TREE_CODE (expr));
13262 if (TREE_CODE (expr) == OMP_TARGET)
13263 optimize_target_teams (expr, pre_p);
13264 if ((ort & (ORT_TARGET | ORT_TARGET_DATA)) != 0
13265 || (ort & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
13267 push_gimplify_context ();
13268 gimple *g = gimplify_and_return_first (OMP_BODY (expr), &body);
13269 if (gimple_code (g) == GIMPLE_BIND)
13270 pop_gimplify_context (g);
13271 else
13272 pop_gimplify_context (NULL);
13273 if ((ort & ORT_TARGET_DATA) != 0)
13275 enum built_in_function end_ix;
13276 switch (TREE_CODE (expr))
13278 case OACC_DATA:
13279 case OACC_HOST_DATA:
13280 end_ix = BUILT_IN_GOACC_DATA_END;
13281 break;
13282 case OMP_TARGET_DATA:
13283 end_ix = BUILT_IN_GOMP_TARGET_END_DATA;
13284 break;
13285 default:
13286 gcc_unreachable ();
13288 tree fn = builtin_decl_explicit (end_ix);
13289 g = gimple_build_call (fn, 0);
13290 gimple_seq cleanup = NULL;
13291 gimple_seq_add_stmt (&cleanup, g);
13292 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
13293 body = NULL;
13294 gimple_seq_add_stmt (&body, g);
13297 else
13298 gimplify_and_add (OMP_BODY (expr), &body);
13299 gimplify_adjust_omp_clauses (pre_p, body, &OMP_CLAUSES (expr),
13300 TREE_CODE (expr));
13301 in_omp_construct = save_in_omp_construct;
13303 switch (TREE_CODE (expr))
13305 case OACC_DATA:
13306 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_DATA,
13307 OMP_CLAUSES (expr));
13308 break;
13309 case OACC_HOST_DATA:
13310 if (omp_find_clause (OMP_CLAUSES (expr), OMP_CLAUSE_IF_PRESENT))
13312 for (tree c = OMP_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
13313 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_USE_DEVICE_PTR)
13314 OMP_CLAUSE_USE_DEVICE_PTR_IF_PRESENT (c) = 1;
13317 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_HOST_DATA,
13318 OMP_CLAUSES (expr));
13319 break;
13320 case OACC_KERNELS:
13321 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_KERNELS,
13322 OMP_CLAUSES (expr));
13323 break;
13324 case OACC_PARALLEL:
13325 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_PARALLEL,
13326 OMP_CLAUSES (expr));
13327 break;
13328 case OACC_SERIAL:
13329 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_OACC_SERIAL,
13330 OMP_CLAUSES (expr));
13331 break;
13332 case OMP_SECTIONS:
13333 stmt = gimple_build_omp_sections (body, OMP_CLAUSES (expr));
13334 break;
13335 case OMP_SINGLE:
13336 stmt = gimple_build_omp_single (body, OMP_CLAUSES (expr));
13337 break;
13338 case OMP_TARGET:
13339 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_REGION,
13340 OMP_CLAUSES (expr));
13341 break;
13342 case OMP_TARGET_DATA:
13343 /* Put use_device_{ptr,addr} clauses last, as map clauses are supposed
13344 to be evaluated before the use_device_{ptr,addr} clauses if they
13345 refer to the same variables. */
13347 tree use_device_clauses;
13348 tree *pc, *uc = &use_device_clauses;
13349 for (pc = &OMP_CLAUSES (expr); *pc; )
13350 if (OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_USE_DEVICE_PTR
13351 || OMP_CLAUSE_CODE (*pc) == OMP_CLAUSE_USE_DEVICE_ADDR)
13353 *uc = *pc;
13354 *pc = OMP_CLAUSE_CHAIN (*pc);
13355 uc = &OMP_CLAUSE_CHAIN (*uc);
13357 else
13358 pc = &OMP_CLAUSE_CHAIN (*pc);
13359 *uc = NULL_TREE;
13360 *pc = use_device_clauses;
13361 stmt = gimple_build_omp_target (body, GF_OMP_TARGET_KIND_DATA,
13362 OMP_CLAUSES (expr));
13364 break;
13365 case OMP_TEAMS:
13366 stmt = gimple_build_omp_teams (body, OMP_CLAUSES (expr));
13367 if ((ort & ORT_HOST_TEAMS) == ORT_HOST_TEAMS)
13368 gimple_omp_teams_set_host (as_a <gomp_teams *> (stmt), true);
13369 break;
13370 default:
13371 gcc_unreachable ();
13374 gimplify_seq_add_stmt (pre_p, stmt);
13375 *expr_p = NULL_TREE;
13378 /* Gimplify the gross structure of OpenACC enter/exit data, update, and OpenMP
13379 target update constructs. */
13381 static void
13382 gimplify_omp_target_update (tree *expr_p, gimple_seq *pre_p)
13384 tree expr = *expr_p;
13385 int kind;
13386 gomp_target *stmt;
13387 enum omp_region_type ort = ORT_WORKSHARE;
13389 switch (TREE_CODE (expr))
13391 case OACC_ENTER_DATA:
13392 case OACC_EXIT_DATA:
13393 kind = GF_OMP_TARGET_KIND_OACC_ENTER_EXIT_DATA;
13394 ort = ORT_ACC;
13395 break;
13396 case OACC_UPDATE:
13397 kind = GF_OMP_TARGET_KIND_OACC_UPDATE;
13398 ort = ORT_ACC;
13399 break;
13400 case OMP_TARGET_UPDATE:
13401 kind = GF_OMP_TARGET_KIND_UPDATE;
13402 break;
13403 case OMP_TARGET_ENTER_DATA:
13404 kind = GF_OMP_TARGET_KIND_ENTER_DATA;
13405 break;
13406 case OMP_TARGET_EXIT_DATA:
13407 kind = GF_OMP_TARGET_KIND_EXIT_DATA;
13408 break;
13409 default:
13410 gcc_unreachable ();
13412 gimplify_scan_omp_clauses (&OMP_STANDALONE_CLAUSES (expr), pre_p,
13413 ort, TREE_CODE (expr));
13414 gimplify_adjust_omp_clauses (pre_p, NULL, &OMP_STANDALONE_CLAUSES (expr),
13415 TREE_CODE (expr));
13416 if (TREE_CODE (expr) == OACC_UPDATE
13417 && omp_find_clause (OMP_STANDALONE_CLAUSES (expr),
13418 OMP_CLAUSE_IF_PRESENT))
13420 /* The runtime uses GOMP_MAP_{TO,FROM} to denote the if_present
13421 clause. */
13422 for (tree c = OMP_STANDALONE_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
13423 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP)
13424 switch (OMP_CLAUSE_MAP_KIND (c))
13426 case GOMP_MAP_FORCE_TO:
13427 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_TO);
13428 break;
13429 case GOMP_MAP_FORCE_FROM:
13430 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FROM);
13431 break;
13432 default:
13433 break;
13436 else if (TREE_CODE (expr) == OACC_EXIT_DATA
13437 && omp_find_clause (OMP_STANDALONE_CLAUSES (expr),
13438 OMP_CLAUSE_FINALIZE))
13440 /* Use GOMP_MAP_DELETE/GOMP_MAP_FORCE_FROM to denote "finalize"
13441 semantics. */
13442 bool have_clause = false;
13443 for (tree c = OMP_STANDALONE_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
13444 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_MAP)
13445 switch (OMP_CLAUSE_MAP_KIND (c))
13447 case GOMP_MAP_FROM:
13448 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FORCE_FROM);
13449 have_clause = true;
13450 break;
13451 case GOMP_MAP_RELEASE:
13452 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_DELETE);
13453 have_clause = true;
13454 break;
13455 case GOMP_MAP_TO_PSET:
13456 /* Fortran arrays with descriptors must map that descriptor when
13457 doing standalone "attach" operations (in OpenACC). In that
13458 case GOMP_MAP_TO_PSET appears by itself with no preceding
13459 clause (see trans-openmp.c:gfc_trans_omp_clauses). */
13460 break;
13461 case GOMP_MAP_POINTER:
13462 /* TODO PR92929: we may see these here, but they'll always follow
13463 one of the clauses above, and will be handled by libgomp as
13464 one group, so no handling required here. */
13465 gcc_assert (have_clause);
13466 break;
13467 case GOMP_MAP_DETACH:
13468 OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_FORCE_DETACH);
13469 have_clause = false;
13470 break;
13471 case GOMP_MAP_STRUCT:
13472 have_clause = false;
13473 break;
13474 default:
13475 gcc_unreachable ();
13478 stmt = gimple_build_omp_target (NULL, kind, OMP_STANDALONE_CLAUSES (expr));
13480 gimplify_seq_add_stmt (pre_p, stmt);
13481 *expr_p = NULL_TREE;
13484 /* A subroutine of gimplify_omp_atomic. The front end is supposed to have
13485 stabilized the lhs of the atomic operation as *ADDR. Return true if
13486 EXPR is this stabilized form. */
13488 static bool
13489 goa_lhs_expr_p (tree expr, tree addr)
13491 /* Also include casts to other type variants. The C front end is fond
13492 of adding these for e.g. volatile variables. This is like
13493 STRIP_TYPE_NOPS but includes the main variant lookup. */
13494 STRIP_USELESS_TYPE_CONVERSION (expr);
13496 if (TREE_CODE (expr) == INDIRECT_REF)
13498 expr = TREE_OPERAND (expr, 0);
13499 while (expr != addr
13500 && (CONVERT_EXPR_P (expr)
13501 || TREE_CODE (expr) == NON_LVALUE_EXPR)
13502 && TREE_CODE (expr) == TREE_CODE (addr)
13503 && types_compatible_p (TREE_TYPE (expr), TREE_TYPE (addr)))
13505 expr = TREE_OPERAND (expr, 0);
13506 addr = TREE_OPERAND (addr, 0);
13508 if (expr == addr)
13509 return true;
13510 return (TREE_CODE (addr) == ADDR_EXPR
13511 && TREE_CODE (expr) == ADDR_EXPR
13512 && TREE_OPERAND (addr, 0) == TREE_OPERAND (expr, 0));
13514 if (TREE_CODE (addr) == ADDR_EXPR && expr == TREE_OPERAND (addr, 0))
13515 return true;
13516 return false;
13519 /* Walk *EXPR_P and replace appearances of *LHS_ADDR with LHS_VAR. If an
13520 expression does not involve the lhs, evaluate it into a temporary.
13521 Return 1 if the lhs appeared as a subexpression, 0 if it did not,
13522 or -1 if an error was encountered. */
13524 static int
13525 goa_stabilize_expr (tree *expr_p, gimple_seq *pre_p, tree lhs_addr,
13526 tree lhs_var)
13528 tree expr = *expr_p;
13529 int saw_lhs;
13531 if (goa_lhs_expr_p (expr, lhs_addr))
13533 *expr_p = lhs_var;
13534 return 1;
13536 if (is_gimple_val (expr))
13537 return 0;
13539 saw_lhs = 0;
13540 switch (TREE_CODE_CLASS (TREE_CODE (expr)))
13542 case tcc_binary:
13543 case tcc_comparison:
13544 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p, lhs_addr,
13545 lhs_var);
13546 /* FALLTHRU */
13547 case tcc_unary:
13548 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p, lhs_addr,
13549 lhs_var);
13550 break;
13551 case tcc_expression:
13552 switch (TREE_CODE (expr))
13554 case TRUTH_ANDIF_EXPR:
13555 case TRUTH_ORIF_EXPR:
13556 case TRUTH_AND_EXPR:
13557 case TRUTH_OR_EXPR:
13558 case TRUTH_XOR_EXPR:
13559 case BIT_INSERT_EXPR:
13560 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 1), pre_p,
13561 lhs_addr, lhs_var);
13562 /* FALLTHRU */
13563 case TRUTH_NOT_EXPR:
13564 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
13565 lhs_addr, lhs_var);
13566 break;
13567 case COMPOUND_EXPR:
13568 /* Break out any preevaluations from cp_build_modify_expr. */
13569 for (; TREE_CODE (expr) == COMPOUND_EXPR;
13570 expr = TREE_OPERAND (expr, 1))
13571 gimplify_stmt (&TREE_OPERAND (expr, 0), pre_p);
13572 *expr_p = expr;
13573 return goa_stabilize_expr (expr_p, pre_p, lhs_addr, lhs_var);
13574 default:
13575 break;
13577 break;
13578 case tcc_reference:
13579 if (TREE_CODE (expr) == BIT_FIELD_REF)
13580 saw_lhs |= goa_stabilize_expr (&TREE_OPERAND (expr, 0), pre_p,
13581 lhs_addr, lhs_var);
13582 break;
13583 default:
13584 break;
13587 if (saw_lhs == 0)
13589 enum gimplify_status gs;
13590 gs = gimplify_expr (expr_p, pre_p, NULL, is_gimple_val, fb_rvalue);
13591 if (gs != GS_ALL_DONE)
13592 saw_lhs = -1;
13595 return saw_lhs;
13598 /* Gimplify an OMP_ATOMIC statement. */
13600 static enum gimplify_status
13601 gimplify_omp_atomic (tree *expr_p, gimple_seq *pre_p)
13603 tree addr = TREE_OPERAND (*expr_p, 0);
13604 tree rhs = TREE_CODE (*expr_p) == OMP_ATOMIC_READ
13605 ? NULL : TREE_OPERAND (*expr_p, 1);
13606 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (addr)));
13607 tree tmp_load;
13608 gomp_atomic_load *loadstmt;
13609 gomp_atomic_store *storestmt;
13611 tmp_load = create_tmp_reg (type);
13612 if (rhs && goa_stabilize_expr (&rhs, pre_p, addr, tmp_load) < 0)
13613 return GS_ERROR;
13615 if (gimplify_expr (&addr, pre_p, NULL, is_gimple_val, fb_rvalue)
13616 != GS_ALL_DONE)
13617 return GS_ERROR;
13619 loadstmt = gimple_build_omp_atomic_load (tmp_load, addr,
13620 OMP_ATOMIC_MEMORY_ORDER (*expr_p));
13621 gimplify_seq_add_stmt (pre_p, loadstmt);
13622 if (rhs)
13624 /* BIT_INSERT_EXPR is not valid for non-integral bitfield
13625 representatives. Use BIT_FIELD_REF on the lhs instead. */
13626 if (TREE_CODE (rhs) == BIT_INSERT_EXPR
13627 && !INTEGRAL_TYPE_P (TREE_TYPE (tmp_load)))
13629 tree bitpos = TREE_OPERAND (rhs, 2);
13630 tree op1 = TREE_OPERAND (rhs, 1);
13631 tree bitsize;
13632 tree tmp_store = tmp_load;
13633 if (TREE_CODE (*expr_p) == OMP_ATOMIC_CAPTURE_OLD)
13634 tmp_store = get_initialized_tmp_var (tmp_load, pre_p);
13635 if (INTEGRAL_TYPE_P (TREE_TYPE (op1)))
13636 bitsize = bitsize_int (TYPE_PRECISION (TREE_TYPE (op1)));
13637 else
13638 bitsize = TYPE_SIZE (TREE_TYPE (op1));
13639 gcc_assert (TREE_OPERAND (rhs, 0) == tmp_load);
13640 tree t = build2_loc (EXPR_LOCATION (rhs),
13641 MODIFY_EXPR, void_type_node,
13642 build3_loc (EXPR_LOCATION (rhs), BIT_FIELD_REF,
13643 TREE_TYPE (op1), tmp_store, bitsize,
13644 bitpos), op1);
13645 gimplify_and_add (t, pre_p);
13646 rhs = tmp_store;
13648 if (gimplify_expr (&rhs, pre_p, NULL, is_gimple_val, fb_rvalue)
13649 != GS_ALL_DONE)
13650 return GS_ERROR;
13653 if (TREE_CODE (*expr_p) == OMP_ATOMIC_READ)
13654 rhs = tmp_load;
13655 storestmt
13656 = gimple_build_omp_atomic_store (rhs, OMP_ATOMIC_MEMORY_ORDER (*expr_p));
13657 gimplify_seq_add_stmt (pre_p, storestmt);
13658 switch (TREE_CODE (*expr_p))
13660 case OMP_ATOMIC_READ:
13661 case OMP_ATOMIC_CAPTURE_OLD:
13662 *expr_p = tmp_load;
13663 gimple_omp_atomic_set_need_value (loadstmt);
13664 break;
13665 case OMP_ATOMIC_CAPTURE_NEW:
13666 *expr_p = rhs;
13667 gimple_omp_atomic_set_need_value (storestmt);
13668 break;
13669 default:
13670 *expr_p = NULL;
13671 break;
13674 return GS_ALL_DONE;
13677 /* Gimplify a TRANSACTION_EXPR. This involves gimplification of the
13678 body, and adding some EH bits. */
13680 static enum gimplify_status
13681 gimplify_transaction (tree *expr_p, gimple_seq *pre_p)
13683 tree expr = *expr_p, temp, tbody = TRANSACTION_EXPR_BODY (expr);
13684 gimple *body_stmt;
13685 gtransaction *trans_stmt;
13686 gimple_seq body = NULL;
13687 int subcode = 0;
13689 /* Wrap the transaction body in a BIND_EXPR so we have a context
13690 where to put decls for OMP. */
13691 if (TREE_CODE (tbody) != BIND_EXPR)
13693 tree bind = build3 (BIND_EXPR, void_type_node, NULL, tbody, NULL);
13694 TREE_SIDE_EFFECTS (bind) = 1;
13695 SET_EXPR_LOCATION (bind, EXPR_LOCATION (tbody));
13696 TRANSACTION_EXPR_BODY (expr) = bind;
13699 push_gimplify_context ();
13700 temp = voidify_wrapper_expr (*expr_p, NULL);
13702 body_stmt = gimplify_and_return_first (TRANSACTION_EXPR_BODY (expr), &body);
13703 pop_gimplify_context (body_stmt);
13705 trans_stmt = gimple_build_transaction (body);
13706 if (TRANSACTION_EXPR_OUTER (expr))
13707 subcode = GTMA_IS_OUTER;
13708 else if (TRANSACTION_EXPR_RELAXED (expr))
13709 subcode = GTMA_IS_RELAXED;
13710 gimple_transaction_set_subcode (trans_stmt, subcode);
13712 gimplify_seq_add_stmt (pre_p, trans_stmt);
13714 if (temp)
13716 *expr_p = temp;
13717 return GS_OK;
13720 *expr_p = NULL_TREE;
13721 return GS_ALL_DONE;
13724 /* Gimplify an OMP_ORDERED construct. EXPR is the tree version. BODY
13725 is the OMP_BODY of the original EXPR (which has already been
13726 gimplified so it's not present in the EXPR).
13728 Return the gimplified GIMPLE_OMP_ORDERED tuple. */
13730 static gimple *
13731 gimplify_omp_ordered (tree expr, gimple_seq body)
13733 tree c, decls;
13734 int failures = 0;
13735 unsigned int i;
13736 tree source_c = NULL_TREE;
13737 tree sink_c = NULL_TREE;
13739 if (gimplify_omp_ctxp)
13741 for (c = OMP_ORDERED_CLAUSES (expr); c; c = OMP_CLAUSE_CHAIN (c))
13742 if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
13743 && gimplify_omp_ctxp->loop_iter_var.is_empty ()
13744 && (OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SINK
13745 || OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SOURCE))
13747 error_at (OMP_CLAUSE_LOCATION (c),
13748 "%<ordered%> construct with %<depend%> clause must be "
13749 "closely nested inside a loop with %<ordered%> clause "
13750 "with a parameter");
13751 failures++;
13753 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
13754 && OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SINK)
13756 bool fail = false;
13757 for (decls = OMP_CLAUSE_DECL (c), i = 0;
13758 decls && TREE_CODE (decls) == TREE_LIST;
13759 decls = TREE_CHAIN (decls), ++i)
13760 if (i >= gimplify_omp_ctxp->loop_iter_var.length () / 2)
13761 continue;
13762 else if (TREE_VALUE (decls)
13763 != gimplify_omp_ctxp->loop_iter_var[2 * i])
13765 error_at (OMP_CLAUSE_LOCATION (c),
13766 "variable %qE is not an iteration "
13767 "of outermost loop %d, expected %qE",
13768 TREE_VALUE (decls), i + 1,
13769 gimplify_omp_ctxp->loop_iter_var[2 * i]);
13770 fail = true;
13771 failures++;
13773 else
13774 TREE_VALUE (decls)
13775 = gimplify_omp_ctxp->loop_iter_var[2 * i + 1];
13776 if (!fail && i != gimplify_omp_ctxp->loop_iter_var.length () / 2)
13778 error_at (OMP_CLAUSE_LOCATION (c),
13779 "number of variables in %<depend%> clause with "
13780 "%<sink%> modifier does not match number of "
13781 "iteration variables");
13782 failures++;
13784 sink_c = c;
13786 else if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_DEPEND
13787 && OMP_CLAUSE_DEPEND_KIND (c) == OMP_CLAUSE_DEPEND_SOURCE)
13789 if (source_c)
13791 error_at (OMP_CLAUSE_LOCATION (c),
13792 "more than one %<depend%> clause with %<source%> "
13793 "modifier on an %<ordered%> construct");
13794 failures++;
13796 else
13797 source_c = c;
13800 if (source_c && sink_c)
13802 error_at (OMP_CLAUSE_LOCATION (source_c),
13803 "%<depend%> clause with %<source%> modifier specified "
13804 "together with %<depend%> clauses with %<sink%> modifier "
13805 "on the same construct");
13806 failures++;
13809 if (failures)
13810 return gimple_build_nop ();
13811 return gimple_build_omp_ordered (body, OMP_ORDERED_CLAUSES (expr));
13814 /* Convert the GENERIC expression tree *EXPR_P to GIMPLE. If the
13815 expression produces a value to be used as an operand inside a GIMPLE
13816 statement, the value will be stored back in *EXPR_P. This value will
13817 be a tree of class tcc_declaration, tcc_constant, tcc_reference or
13818 an SSA_NAME. The corresponding sequence of GIMPLE statements is
13819 emitted in PRE_P and POST_P.
13821 Additionally, this process may overwrite parts of the input
13822 expression during gimplification. Ideally, it should be
13823 possible to do non-destructive gimplification.
13825 EXPR_P points to the GENERIC expression to convert to GIMPLE. If
13826 the expression needs to evaluate to a value to be used as
13827 an operand in a GIMPLE statement, this value will be stored in
13828 *EXPR_P on exit. This happens when the caller specifies one
13829 of fb_lvalue or fb_rvalue fallback flags.
13831 PRE_P will contain the sequence of GIMPLE statements corresponding
13832 to the evaluation of EXPR and all the side-effects that must
13833 be executed before the main expression. On exit, the last
13834 statement of PRE_P is the core statement being gimplified. For
13835 instance, when gimplifying 'if (++a)' the last statement in
13836 PRE_P will be 'if (t.1)' where t.1 is the result of
13837 pre-incrementing 'a'.
13839 POST_P will contain the sequence of GIMPLE statements corresponding
13840 to the evaluation of all the side-effects that must be executed
13841 after the main expression. If this is NULL, the post
13842 side-effects are stored at the end of PRE_P.
13844 The reason why the output is split in two is to handle post
13845 side-effects explicitly. In some cases, an expression may have
13846 inner and outer post side-effects which need to be emitted in
13847 an order different from the one given by the recursive
13848 traversal. For instance, for the expression (*p--)++ the post
13849 side-effects of '--' must actually occur *after* the post
13850 side-effects of '++'. However, gimplification will first visit
13851 the inner expression, so if a separate POST sequence was not
13852 used, the resulting sequence would be:
13854 1 t.1 = *p
13855 2 p = p - 1
13856 3 t.2 = t.1 + 1
13857 4 *p = t.2
13859 However, the post-decrement operation in line #2 must not be
13860 evaluated until after the store to *p at line #4, so the
13861 correct sequence should be:
13863 1 t.1 = *p
13864 2 t.2 = t.1 + 1
13865 3 *p = t.2
13866 4 p = p - 1
13868 So, by specifying a separate post queue, it is possible
13869 to emit the post side-effects in the correct order.
13870 If POST_P is NULL, an internal queue will be used. Before
13871 returning to the caller, the sequence POST_P is appended to
13872 the main output sequence PRE_P.
13874 GIMPLE_TEST_F points to a function that takes a tree T and
13875 returns nonzero if T is in the GIMPLE form requested by the
13876 caller. The GIMPLE predicates are in gimple.c.
13878 FALLBACK tells the function what sort of a temporary we want if
13879 gimplification cannot produce an expression that complies with
13880 GIMPLE_TEST_F.
13882 fb_none means that no temporary should be generated
13883 fb_rvalue means that an rvalue is OK to generate
13884 fb_lvalue means that an lvalue is OK to generate
13885 fb_either means that either is OK, but an lvalue is preferable.
13886 fb_mayfail means that gimplification may fail (in which case
13887 GS_ERROR will be returned)
13889 The return value is either GS_ERROR or GS_ALL_DONE, since this
13890 function iterates until EXPR is completely gimplified or an error
13891 occurs. */
13893 enum gimplify_status
13894 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
13895 bool (*gimple_test_f) (tree), fallback_t fallback)
13897 tree tmp;
13898 gimple_seq internal_pre = NULL;
13899 gimple_seq internal_post = NULL;
13900 tree save_expr;
13901 bool is_statement;
13902 location_t saved_location;
13903 enum gimplify_status ret;
13904 gimple_stmt_iterator pre_last_gsi, post_last_gsi;
13905 tree label;
13907 save_expr = *expr_p;
13908 if (save_expr == NULL_TREE)
13909 return GS_ALL_DONE;
13911 /* If we are gimplifying a top-level statement, PRE_P must be valid. */
13912 is_statement = gimple_test_f == is_gimple_stmt;
13913 if (is_statement)
13914 gcc_assert (pre_p);
13916 /* Consistency checks. */
13917 if (gimple_test_f == is_gimple_reg)
13918 gcc_assert (fallback & (fb_rvalue | fb_lvalue));
13919 else if (gimple_test_f == is_gimple_val
13920 || gimple_test_f == is_gimple_call_addr
13921 || gimple_test_f == is_gimple_condexpr
13922 || gimple_test_f == is_gimple_condexpr_for_cond
13923 || gimple_test_f == is_gimple_mem_rhs
13924 || gimple_test_f == is_gimple_mem_rhs_or_call
13925 || gimple_test_f == is_gimple_reg_rhs
13926 || gimple_test_f == is_gimple_reg_rhs_or_call
13927 || gimple_test_f == is_gimple_asm_val
13928 || gimple_test_f == is_gimple_mem_ref_addr)
13929 gcc_assert (fallback & fb_rvalue);
13930 else if (gimple_test_f == is_gimple_min_lval
13931 || gimple_test_f == is_gimple_lvalue)
13932 gcc_assert (fallback & fb_lvalue);
13933 else if (gimple_test_f == is_gimple_addressable)
13934 gcc_assert (fallback & fb_either);
13935 else if (gimple_test_f == is_gimple_stmt)
13936 gcc_assert (fallback == fb_none);
13937 else
13939 /* We should have recognized the GIMPLE_TEST_F predicate to
13940 know what kind of fallback to use in case a temporary is
13941 needed to hold the value or address of *EXPR_P. */
13942 gcc_unreachable ();
13945 /* We used to check the predicate here and return immediately if it
13946 succeeds. This is wrong; the design is for gimplification to be
13947 idempotent, and for the predicates to only test for valid forms, not
13948 whether they are fully simplified. */
13949 if (pre_p == NULL)
13950 pre_p = &internal_pre;
13952 if (post_p == NULL)
13953 post_p = &internal_post;
13955 /* Remember the last statements added to PRE_P and POST_P. Every
13956 new statement added by the gimplification helpers needs to be
13957 annotated with location information. To centralize the
13958 responsibility, we remember the last statement that had been
13959 added to both queues before gimplifying *EXPR_P. If
13960 gimplification produces new statements in PRE_P and POST_P, those
13961 statements will be annotated with the same location information
13962 as *EXPR_P. */
13963 pre_last_gsi = gsi_last (*pre_p);
13964 post_last_gsi = gsi_last (*post_p);
13966 saved_location = input_location;
13967 if (save_expr != error_mark_node
13968 && EXPR_HAS_LOCATION (*expr_p))
13969 input_location = EXPR_LOCATION (*expr_p);
13971 /* Loop over the specific gimplifiers until the toplevel node
13972 remains the same. */
13975 /* Strip away as many useless type conversions as possible
13976 at the toplevel. */
13977 STRIP_USELESS_TYPE_CONVERSION (*expr_p);
13979 /* Remember the expr. */
13980 save_expr = *expr_p;
13982 /* Die, die, die, my darling. */
13983 if (error_operand_p (save_expr))
13985 ret = GS_ERROR;
13986 break;
13989 /* Do any language-specific gimplification. */
13990 ret = ((enum gimplify_status)
13991 lang_hooks.gimplify_expr (expr_p, pre_p, post_p));
13992 if (ret == GS_OK)
13994 if (*expr_p == NULL_TREE)
13995 break;
13996 if (*expr_p != save_expr)
13997 continue;
13999 else if (ret != GS_UNHANDLED)
14000 break;
14002 /* Make sure that all the cases set 'ret' appropriately. */
14003 ret = GS_UNHANDLED;
14004 switch (TREE_CODE (*expr_p))
14006 /* First deal with the special cases. */
14008 case POSTINCREMENT_EXPR:
14009 case POSTDECREMENT_EXPR:
14010 case PREINCREMENT_EXPR:
14011 case PREDECREMENT_EXPR:
14012 ret = gimplify_self_mod_expr (expr_p, pre_p, post_p,
14013 fallback != fb_none,
14014 TREE_TYPE (*expr_p));
14015 break;
14017 case VIEW_CONVERT_EXPR:
14018 if ((fallback & fb_rvalue)
14019 && is_gimple_reg_type (TREE_TYPE (*expr_p))
14020 && is_gimple_reg_type (TREE_TYPE (TREE_OPERAND (*expr_p, 0))))
14022 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
14023 post_p, is_gimple_val, fb_rvalue);
14024 recalculate_side_effects (*expr_p);
14025 break;
14027 /* Fallthru. */
14029 case ARRAY_REF:
14030 case ARRAY_RANGE_REF:
14031 case REALPART_EXPR:
14032 case IMAGPART_EXPR:
14033 case COMPONENT_REF:
14034 ret = gimplify_compound_lval (expr_p, pre_p, post_p,
14035 fallback ? fallback : fb_rvalue);
14036 break;
14038 case COND_EXPR:
14039 ret = gimplify_cond_expr (expr_p, pre_p, fallback);
14041 /* C99 code may assign to an array in a structure value of a
14042 conditional expression, and this has undefined behavior
14043 only on execution, so create a temporary if an lvalue is
14044 required. */
14045 if (fallback == fb_lvalue)
14047 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
14048 mark_addressable (*expr_p);
14049 ret = GS_OK;
14051 break;
14053 case CALL_EXPR:
14054 ret = gimplify_call_expr (expr_p, pre_p, fallback != fb_none);
14056 /* C99 code may assign to an array in a structure returned
14057 from a function, and this has undefined behavior only on
14058 execution, so create a temporary if an lvalue is
14059 required. */
14060 if (fallback == fb_lvalue)
14062 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
14063 mark_addressable (*expr_p);
14064 ret = GS_OK;
14066 break;
14068 case TREE_LIST:
14069 gcc_unreachable ();
14071 case COMPOUND_EXPR:
14072 ret = gimplify_compound_expr (expr_p, pre_p, fallback != fb_none);
14073 break;
14075 case COMPOUND_LITERAL_EXPR:
14076 ret = gimplify_compound_literal_expr (expr_p, pre_p,
14077 gimple_test_f, fallback);
14078 break;
14080 case MODIFY_EXPR:
14081 case INIT_EXPR:
14082 ret = gimplify_modify_expr (expr_p, pre_p, post_p,
14083 fallback != fb_none);
14084 break;
14086 case TRUTH_ANDIF_EXPR:
14087 case TRUTH_ORIF_EXPR:
14089 /* Preserve the original type of the expression and the
14090 source location of the outer expression. */
14091 tree org_type = TREE_TYPE (*expr_p);
14092 *expr_p = gimple_boolify (*expr_p);
14093 *expr_p = build3_loc (input_location, COND_EXPR,
14094 org_type, *expr_p,
14095 fold_convert_loc
14096 (input_location,
14097 org_type, boolean_true_node),
14098 fold_convert_loc
14099 (input_location,
14100 org_type, boolean_false_node));
14101 ret = GS_OK;
14102 break;
14105 case TRUTH_NOT_EXPR:
14107 tree type = TREE_TYPE (*expr_p);
14108 /* The parsers are careful to generate TRUTH_NOT_EXPR
14109 only with operands that are always zero or one.
14110 We do not fold here but handle the only interesting case
14111 manually, as fold may re-introduce the TRUTH_NOT_EXPR. */
14112 *expr_p = gimple_boolify (*expr_p);
14113 if (TYPE_PRECISION (TREE_TYPE (*expr_p)) == 1)
14114 *expr_p = build1_loc (input_location, BIT_NOT_EXPR,
14115 TREE_TYPE (*expr_p),
14116 TREE_OPERAND (*expr_p, 0));
14117 else
14118 *expr_p = build2_loc (input_location, BIT_XOR_EXPR,
14119 TREE_TYPE (*expr_p),
14120 TREE_OPERAND (*expr_p, 0),
14121 build_int_cst (TREE_TYPE (*expr_p), 1));
14122 if (!useless_type_conversion_p (type, TREE_TYPE (*expr_p)))
14123 *expr_p = fold_convert_loc (input_location, type, *expr_p);
14124 ret = GS_OK;
14125 break;
14128 case ADDR_EXPR:
14129 ret = gimplify_addr_expr (expr_p, pre_p, post_p);
14130 break;
14132 case ANNOTATE_EXPR:
14134 tree cond = TREE_OPERAND (*expr_p, 0);
14135 tree kind = TREE_OPERAND (*expr_p, 1);
14136 tree data = TREE_OPERAND (*expr_p, 2);
14137 tree type = TREE_TYPE (cond);
14138 if (!INTEGRAL_TYPE_P (type))
14140 *expr_p = cond;
14141 ret = GS_OK;
14142 break;
14144 tree tmp = create_tmp_var (type);
14145 gimplify_arg (&cond, pre_p, EXPR_LOCATION (*expr_p));
14146 gcall *call
14147 = gimple_build_call_internal (IFN_ANNOTATE, 3, cond, kind, data);
14148 gimple_call_set_lhs (call, tmp);
14149 gimplify_seq_add_stmt (pre_p, call);
14150 *expr_p = tmp;
14151 ret = GS_ALL_DONE;
14152 break;
14155 case VA_ARG_EXPR:
14156 ret = gimplify_va_arg_expr (expr_p, pre_p, post_p);
14157 break;
14159 CASE_CONVERT:
14160 if (IS_EMPTY_STMT (*expr_p))
14162 ret = GS_ALL_DONE;
14163 break;
14166 if (VOID_TYPE_P (TREE_TYPE (*expr_p))
14167 || fallback == fb_none)
14169 /* Just strip a conversion to void (or in void context) and
14170 try again. */
14171 *expr_p = TREE_OPERAND (*expr_p, 0);
14172 ret = GS_OK;
14173 break;
14176 ret = gimplify_conversion (expr_p);
14177 if (ret == GS_ERROR)
14178 break;
14179 if (*expr_p != save_expr)
14180 break;
14181 /* FALLTHRU */
14183 case FIX_TRUNC_EXPR:
14184 /* unary_expr: ... | '(' cast ')' val | ... */
14185 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
14186 is_gimple_val, fb_rvalue);
14187 recalculate_side_effects (*expr_p);
14188 break;
14190 case INDIRECT_REF:
14192 bool volatilep = TREE_THIS_VOLATILE (*expr_p);
14193 bool notrap = TREE_THIS_NOTRAP (*expr_p);
14194 tree saved_ptr_type = TREE_TYPE (TREE_OPERAND (*expr_p, 0));
14196 *expr_p = fold_indirect_ref_loc (input_location, *expr_p);
14197 if (*expr_p != save_expr)
14199 ret = GS_OK;
14200 break;
14203 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
14204 is_gimple_reg, fb_rvalue);
14205 if (ret == GS_ERROR)
14206 break;
14208 recalculate_side_effects (*expr_p);
14209 *expr_p = fold_build2_loc (input_location, MEM_REF,
14210 TREE_TYPE (*expr_p),
14211 TREE_OPERAND (*expr_p, 0),
14212 build_int_cst (saved_ptr_type, 0));
14213 TREE_THIS_VOLATILE (*expr_p) = volatilep;
14214 TREE_THIS_NOTRAP (*expr_p) = notrap;
14215 ret = GS_OK;
14216 break;
14219 /* We arrive here through the various re-gimplifcation paths. */
14220 case MEM_REF:
14221 /* First try re-folding the whole thing. */
14222 tmp = fold_binary (MEM_REF, TREE_TYPE (*expr_p),
14223 TREE_OPERAND (*expr_p, 0),
14224 TREE_OPERAND (*expr_p, 1));
14225 if (tmp)
14227 REF_REVERSE_STORAGE_ORDER (tmp)
14228 = REF_REVERSE_STORAGE_ORDER (*expr_p);
14229 *expr_p = tmp;
14230 recalculate_side_effects (*expr_p);
14231 ret = GS_OK;
14232 break;
14234 /* Avoid re-gimplifying the address operand if it is already
14235 in suitable form. Re-gimplifying would mark the address
14236 operand addressable. Always gimplify when not in SSA form
14237 as we still may have to gimplify decls with value-exprs. */
14238 if (!gimplify_ctxp || !gimple_in_ssa_p (cfun)
14239 || !is_gimple_mem_ref_addr (TREE_OPERAND (*expr_p, 0)))
14241 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
14242 is_gimple_mem_ref_addr, fb_rvalue);
14243 if (ret == GS_ERROR)
14244 break;
14246 recalculate_side_effects (*expr_p);
14247 ret = GS_ALL_DONE;
14248 break;
14250 /* Constants need not be gimplified. */
14251 case INTEGER_CST:
14252 case REAL_CST:
14253 case FIXED_CST:
14254 case STRING_CST:
14255 case COMPLEX_CST:
14256 case VECTOR_CST:
14257 /* Drop the overflow flag on constants, we do not want
14258 that in the GIMPLE IL. */
14259 if (TREE_OVERFLOW_P (*expr_p))
14260 *expr_p = drop_tree_overflow (*expr_p);
14261 ret = GS_ALL_DONE;
14262 break;
14264 case CONST_DECL:
14265 /* If we require an lvalue, such as for ADDR_EXPR, retain the
14266 CONST_DECL node. Otherwise the decl is replaceable by its
14267 value. */
14268 /* ??? Should be == fb_lvalue, but ADDR_EXPR passes fb_either. */
14269 if (fallback & fb_lvalue)
14270 ret = GS_ALL_DONE;
14271 else
14273 *expr_p = DECL_INITIAL (*expr_p);
14274 ret = GS_OK;
14276 break;
14278 case DECL_EXPR:
14279 ret = gimplify_decl_expr (expr_p, pre_p);
14280 break;
14282 case BIND_EXPR:
14283 ret = gimplify_bind_expr (expr_p, pre_p);
14284 break;
14286 case LOOP_EXPR:
14287 ret = gimplify_loop_expr (expr_p, pre_p);
14288 break;
14290 case SWITCH_EXPR:
14291 ret = gimplify_switch_expr (expr_p, pre_p);
14292 break;
14294 case EXIT_EXPR:
14295 ret = gimplify_exit_expr (expr_p);
14296 break;
14298 case GOTO_EXPR:
14299 /* If the target is not LABEL, then it is a computed jump
14300 and the target needs to be gimplified. */
14301 if (TREE_CODE (GOTO_DESTINATION (*expr_p)) != LABEL_DECL)
14303 ret = gimplify_expr (&GOTO_DESTINATION (*expr_p), pre_p,
14304 NULL, is_gimple_val, fb_rvalue);
14305 if (ret == GS_ERROR)
14306 break;
14308 gimplify_seq_add_stmt (pre_p,
14309 gimple_build_goto (GOTO_DESTINATION (*expr_p)));
14310 ret = GS_ALL_DONE;
14311 break;
14313 case PREDICT_EXPR:
14314 gimplify_seq_add_stmt (pre_p,
14315 gimple_build_predict (PREDICT_EXPR_PREDICTOR (*expr_p),
14316 PREDICT_EXPR_OUTCOME (*expr_p)));
14317 ret = GS_ALL_DONE;
14318 break;
14320 case LABEL_EXPR:
14321 ret = gimplify_label_expr (expr_p, pre_p);
14322 label = LABEL_EXPR_LABEL (*expr_p);
14323 gcc_assert (decl_function_context (label) == current_function_decl);
14325 /* If the label is used in a goto statement, or address of the label
14326 is taken, we need to unpoison all variables that were seen so far.
14327 Doing so would prevent us from reporting a false positives. */
14328 if (asan_poisoned_variables
14329 && asan_used_labels != NULL
14330 && asan_used_labels->contains (label))
14331 asan_poison_variables (asan_poisoned_variables, false, pre_p);
14332 break;
14334 case CASE_LABEL_EXPR:
14335 ret = gimplify_case_label_expr (expr_p, pre_p);
14337 if (gimplify_ctxp->live_switch_vars)
14338 asan_poison_variables (gimplify_ctxp->live_switch_vars, false,
14339 pre_p);
14340 break;
14342 case RETURN_EXPR:
14343 ret = gimplify_return_expr (*expr_p, pre_p);
14344 break;
14346 case CONSTRUCTOR:
14347 /* Don't reduce this in place; let gimplify_init_constructor work its
14348 magic. Buf if we're just elaborating this for side effects, just
14349 gimplify any element that has side-effects. */
14350 if (fallback == fb_none)
14352 unsigned HOST_WIDE_INT ix;
14353 tree val;
14354 tree temp = NULL_TREE;
14355 FOR_EACH_CONSTRUCTOR_VALUE (CONSTRUCTOR_ELTS (*expr_p), ix, val)
14356 if (TREE_SIDE_EFFECTS (val))
14357 append_to_statement_list (val, &temp);
14359 *expr_p = temp;
14360 ret = temp ? GS_OK : GS_ALL_DONE;
14362 /* C99 code may assign to an array in a constructed
14363 structure or union, and this has undefined behavior only
14364 on execution, so create a temporary if an lvalue is
14365 required. */
14366 else if (fallback == fb_lvalue)
14368 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, post_p, false);
14369 mark_addressable (*expr_p);
14370 ret = GS_OK;
14372 else
14373 ret = GS_ALL_DONE;
14374 break;
14376 /* The following are special cases that are not handled by the
14377 original GIMPLE grammar. */
14379 /* SAVE_EXPR nodes are converted into a GIMPLE identifier and
14380 eliminated. */
14381 case SAVE_EXPR:
14382 ret = gimplify_save_expr (expr_p, pre_p, post_p);
14383 break;
14385 case BIT_FIELD_REF:
14386 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
14387 post_p, is_gimple_lvalue, fb_either);
14388 recalculate_side_effects (*expr_p);
14389 break;
14391 case TARGET_MEM_REF:
14393 enum gimplify_status r0 = GS_ALL_DONE, r1 = GS_ALL_DONE;
14395 if (TMR_BASE (*expr_p))
14396 r0 = gimplify_expr (&TMR_BASE (*expr_p), pre_p,
14397 post_p, is_gimple_mem_ref_addr, fb_either);
14398 if (TMR_INDEX (*expr_p))
14399 r1 = gimplify_expr (&TMR_INDEX (*expr_p), pre_p,
14400 post_p, is_gimple_val, fb_rvalue);
14401 if (TMR_INDEX2 (*expr_p))
14402 r1 = gimplify_expr (&TMR_INDEX2 (*expr_p), pre_p,
14403 post_p, is_gimple_val, fb_rvalue);
14404 /* TMR_STEP and TMR_OFFSET are always integer constants. */
14405 ret = MIN (r0, r1);
14407 break;
14409 case NON_LVALUE_EXPR:
14410 /* This should have been stripped above. */
14411 gcc_unreachable ();
14413 case ASM_EXPR:
14414 ret = gimplify_asm_expr (expr_p, pre_p, post_p);
14415 break;
14417 case TRY_FINALLY_EXPR:
14418 case TRY_CATCH_EXPR:
14420 gimple_seq eval, cleanup;
14421 gtry *try_;
14423 /* Calls to destructors are generated automatically in FINALLY/CATCH
14424 block. They should have location as UNKNOWN_LOCATION. However,
14425 gimplify_call_expr will reset these call stmts to input_location
14426 if it finds stmt's location is unknown. To prevent resetting for
14427 destructors, we set the input_location to unknown.
14428 Note that this only affects the destructor calls in FINALLY/CATCH
14429 block, and will automatically reset to its original value by the
14430 end of gimplify_expr. */
14431 input_location = UNKNOWN_LOCATION;
14432 eval = cleanup = NULL;
14433 gimplify_and_add (TREE_OPERAND (*expr_p, 0), &eval);
14434 if (TREE_CODE (*expr_p) == TRY_FINALLY_EXPR
14435 && TREE_CODE (TREE_OPERAND (*expr_p, 1)) == EH_ELSE_EXPR)
14437 gimple_seq n = NULL, e = NULL;
14438 gimplify_and_add (TREE_OPERAND (TREE_OPERAND (*expr_p, 1),
14439 0), &n);
14440 gimplify_and_add (TREE_OPERAND (TREE_OPERAND (*expr_p, 1),
14441 1), &e);
14442 if (!gimple_seq_empty_p (n) && !gimple_seq_empty_p (e))
14444 geh_else *stmt = gimple_build_eh_else (n, e);
14445 gimple_seq_add_stmt (&cleanup, stmt);
14448 else
14449 gimplify_and_add (TREE_OPERAND (*expr_p, 1), &cleanup);
14450 /* Don't create bogus GIMPLE_TRY with empty cleanup. */
14451 if (gimple_seq_empty_p (cleanup))
14453 gimple_seq_add_seq (pre_p, eval);
14454 ret = GS_ALL_DONE;
14455 break;
14457 try_ = gimple_build_try (eval, cleanup,
14458 TREE_CODE (*expr_p) == TRY_FINALLY_EXPR
14459 ? GIMPLE_TRY_FINALLY
14460 : GIMPLE_TRY_CATCH);
14461 if (EXPR_HAS_LOCATION (save_expr))
14462 gimple_set_location (try_, EXPR_LOCATION (save_expr));
14463 else if (LOCATION_LOCUS (saved_location) != UNKNOWN_LOCATION)
14464 gimple_set_location (try_, saved_location);
14465 if (TREE_CODE (*expr_p) == TRY_CATCH_EXPR)
14466 gimple_try_set_catch_is_cleanup (try_,
14467 TRY_CATCH_IS_CLEANUP (*expr_p));
14468 gimplify_seq_add_stmt (pre_p, try_);
14469 ret = GS_ALL_DONE;
14470 break;
14473 case CLEANUP_POINT_EXPR:
14474 ret = gimplify_cleanup_point_expr (expr_p, pre_p);
14475 break;
14477 case TARGET_EXPR:
14478 ret = gimplify_target_expr (expr_p, pre_p, post_p);
14479 break;
14481 case CATCH_EXPR:
14483 gimple *c;
14484 gimple_seq handler = NULL;
14485 gimplify_and_add (CATCH_BODY (*expr_p), &handler);
14486 c = gimple_build_catch (CATCH_TYPES (*expr_p), handler);
14487 gimplify_seq_add_stmt (pre_p, c);
14488 ret = GS_ALL_DONE;
14489 break;
14492 case EH_FILTER_EXPR:
14494 gimple *ehf;
14495 gimple_seq failure = NULL;
14497 gimplify_and_add (EH_FILTER_FAILURE (*expr_p), &failure);
14498 ehf = gimple_build_eh_filter (EH_FILTER_TYPES (*expr_p), failure);
14499 gimple_set_no_warning (ehf, TREE_NO_WARNING (*expr_p));
14500 gimplify_seq_add_stmt (pre_p, ehf);
14501 ret = GS_ALL_DONE;
14502 break;
14505 case OBJ_TYPE_REF:
14507 enum gimplify_status r0, r1;
14508 r0 = gimplify_expr (&OBJ_TYPE_REF_OBJECT (*expr_p), pre_p,
14509 post_p, is_gimple_val, fb_rvalue);
14510 r1 = gimplify_expr (&OBJ_TYPE_REF_EXPR (*expr_p), pre_p,
14511 post_p, is_gimple_val, fb_rvalue);
14512 TREE_SIDE_EFFECTS (*expr_p) = 0;
14513 ret = MIN (r0, r1);
14515 break;
14517 case LABEL_DECL:
14518 /* We get here when taking the address of a label. We mark
14519 the label as "forced"; meaning it can never be removed and
14520 it is a potential target for any computed goto. */
14521 FORCED_LABEL (*expr_p) = 1;
14522 ret = GS_ALL_DONE;
14523 break;
14525 case STATEMENT_LIST:
14526 ret = gimplify_statement_list (expr_p, pre_p);
14527 break;
14529 case WITH_SIZE_EXPR:
14531 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
14532 post_p == &internal_post ? NULL : post_p,
14533 gimple_test_f, fallback);
14534 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
14535 is_gimple_val, fb_rvalue);
14536 ret = GS_ALL_DONE;
14538 break;
14540 case VAR_DECL:
14541 case PARM_DECL:
14542 ret = gimplify_var_or_parm_decl (expr_p);
14543 break;
14545 case RESULT_DECL:
14546 /* When within an OMP context, notice uses of variables. */
14547 if (gimplify_omp_ctxp)
14548 omp_notice_variable (gimplify_omp_ctxp, *expr_p, true);
14549 ret = GS_ALL_DONE;
14550 break;
14552 case DEBUG_EXPR_DECL:
14553 gcc_unreachable ();
14555 case DEBUG_BEGIN_STMT:
14556 gimplify_seq_add_stmt (pre_p,
14557 gimple_build_debug_begin_stmt
14558 (TREE_BLOCK (*expr_p),
14559 EXPR_LOCATION (*expr_p)));
14560 ret = GS_ALL_DONE;
14561 *expr_p = NULL;
14562 break;
14564 case SSA_NAME:
14565 /* Allow callbacks into the gimplifier during optimization. */
14566 ret = GS_ALL_DONE;
14567 break;
14569 case OMP_PARALLEL:
14570 gimplify_omp_parallel (expr_p, pre_p);
14571 ret = GS_ALL_DONE;
14572 break;
14574 case OMP_TASK:
14575 gimplify_omp_task (expr_p, pre_p);
14576 ret = GS_ALL_DONE;
14577 break;
14579 case OMP_FOR:
14580 case OMP_SIMD:
14581 case OMP_DISTRIBUTE:
14582 case OMP_TASKLOOP:
14583 case OACC_LOOP:
14584 ret = gimplify_omp_for (expr_p, pre_p);
14585 break;
14587 case OMP_LOOP:
14588 ret = gimplify_omp_loop (expr_p, pre_p);
14589 break;
14591 case OACC_CACHE:
14592 gimplify_oacc_cache (expr_p, pre_p);
14593 ret = GS_ALL_DONE;
14594 break;
14596 case OACC_DECLARE:
14597 gimplify_oacc_declare (expr_p, pre_p);
14598 ret = GS_ALL_DONE;
14599 break;
14601 case OACC_HOST_DATA:
14602 case OACC_DATA:
14603 case OACC_KERNELS:
14604 case OACC_PARALLEL:
14605 case OACC_SERIAL:
14606 case OMP_SECTIONS:
14607 case OMP_SINGLE:
14608 case OMP_TARGET:
14609 case OMP_TARGET_DATA:
14610 case OMP_TEAMS:
14611 gimplify_omp_workshare (expr_p, pre_p);
14612 ret = GS_ALL_DONE;
14613 break;
14615 case OACC_ENTER_DATA:
14616 case OACC_EXIT_DATA:
14617 case OACC_UPDATE:
14618 case OMP_TARGET_UPDATE:
14619 case OMP_TARGET_ENTER_DATA:
14620 case OMP_TARGET_EXIT_DATA:
14621 gimplify_omp_target_update (expr_p, pre_p);
14622 ret = GS_ALL_DONE;
14623 break;
14625 case OMP_SECTION:
14626 case OMP_MASTER:
14627 case OMP_ORDERED:
14628 case OMP_CRITICAL:
14629 case OMP_SCAN:
14631 gimple_seq body = NULL;
14632 gimple *g;
14633 bool saved_in_omp_construct = in_omp_construct;
14635 in_omp_construct = true;
14636 gimplify_and_add (OMP_BODY (*expr_p), &body);
14637 in_omp_construct = saved_in_omp_construct;
14638 switch (TREE_CODE (*expr_p))
14640 case OMP_SECTION:
14641 g = gimple_build_omp_section (body);
14642 break;
14643 case OMP_MASTER:
14644 g = gimple_build_omp_master (body);
14645 break;
14646 case OMP_ORDERED:
14647 g = gimplify_omp_ordered (*expr_p, body);
14648 break;
14649 case OMP_CRITICAL:
14650 gimplify_scan_omp_clauses (&OMP_CRITICAL_CLAUSES (*expr_p),
14651 pre_p, ORT_WORKSHARE, OMP_CRITICAL);
14652 gimplify_adjust_omp_clauses (pre_p, body,
14653 &OMP_CRITICAL_CLAUSES (*expr_p),
14654 OMP_CRITICAL);
14655 g = gimple_build_omp_critical (body,
14656 OMP_CRITICAL_NAME (*expr_p),
14657 OMP_CRITICAL_CLAUSES (*expr_p));
14658 break;
14659 case OMP_SCAN:
14660 gimplify_scan_omp_clauses (&OMP_SCAN_CLAUSES (*expr_p),
14661 pre_p, ORT_WORKSHARE, OMP_SCAN);
14662 gimplify_adjust_omp_clauses (pre_p, body,
14663 &OMP_SCAN_CLAUSES (*expr_p),
14664 OMP_SCAN);
14665 g = gimple_build_omp_scan (body, OMP_SCAN_CLAUSES (*expr_p));
14666 break;
14667 default:
14668 gcc_unreachable ();
14670 gimplify_seq_add_stmt (pre_p, g);
14671 ret = GS_ALL_DONE;
14672 break;
14675 case OMP_TASKGROUP:
14677 gimple_seq body = NULL;
14679 tree *pclauses = &OMP_TASKGROUP_CLAUSES (*expr_p);
14680 bool saved_in_omp_construct = in_omp_construct;
14681 gimplify_scan_omp_clauses (pclauses, pre_p, ORT_TASKGROUP,
14682 OMP_TASKGROUP);
14683 gimplify_adjust_omp_clauses (pre_p, NULL, pclauses, OMP_TASKGROUP);
14685 in_omp_construct = true;
14686 gimplify_and_add (OMP_BODY (*expr_p), &body);
14687 in_omp_construct = saved_in_omp_construct;
14688 gimple_seq cleanup = NULL;
14689 tree fn = builtin_decl_explicit (BUILT_IN_GOMP_TASKGROUP_END);
14690 gimple *g = gimple_build_call (fn, 0);
14691 gimple_seq_add_stmt (&cleanup, g);
14692 g = gimple_build_try (body, cleanup, GIMPLE_TRY_FINALLY);
14693 body = NULL;
14694 gimple_seq_add_stmt (&body, g);
14695 g = gimple_build_omp_taskgroup (body, *pclauses);
14696 gimplify_seq_add_stmt (pre_p, g);
14697 ret = GS_ALL_DONE;
14698 break;
14701 case OMP_ATOMIC:
14702 case OMP_ATOMIC_READ:
14703 case OMP_ATOMIC_CAPTURE_OLD:
14704 case OMP_ATOMIC_CAPTURE_NEW:
14705 ret = gimplify_omp_atomic (expr_p, pre_p);
14706 break;
14708 case TRANSACTION_EXPR:
14709 ret = gimplify_transaction (expr_p, pre_p);
14710 break;
14712 case TRUTH_AND_EXPR:
14713 case TRUTH_OR_EXPR:
14714 case TRUTH_XOR_EXPR:
14716 tree orig_type = TREE_TYPE (*expr_p);
14717 tree new_type, xop0, xop1;
14718 *expr_p = gimple_boolify (*expr_p);
14719 new_type = TREE_TYPE (*expr_p);
14720 if (!useless_type_conversion_p (orig_type, new_type))
14722 *expr_p = fold_convert_loc (input_location, orig_type, *expr_p);
14723 ret = GS_OK;
14724 break;
14727 /* Boolified binary truth expressions are semantically equivalent
14728 to bitwise binary expressions. Canonicalize them to the
14729 bitwise variant. */
14730 switch (TREE_CODE (*expr_p))
14732 case TRUTH_AND_EXPR:
14733 TREE_SET_CODE (*expr_p, BIT_AND_EXPR);
14734 break;
14735 case TRUTH_OR_EXPR:
14736 TREE_SET_CODE (*expr_p, BIT_IOR_EXPR);
14737 break;
14738 case TRUTH_XOR_EXPR:
14739 TREE_SET_CODE (*expr_p, BIT_XOR_EXPR);
14740 break;
14741 default:
14742 break;
14744 /* Now make sure that operands have compatible type to
14745 expression's new_type. */
14746 xop0 = TREE_OPERAND (*expr_p, 0);
14747 xop1 = TREE_OPERAND (*expr_p, 1);
14748 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop0)))
14749 TREE_OPERAND (*expr_p, 0) = fold_convert_loc (input_location,
14750 new_type,
14751 xop0);
14752 if (!useless_type_conversion_p (new_type, TREE_TYPE (xop1)))
14753 TREE_OPERAND (*expr_p, 1) = fold_convert_loc (input_location,
14754 new_type,
14755 xop1);
14756 /* Continue classified as tcc_binary. */
14757 goto expr_2;
14760 case VEC_COND_EXPR:
14761 goto expr_3;
14763 case VEC_PERM_EXPR:
14764 /* Classified as tcc_expression. */
14765 goto expr_3;
14767 case BIT_INSERT_EXPR:
14768 /* Argument 3 is a constant. */
14769 goto expr_2;
14771 case POINTER_PLUS_EXPR:
14773 enum gimplify_status r0, r1;
14774 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
14775 post_p, is_gimple_val, fb_rvalue);
14776 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
14777 post_p, is_gimple_val, fb_rvalue);
14778 recalculate_side_effects (*expr_p);
14779 ret = MIN (r0, r1);
14780 break;
14783 default:
14784 switch (TREE_CODE_CLASS (TREE_CODE (*expr_p)))
14786 case tcc_comparison:
14787 /* Handle comparison of objects of non scalar mode aggregates
14788 with a call to memcmp. It would be nice to only have to do
14789 this for variable-sized objects, but then we'd have to allow
14790 the same nest of reference nodes we allow for MODIFY_EXPR and
14791 that's too complex.
14793 Compare scalar mode aggregates as scalar mode values. Using
14794 memcmp for them would be very inefficient at best, and is
14795 plain wrong if bitfields are involved. */
14797 tree type = TREE_TYPE (TREE_OPERAND (*expr_p, 1));
14799 /* Vector comparisons need no boolification. */
14800 if (TREE_CODE (type) == VECTOR_TYPE)
14801 goto expr_2;
14802 else if (!AGGREGATE_TYPE_P (type))
14804 tree org_type = TREE_TYPE (*expr_p);
14805 *expr_p = gimple_boolify (*expr_p);
14806 if (!useless_type_conversion_p (org_type,
14807 TREE_TYPE (*expr_p)))
14809 *expr_p = fold_convert_loc (input_location,
14810 org_type, *expr_p);
14811 ret = GS_OK;
14813 else
14814 goto expr_2;
14816 else if (TYPE_MODE (type) != BLKmode)
14817 ret = gimplify_scalar_mode_aggregate_compare (expr_p);
14818 else
14819 ret = gimplify_variable_sized_compare (expr_p);
14821 break;
14824 /* If *EXPR_P does not need to be special-cased, handle it
14825 according to its class. */
14826 case tcc_unary:
14827 ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
14828 post_p, is_gimple_val, fb_rvalue);
14829 break;
14831 case tcc_binary:
14832 expr_2:
14834 enum gimplify_status r0, r1;
14836 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
14837 post_p, is_gimple_val, fb_rvalue);
14838 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
14839 post_p, is_gimple_val, fb_rvalue);
14841 ret = MIN (r0, r1);
14842 break;
14845 expr_3:
14847 enum gimplify_status r0, r1, r2;
14849 r0 = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p,
14850 post_p, is_gimple_val, fb_rvalue);
14851 r1 = gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p,
14852 post_p, is_gimple_val, fb_rvalue);
14853 r2 = gimplify_expr (&TREE_OPERAND (*expr_p, 2), pre_p,
14854 post_p, is_gimple_val, fb_rvalue);
14856 ret = MIN (MIN (r0, r1), r2);
14857 break;
14860 case tcc_declaration:
14861 case tcc_constant:
14862 ret = GS_ALL_DONE;
14863 goto dont_recalculate;
14865 default:
14866 gcc_unreachable ();
14869 recalculate_side_effects (*expr_p);
14871 dont_recalculate:
14872 break;
14875 gcc_assert (*expr_p || ret != GS_OK);
14877 while (ret == GS_OK);
14879 /* If we encountered an error_mark somewhere nested inside, either
14880 stub out the statement or propagate the error back out. */
14881 if (ret == GS_ERROR)
14883 if (is_statement)
14884 *expr_p = NULL;
14885 goto out;
14888 /* This was only valid as a return value from the langhook, which
14889 we handled. Make sure it doesn't escape from any other context. */
14890 gcc_assert (ret != GS_UNHANDLED);
14892 if (fallback == fb_none && *expr_p && !is_gimple_stmt (*expr_p))
14894 /* We aren't looking for a value, and we don't have a valid
14895 statement. If it doesn't have side-effects, throw it away.
14896 We can also get here with code such as "*&&L;", where L is
14897 a LABEL_DECL that is marked as FORCED_LABEL. */
14898 if (TREE_CODE (*expr_p) == LABEL_DECL
14899 || !TREE_SIDE_EFFECTS (*expr_p))
14900 *expr_p = NULL;
14901 else if (!TREE_THIS_VOLATILE (*expr_p))
14903 /* This is probably a _REF that contains something nested that
14904 has side effects. Recurse through the operands to find it. */
14905 enum tree_code code = TREE_CODE (*expr_p);
14907 switch (code)
14909 case COMPONENT_REF:
14910 case REALPART_EXPR:
14911 case IMAGPART_EXPR:
14912 case VIEW_CONVERT_EXPR:
14913 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
14914 gimple_test_f, fallback);
14915 break;
14917 case ARRAY_REF:
14918 case ARRAY_RANGE_REF:
14919 gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
14920 gimple_test_f, fallback);
14921 gimplify_expr (&TREE_OPERAND (*expr_p, 1), pre_p, post_p,
14922 gimple_test_f, fallback);
14923 break;
14925 default:
14926 /* Anything else with side-effects must be converted to
14927 a valid statement before we get here. */
14928 gcc_unreachable ();
14931 *expr_p = NULL;
14933 else if (COMPLETE_TYPE_P (TREE_TYPE (*expr_p))
14934 && TYPE_MODE (TREE_TYPE (*expr_p)) != BLKmode)
14936 /* Historically, the compiler has treated a bare reference
14937 to a non-BLKmode volatile lvalue as forcing a load. */
14938 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (*expr_p));
14940 /* Normally, we do not want to create a temporary for a
14941 TREE_ADDRESSABLE type because such a type should not be
14942 copied by bitwise-assignment. However, we make an
14943 exception here, as all we are doing here is ensuring that
14944 we read the bytes that make up the type. We use
14945 create_tmp_var_raw because create_tmp_var will abort when
14946 given a TREE_ADDRESSABLE type. */
14947 tree tmp = create_tmp_var_raw (type, "vol");
14948 gimple_add_tmp_var (tmp);
14949 gimplify_assign (tmp, *expr_p, pre_p);
14950 *expr_p = NULL;
14952 else
14953 /* We can't do anything useful with a volatile reference to
14954 an incomplete type, so just throw it away. Likewise for
14955 a BLKmode type, since any implicit inner load should
14956 already have been turned into an explicit one by the
14957 gimplification process. */
14958 *expr_p = NULL;
14961 /* If we are gimplifying at the statement level, we're done. Tack
14962 everything together and return. */
14963 if (fallback == fb_none || is_statement)
14965 /* Since *EXPR_P has been converted into a GIMPLE tuple, clear
14966 it out for GC to reclaim it. */
14967 *expr_p = NULL_TREE;
14969 if (!gimple_seq_empty_p (internal_pre)
14970 || !gimple_seq_empty_p (internal_post))
14972 gimplify_seq_add_seq (&internal_pre, internal_post);
14973 gimplify_seq_add_seq (pre_p, internal_pre);
14976 /* The result of gimplifying *EXPR_P is going to be the last few
14977 statements in *PRE_P and *POST_P. Add location information
14978 to all the statements that were added by the gimplification
14979 helpers. */
14980 if (!gimple_seq_empty_p (*pre_p))
14981 annotate_all_with_location_after (*pre_p, pre_last_gsi, input_location);
14983 if (!gimple_seq_empty_p (*post_p))
14984 annotate_all_with_location_after (*post_p, post_last_gsi,
14985 input_location);
14987 goto out;
14990 #ifdef ENABLE_GIMPLE_CHECKING
14991 if (*expr_p)
14993 enum tree_code code = TREE_CODE (*expr_p);
14994 /* These expressions should already be in gimple IR form. */
14995 gcc_assert (code != MODIFY_EXPR
14996 && code != ASM_EXPR
14997 && code != BIND_EXPR
14998 && code != CATCH_EXPR
14999 && (code != COND_EXPR || gimplify_ctxp->allow_rhs_cond_expr)
15000 && code != EH_FILTER_EXPR
15001 && code != GOTO_EXPR
15002 && code != LABEL_EXPR
15003 && code != LOOP_EXPR
15004 && code != SWITCH_EXPR
15005 && code != TRY_FINALLY_EXPR
15006 && code != EH_ELSE_EXPR
15007 && code != OACC_PARALLEL
15008 && code != OACC_KERNELS
15009 && code != OACC_SERIAL
15010 && code != OACC_DATA
15011 && code != OACC_HOST_DATA
15012 && code != OACC_DECLARE
15013 && code != OACC_UPDATE
15014 && code != OACC_ENTER_DATA
15015 && code != OACC_EXIT_DATA
15016 && code != OACC_CACHE
15017 && code != OMP_CRITICAL
15018 && code != OMP_FOR
15019 && code != OACC_LOOP
15020 && code != OMP_MASTER
15021 && code != OMP_TASKGROUP
15022 && code != OMP_ORDERED
15023 && code != OMP_PARALLEL
15024 && code != OMP_SCAN
15025 && code != OMP_SECTIONS
15026 && code != OMP_SECTION
15027 && code != OMP_SINGLE);
15029 #endif
15031 /* Otherwise we're gimplifying a subexpression, so the resulting
15032 value is interesting. If it's a valid operand that matches
15033 GIMPLE_TEST_F, we're done. Unless we are handling some
15034 post-effects internally; if that's the case, we need to copy into
15035 a temporary before adding the post-effects to POST_P. */
15036 if (gimple_seq_empty_p (internal_post) && (*gimple_test_f) (*expr_p))
15037 goto out;
15039 /* Otherwise, we need to create a new temporary for the gimplified
15040 expression. */
15042 /* We can't return an lvalue if we have an internal postqueue. The
15043 object the lvalue refers to would (probably) be modified by the
15044 postqueue; we need to copy the value out first, which means an
15045 rvalue. */
15046 if ((fallback & fb_lvalue)
15047 && gimple_seq_empty_p (internal_post)
15048 && is_gimple_addressable (*expr_p))
15050 /* An lvalue will do. Take the address of the expression, store it
15051 in a temporary, and replace the expression with an INDIRECT_REF of
15052 that temporary. */
15053 tree ref_alias_type = reference_alias_ptr_type (*expr_p);
15054 unsigned int ref_align = get_object_alignment (*expr_p);
15055 tree ref_type = TREE_TYPE (*expr_p);
15056 tmp = build_fold_addr_expr_loc (input_location, *expr_p);
15057 gimplify_expr (&tmp, pre_p, post_p, is_gimple_reg, fb_rvalue);
15058 if (TYPE_ALIGN (ref_type) != ref_align)
15059 ref_type = build_aligned_type (ref_type, ref_align);
15060 *expr_p = build2 (MEM_REF, ref_type,
15061 tmp, build_zero_cst (ref_alias_type));
15063 else if ((fallback & fb_rvalue) && is_gimple_reg_rhs_or_call (*expr_p))
15065 /* An rvalue will do. Assign the gimplified expression into a
15066 new temporary TMP and replace the original expression with
15067 TMP. First, make sure that the expression has a type so that
15068 it can be assigned into a temporary. */
15069 gcc_assert (!VOID_TYPE_P (TREE_TYPE (*expr_p)));
15070 *expr_p = get_formal_tmp_var (*expr_p, pre_p);
15072 else
15074 #ifdef ENABLE_GIMPLE_CHECKING
15075 if (!(fallback & fb_mayfail))
15077 fprintf (stderr, "gimplification failed:\n");
15078 print_generic_expr (stderr, *expr_p);
15079 debug_tree (*expr_p);
15080 internal_error ("gimplification failed");
15082 #endif
15083 gcc_assert (fallback & fb_mayfail);
15085 /* If this is an asm statement, and the user asked for the
15086 impossible, don't die. Fail and let gimplify_asm_expr
15087 issue an error. */
15088 ret = GS_ERROR;
15089 goto out;
15092 /* Make sure the temporary matches our predicate. */
15093 gcc_assert ((*gimple_test_f) (*expr_p));
15095 if (!gimple_seq_empty_p (internal_post))
15097 annotate_all_with_location (internal_post, input_location);
15098 gimplify_seq_add_seq (pre_p, internal_post);
15101 out:
15102 input_location = saved_location;
15103 return ret;
15106 /* Like gimplify_expr but make sure the gimplified result is not itself
15107 a SSA name (but a decl if it were). Temporaries required by
15108 evaluating *EXPR_P may be still SSA names. */
15110 static enum gimplify_status
15111 gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p,
15112 bool (*gimple_test_f) (tree), fallback_t fallback,
15113 bool allow_ssa)
15115 bool was_ssa_name_p = TREE_CODE (*expr_p) == SSA_NAME;
15116 enum gimplify_status ret = gimplify_expr (expr_p, pre_p, post_p,
15117 gimple_test_f, fallback);
15118 if (! allow_ssa
15119 && TREE_CODE (*expr_p) == SSA_NAME)
15121 tree name = *expr_p;
15122 if (was_ssa_name_p)
15123 *expr_p = get_initialized_tmp_var (*expr_p, pre_p, NULL, false);
15124 else
15126 /* Avoid the extra copy if possible. */
15127 *expr_p = create_tmp_reg (TREE_TYPE (name));
15128 if (!gimple_nop_p (SSA_NAME_DEF_STMT (name)))
15129 gimple_set_lhs (SSA_NAME_DEF_STMT (name), *expr_p);
15130 release_ssa_name (name);
15133 return ret;
15136 /* Look through TYPE for variable-sized objects and gimplify each such
15137 size that we find. Add to LIST_P any statements generated. */
15139 void
15140 gimplify_type_sizes (tree type, gimple_seq *list_p)
15142 tree field, t;
15144 if (type == NULL || type == error_mark_node)
15145 return;
15147 /* We first do the main variant, then copy into any other variants. */
15148 type = TYPE_MAIN_VARIANT (type);
15150 /* Avoid infinite recursion. */
15151 if (TYPE_SIZES_GIMPLIFIED (type))
15152 return;
15154 TYPE_SIZES_GIMPLIFIED (type) = 1;
15156 switch (TREE_CODE (type))
15158 case INTEGER_TYPE:
15159 case ENUMERAL_TYPE:
15160 case BOOLEAN_TYPE:
15161 case REAL_TYPE:
15162 case FIXED_POINT_TYPE:
15163 gimplify_one_sizepos (&TYPE_MIN_VALUE (type), list_p);
15164 gimplify_one_sizepos (&TYPE_MAX_VALUE (type), list_p);
15166 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
15168 TYPE_MIN_VALUE (t) = TYPE_MIN_VALUE (type);
15169 TYPE_MAX_VALUE (t) = TYPE_MAX_VALUE (type);
15171 break;
15173 case ARRAY_TYPE:
15174 /* These types may not have declarations, so handle them here. */
15175 gimplify_type_sizes (TREE_TYPE (type), list_p);
15176 gimplify_type_sizes (TYPE_DOMAIN (type), list_p);
15177 /* Ensure VLA bounds aren't removed, for -O0 they should be variables
15178 with assigned stack slots, for -O1+ -g they should be tracked
15179 by VTA. */
15180 if (!(TYPE_NAME (type)
15181 && TREE_CODE (TYPE_NAME (type)) == TYPE_DECL
15182 && DECL_IGNORED_P (TYPE_NAME (type)))
15183 && TYPE_DOMAIN (type)
15184 && INTEGRAL_TYPE_P (TYPE_DOMAIN (type)))
15186 t = TYPE_MIN_VALUE (TYPE_DOMAIN (type));
15187 if (t && VAR_P (t) && DECL_ARTIFICIAL (t))
15188 DECL_IGNORED_P (t) = 0;
15189 t = TYPE_MAX_VALUE (TYPE_DOMAIN (type));
15190 if (t && VAR_P (t) && DECL_ARTIFICIAL (t))
15191 DECL_IGNORED_P (t) = 0;
15193 break;
15195 case RECORD_TYPE:
15196 case UNION_TYPE:
15197 case QUAL_UNION_TYPE:
15198 for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
15199 if (TREE_CODE (field) == FIELD_DECL)
15201 gimplify_one_sizepos (&DECL_FIELD_OFFSET (field), list_p);
15202 gimplify_one_sizepos (&DECL_SIZE (field), list_p);
15203 gimplify_one_sizepos (&DECL_SIZE_UNIT (field), list_p);
15204 gimplify_type_sizes (TREE_TYPE (field), list_p);
15206 break;
15208 case POINTER_TYPE:
15209 case REFERENCE_TYPE:
15210 /* We used to recurse on the pointed-to type here, which turned out to
15211 be incorrect because its definition might refer to variables not
15212 yet initialized at this point if a forward declaration is involved.
15214 It was actually useful for anonymous pointed-to types to ensure
15215 that the sizes evaluation dominates every possible later use of the
15216 values. Restricting to such types here would be safe since there
15217 is no possible forward declaration around, but would introduce an
15218 undesirable middle-end semantic to anonymity. We then defer to
15219 front-ends the responsibility of ensuring that the sizes are
15220 evaluated both early and late enough, e.g. by attaching artificial
15221 type declarations to the tree. */
15222 break;
15224 default:
15225 break;
15228 gimplify_one_sizepos (&TYPE_SIZE (type), list_p);
15229 gimplify_one_sizepos (&TYPE_SIZE_UNIT (type), list_p);
15231 for (t = TYPE_NEXT_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
15233 TYPE_SIZE (t) = TYPE_SIZE (type);
15234 TYPE_SIZE_UNIT (t) = TYPE_SIZE_UNIT (type);
15235 TYPE_SIZES_GIMPLIFIED (t) = 1;
15239 /* A subroutine of gimplify_type_sizes to make sure that *EXPR_P,
15240 a size or position, has had all of its SAVE_EXPRs evaluated.
15241 We add any required statements to *STMT_P. */
15243 void
15244 gimplify_one_sizepos (tree *expr_p, gimple_seq *stmt_p)
15246 tree expr = *expr_p;
15248 /* We don't do anything if the value isn't there, is constant, or contains
15249 A PLACEHOLDER_EXPR. We also don't want to do anything if it's already
15250 a VAR_DECL. If it's a VAR_DECL from another function, the gimplifier
15251 will want to replace it with a new variable, but that will cause problems
15252 if this type is from outside the function. It's OK to have that here. */
15253 if (expr == NULL_TREE
15254 || is_gimple_constant (expr)
15255 || TREE_CODE (expr) == VAR_DECL
15256 || CONTAINS_PLACEHOLDER_P (expr))
15257 return;
15259 *expr_p = unshare_expr (expr);
15261 /* SSA names in decl/type fields are a bad idea - they'll get reclaimed
15262 if the def vanishes. */
15263 gimplify_expr (expr_p, stmt_p, NULL, is_gimple_val, fb_rvalue, false);
15265 /* If expr wasn't already is_gimple_sizepos or is_gimple_constant from the
15266 FE, ensure that it is a VAR_DECL, otherwise we might handle some decls
15267 as gimplify_vla_decl even when they would have all sizes INTEGER_CSTs. */
15268 if (is_gimple_constant (*expr_p))
15269 *expr_p = get_initialized_tmp_var (*expr_p, stmt_p, NULL, false);
15272 /* Gimplify the body of statements of FNDECL and return a GIMPLE_BIND node
15273 containing the sequence of corresponding GIMPLE statements. If DO_PARMS
15274 is true, also gimplify the parameters. */
15276 gbind *
15277 gimplify_body (tree fndecl, bool do_parms)
15279 location_t saved_location = input_location;
15280 gimple_seq parm_stmts, parm_cleanup = NULL, seq;
15281 gimple *outer_stmt;
15282 gbind *outer_bind;
15284 timevar_push (TV_TREE_GIMPLIFY);
15286 init_tree_ssa (cfun);
15288 /* Initialize for optimize_insn_for_s{ize,peed}_p possibly called during
15289 gimplification. */
15290 default_rtl_profile ();
15292 gcc_assert (gimplify_ctxp == NULL);
15293 push_gimplify_context (true);
15295 if (flag_openacc || flag_openmp)
15297 gcc_assert (gimplify_omp_ctxp == NULL);
15298 if (lookup_attribute ("omp declare target", DECL_ATTRIBUTES (fndecl)))
15299 gimplify_omp_ctxp = new_omp_context (ORT_IMPLICIT_TARGET);
15302 /* Unshare most shared trees in the body and in that of any nested functions.
15303 It would seem we don't have to do this for nested functions because
15304 they are supposed to be output and then the outer function gimplified
15305 first, but the g++ front end doesn't always do it that way. */
15306 unshare_body (fndecl);
15307 unvisit_body (fndecl);
15309 /* Make sure input_location isn't set to something weird. */
15310 input_location = DECL_SOURCE_LOCATION (fndecl);
15312 /* Resolve callee-copies. This has to be done before processing
15313 the body so that DECL_VALUE_EXPR gets processed correctly. */
15314 parm_stmts = do_parms ? gimplify_parameters (&parm_cleanup) : NULL;
15316 /* Gimplify the function's body. */
15317 seq = NULL;
15318 gimplify_stmt (&DECL_SAVED_TREE (fndecl), &seq);
15319 outer_stmt = gimple_seq_first_nondebug_stmt (seq);
15320 if (!outer_stmt)
15322 outer_stmt = gimple_build_nop ();
15323 gimplify_seq_add_stmt (&seq, outer_stmt);
15326 /* The body must contain exactly one statement, a GIMPLE_BIND. If this is
15327 not the case, wrap everything in a GIMPLE_BIND to make it so. */
15328 if (gimple_code (outer_stmt) == GIMPLE_BIND
15329 && (gimple_seq_first_nondebug_stmt (seq)
15330 == gimple_seq_last_nondebug_stmt (seq)))
15332 outer_bind = as_a <gbind *> (outer_stmt);
15333 if (gimple_seq_first_stmt (seq) != outer_stmt
15334 || gimple_seq_last_stmt (seq) != outer_stmt)
15336 /* If there are debug stmts before or after outer_stmt, move them
15337 inside of outer_bind body. */
15338 gimple_stmt_iterator gsi = gsi_for_stmt (outer_stmt, &seq);
15339 gimple_seq second_seq = NULL;
15340 if (gimple_seq_first_stmt (seq) != outer_stmt
15341 && gimple_seq_last_stmt (seq) != outer_stmt)
15343 second_seq = gsi_split_seq_after (gsi);
15344 gsi_remove (&gsi, false);
15346 else if (gimple_seq_first_stmt (seq) != outer_stmt)
15347 gsi_remove (&gsi, false);
15348 else
15350 gsi_remove (&gsi, false);
15351 second_seq = seq;
15352 seq = NULL;
15354 gimple_seq_add_seq_without_update (&seq,
15355 gimple_bind_body (outer_bind));
15356 gimple_seq_add_seq_without_update (&seq, second_seq);
15357 gimple_bind_set_body (outer_bind, seq);
15360 else
15361 outer_bind = gimple_build_bind (NULL_TREE, seq, NULL);
15363 DECL_SAVED_TREE (fndecl) = NULL_TREE;
15365 /* If we had callee-copies statements, insert them at the beginning
15366 of the function and clear DECL_VALUE_EXPR_P on the parameters. */
15367 if (!gimple_seq_empty_p (parm_stmts))
15369 tree parm;
15371 gimplify_seq_add_seq (&parm_stmts, gimple_bind_body (outer_bind));
15372 if (parm_cleanup)
15374 gtry *g = gimple_build_try (parm_stmts, parm_cleanup,
15375 GIMPLE_TRY_FINALLY);
15376 parm_stmts = NULL;
15377 gimple_seq_add_stmt (&parm_stmts, g);
15379 gimple_bind_set_body (outer_bind, parm_stmts);
15381 for (parm = DECL_ARGUMENTS (current_function_decl);
15382 parm; parm = DECL_CHAIN (parm))
15383 if (DECL_HAS_VALUE_EXPR_P (parm))
15385 DECL_HAS_VALUE_EXPR_P (parm) = 0;
15386 DECL_IGNORED_P (parm) = 0;
15390 if ((flag_openacc || flag_openmp || flag_openmp_simd)
15391 && gimplify_omp_ctxp)
15393 delete_omp_context (gimplify_omp_ctxp);
15394 gimplify_omp_ctxp = NULL;
15397 pop_gimplify_context (outer_bind);
15398 gcc_assert (gimplify_ctxp == NULL);
15400 if (flag_checking && !seen_error ())
15401 verify_gimple_in_seq (gimple_bind_body (outer_bind));
15403 timevar_pop (TV_TREE_GIMPLIFY);
15404 input_location = saved_location;
15406 return outer_bind;
15409 typedef char *char_p; /* For DEF_VEC_P. */
15411 /* Return whether we should exclude FNDECL from instrumentation. */
15413 static bool
15414 flag_instrument_functions_exclude_p (tree fndecl)
15416 vec<char_p> *v;
15418 v = (vec<char_p> *) flag_instrument_functions_exclude_functions;
15419 if (v && v->length () > 0)
15421 const char *name;
15422 int i;
15423 char *s;
15425 name = lang_hooks.decl_printable_name (fndecl, 1);
15426 FOR_EACH_VEC_ELT (*v, i, s)
15427 if (strstr (name, s) != NULL)
15428 return true;
15431 v = (vec<char_p> *) flag_instrument_functions_exclude_files;
15432 if (v && v->length () > 0)
15434 const char *name;
15435 int i;
15436 char *s;
15438 name = DECL_SOURCE_FILE (fndecl);
15439 FOR_EACH_VEC_ELT (*v, i, s)
15440 if (strstr (name, s) != NULL)
15441 return true;
15444 return false;
15447 /* Entry point to the gimplification pass. FNDECL is the FUNCTION_DECL
15448 node for the function we want to gimplify.
15450 Return the sequence of GIMPLE statements corresponding to the body
15451 of FNDECL. */
15453 void
15454 gimplify_function_tree (tree fndecl)
15456 gimple_seq seq;
15457 gbind *bind;
15459 gcc_assert (!gimple_body (fndecl));
15461 if (DECL_STRUCT_FUNCTION (fndecl))
15462 push_cfun (DECL_STRUCT_FUNCTION (fndecl));
15463 else
15464 push_struct_function (fndecl);
15466 /* Tentatively set PROP_gimple_lva here, and reset it in gimplify_va_arg_expr
15467 if necessary. */
15468 cfun->curr_properties |= PROP_gimple_lva;
15470 if (asan_sanitize_use_after_scope ())
15471 asan_poisoned_variables = new hash_set<tree> ();
15472 bind = gimplify_body (fndecl, true);
15473 if (asan_poisoned_variables)
15475 delete asan_poisoned_variables;
15476 asan_poisoned_variables = NULL;
15479 /* The tree body of the function is no longer needed, replace it
15480 with the new GIMPLE body. */
15481 seq = NULL;
15482 gimple_seq_add_stmt (&seq, bind);
15483 gimple_set_body (fndecl, seq);
15485 /* If we're instrumenting function entry/exit, then prepend the call to
15486 the entry hook and wrap the whole function in a TRY_FINALLY_EXPR to
15487 catch the exit hook. */
15488 /* ??? Add some way to ignore exceptions for this TFE. */
15489 if (flag_instrument_function_entry_exit
15490 && !DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT (fndecl)
15491 /* Do not instrument extern inline functions. */
15492 && !(DECL_DECLARED_INLINE_P (fndecl)
15493 && DECL_EXTERNAL (fndecl)
15494 && DECL_DISREGARD_INLINE_LIMITS (fndecl))
15495 && !flag_instrument_functions_exclude_p (fndecl))
15497 tree x;
15498 gbind *new_bind;
15499 gimple *tf;
15500 gimple_seq cleanup = NULL, body = NULL;
15501 tree tmp_var, this_fn_addr;
15502 gcall *call;
15504 /* The instrumentation hooks aren't going to call the instrumented
15505 function and the address they receive is expected to be matchable
15506 against symbol addresses. Make sure we don't create a trampoline,
15507 in case the current function is nested. */
15508 this_fn_addr = build_fold_addr_expr (current_function_decl);
15509 TREE_NO_TRAMPOLINE (this_fn_addr) = 1;
15511 x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
15512 call = gimple_build_call (x, 1, integer_zero_node);
15513 tmp_var = create_tmp_var (ptr_type_node, "return_addr");
15514 gimple_call_set_lhs (call, tmp_var);
15515 gimplify_seq_add_stmt (&cleanup, call);
15516 x = builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_EXIT);
15517 call = gimple_build_call (x, 2, this_fn_addr, tmp_var);
15518 gimplify_seq_add_stmt (&cleanup, call);
15519 tf = gimple_build_try (seq, cleanup, GIMPLE_TRY_FINALLY);
15521 x = builtin_decl_implicit (BUILT_IN_RETURN_ADDRESS);
15522 call = gimple_build_call (x, 1, integer_zero_node);
15523 tmp_var = create_tmp_var (ptr_type_node, "return_addr");
15524 gimple_call_set_lhs (call, tmp_var);
15525 gimplify_seq_add_stmt (&body, call);
15526 x = builtin_decl_implicit (BUILT_IN_PROFILE_FUNC_ENTER);
15527 call = gimple_build_call (x, 2, this_fn_addr, tmp_var);
15528 gimplify_seq_add_stmt (&body, call);
15529 gimplify_seq_add_stmt (&body, tf);
15530 new_bind = gimple_build_bind (NULL, body, NULL);
15532 /* Replace the current function body with the body
15533 wrapped in the try/finally TF. */
15534 seq = NULL;
15535 gimple_seq_add_stmt (&seq, new_bind);
15536 gimple_set_body (fndecl, seq);
15537 bind = new_bind;
15540 if (sanitize_flags_p (SANITIZE_THREAD)
15541 && param_tsan_instrument_func_entry_exit)
15543 gcall *call = gimple_build_call_internal (IFN_TSAN_FUNC_EXIT, 0);
15544 gimple *tf = gimple_build_try (seq, call, GIMPLE_TRY_FINALLY);
15545 gbind *new_bind = gimple_build_bind (NULL, tf, NULL);
15546 /* Replace the current function body with the body
15547 wrapped in the try/finally TF. */
15548 seq = NULL;
15549 gimple_seq_add_stmt (&seq, new_bind);
15550 gimple_set_body (fndecl, seq);
15553 DECL_SAVED_TREE (fndecl) = NULL_TREE;
15554 cfun->curr_properties |= PROP_gimple_any;
15556 pop_cfun ();
15558 dump_function (TDI_gimple, fndecl);
15561 /* Return a dummy expression of type TYPE in order to keep going after an
15562 error. */
15564 static tree
15565 dummy_object (tree type)
15567 tree t = build_int_cst (build_pointer_type (type), 0);
15568 return build2 (MEM_REF, type, t, t);
15571 /* Gimplify __builtin_va_arg, aka VA_ARG_EXPR, which is not really a
15572 builtin function, but a very special sort of operator. */
15574 enum gimplify_status
15575 gimplify_va_arg_expr (tree *expr_p, gimple_seq *pre_p,
15576 gimple_seq *post_p ATTRIBUTE_UNUSED)
15578 tree promoted_type, have_va_type;
15579 tree valist = TREE_OPERAND (*expr_p, 0);
15580 tree type = TREE_TYPE (*expr_p);
15581 tree t, tag, aptag;
15582 location_t loc = EXPR_LOCATION (*expr_p);
15584 /* Verify that valist is of the proper type. */
15585 have_va_type = TREE_TYPE (valist);
15586 if (have_va_type == error_mark_node)
15587 return GS_ERROR;
15588 have_va_type = targetm.canonical_va_list_type (have_va_type);
15589 if (have_va_type == NULL_TREE
15590 && POINTER_TYPE_P (TREE_TYPE (valist)))
15591 /* Handle 'Case 1: Not an array type' from c-common.c/build_va_arg. */
15592 have_va_type
15593 = targetm.canonical_va_list_type (TREE_TYPE (TREE_TYPE (valist)));
15594 gcc_assert (have_va_type != NULL_TREE);
15596 /* Generate a diagnostic for requesting data of a type that cannot
15597 be passed through `...' due to type promotion at the call site. */
15598 if ((promoted_type = lang_hooks.types.type_promotes_to (type))
15599 != type)
15601 static bool gave_help;
15602 bool warned;
15603 /* Use the expansion point to handle cases such as passing bool (defined
15604 in a system header) through `...'. */
15605 location_t xloc
15606 = expansion_point_location_if_in_system_header (loc);
15608 /* Unfortunately, this is merely undefined, rather than a constraint
15609 violation, so we cannot make this an error. If this call is never
15610 executed, the program is still strictly conforming. */
15611 auto_diagnostic_group d;
15612 warned = warning_at (xloc, 0,
15613 "%qT is promoted to %qT when passed through %<...%>",
15614 type, promoted_type);
15615 if (!gave_help && warned)
15617 gave_help = true;
15618 inform (xloc, "(so you should pass %qT not %qT to %<va_arg%>)",
15619 promoted_type, type);
15622 /* We can, however, treat "undefined" any way we please.
15623 Call abort to encourage the user to fix the program. */
15624 if (warned)
15625 inform (xloc, "if this code is reached, the program will abort");
15626 /* Before the abort, allow the evaluation of the va_list
15627 expression to exit or longjmp. */
15628 gimplify_and_add (valist, pre_p);
15629 t = build_call_expr_loc (loc,
15630 builtin_decl_implicit (BUILT_IN_TRAP), 0);
15631 gimplify_and_add (t, pre_p);
15633 /* This is dead code, but go ahead and finish so that the
15634 mode of the result comes out right. */
15635 *expr_p = dummy_object (type);
15636 return GS_ALL_DONE;
15639 tag = build_int_cst (build_pointer_type (type), 0);
15640 aptag = build_int_cst (TREE_TYPE (valist), 0);
15642 *expr_p = build_call_expr_internal_loc (loc, IFN_VA_ARG, type, 3,
15643 valist, tag, aptag);
15645 /* Clear the tentatively set PROP_gimple_lva, to indicate that IFN_VA_ARG
15646 needs to be expanded. */
15647 cfun->curr_properties &= ~PROP_gimple_lva;
15649 return GS_OK;
15652 /* Build a new GIMPLE_ASSIGN tuple and append it to the end of *SEQ_P.
15654 DST/SRC are the destination and source respectively. You can pass
15655 ungimplified trees in DST or SRC, in which case they will be
15656 converted to a gimple operand if necessary.
15658 This function returns the newly created GIMPLE_ASSIGN tuple. */
15660 gimple *
15661 gimplify_assign (tree dst, tree src, gimple_seq *seq_p)
15663 tree t = build2 (MODIFY_EXPR, TREE_TYPE (dst), dst, src);
15664 gimplify_and_add (t, seq_p);
15665 ggc_free (t);
15666 return gimple_seq_last_stmt (*seq_p);
15669 inline hashval_t
15670 gimplify_hasher::hash (const elt_t *p)
15672 tree t = p->val;
15673 return iterative_hash_expr (t, 0);
15676 inline bool
15677 gimplify_hasher::equal (const elt_t *p1, const elt_t *p2)
15679 tree t1 = p1->val;
15680 tree t2 = p2->val;
15681 enum tree_code code = TREE_CODE (t1);
15683 if (TREE_CODE (t2) != code
15684 || TREE_TYPE (t1) != TREE_TYPE (t2))
15685 return false;
15687 if (!operand_equal_p (t1, t2, 0))
15688 return false;
15690 /* Only allow them to compare equal if they also hash equal; otherwise
15691 results are nondeterminate, and we fail bootstrap comparison. */
15692 gcc_checking_assert (hash (p1) == hash (p2));
15694 return true;